Docs update: copy documentation from elm-lang.org

- Copy documentation from elm-lang.org (dev branch) to .elm files in
libraries folder
- Added TODO's for stuff that was not found in 0.8 version
- Added Review TODO in json.elm
This commit is contained in:
Mads Flensted-Urech 2013-03-24 13:45:56 +01:00
parent 893e4691e6
commit 441d09c4a7
15 changed files with 371 additions and 28 deletions

View file

@ -1,16 +1,22 @@
-- This library is a way to package up dynamic behavior. It makes it easier to
-- dynamically create dynamic components. See the [original release
-- notes](/blog/announce/version-0.5.0.elm) on this library to get a feel for how
-- it can be used.
module Automaton where
data Automaton a b = Automaton (a -> (b, Automaton a b))
-- Run an automaton on a given signal. The automaton takes in ‘a’ values and returns ‘b’ values. The automaton steps forward whenever the input signal updates.
run : Automaton a b -> Signal a -> Signal b
run (Automaton m0) input =
lift fst $ foldp' (\a (b, Automaton m) -> m a) m0 input
-- Step an automaton forward once with a given input.
step : Automaton a b -> a -> (b, Automaton a b)
step (Automaton m) a = m a
-- Compose two automatons, chaining them together.
(>>>) : Automaton a b -> Automaton b c -> Automaton a c
a1 >>> a2 =
let Automaton m1 = a1
@ -19,23 +25,29 @@ a1 >>> a2 =
(c,m2') = m2 b
in (c, m1' >>> m2'))
-- Compose two automatons, chaining them together.
(<<<) : Automaton b c -> Automaton a b -> Automaton a c
a2 <<< a1 = a1 >>> a2
-- Combine a list of automatons into a single automaton that produces a list.
combine : [Automaton a b] -> Automaton a [b]
combine autos =
Automaton (\a -> let (bs,autos') = unzip $ map (\(Automaton m) -> m a) autos in
(bs, combine autos'))
-- Create an automaton with no memory. It just applies the given function to every input.
pure : (a -> b) -> Automaton a b
pure f = Automaton (\x -> (f x, pure f))
-- Create an automaton with no memory. It just applies the given function to every input.
init : b -> (a -> b -> b) -> Automaton a b
init s step = Automaton (\a -> let s' = step a s in (s', init s' step))
-- Create an automaton with hidden state. Requires an initial state and a step function to step the state forward and produce an output.
init' : s -> (a -> s -> (b,s)) -> Automaton a b
init' s step = Automaton (\a -> let (b,s') = step a s in (b , init' s' step))
-- Count the number of steps taken.
count : Automaton a Int
count = init 0 (\_ c -> c + 1)
@ -56,6 +68,7 @@ stepDrag (press,pos) (ds,form) =
else (let form' = uncurry move (vecSub pos p0) form in
(form', (Listen,form')))
-- Create a draggable form that can be dynamically created and added to a scene.
draggable : Form -> Automaton (Bool,(Int,Int)) Form
draggable form = init' (Listen,form) stepDrag
@ -68,4 +81,5 @@ draggable form = init' (Listen,form) stepDrag
Speeding things up is a really low priority. Language features and
libraries with nice APIs and are way more important!
--}
--}

View file

@ -1,19 +1,50 @@
-- Library for working with dates. It is still a work in progress, so email
-- the mailing list if you are having issues with internationalization or
-- locale formatting or something.
module Date where
-- Represents the days of the week.
data Day = Mon | Tue | Wed | Thu | Fri | Sat | Sun
-- Represents the month of the year.
data Month = Jan | Feb | Mar | Apr
| May | Jun | Jul | Aug
| Sep | Oct | Nov | Dec
read : String -> Date
-- Attempt to read a date from a string.
read : String -> Maybe Date
-- Convert a date into a time since midnight (UTC) of 1 January 1990 (i.e.
-- [UNIX time](http://en.wikipedia.org/wiki/Unix_time)). Given the date 23 June
-- 1990 at 11:45AM this returns the corresponding time.
toTime : Date -> Time
-- Extract the year of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the integer `1990`.
year : Date -> Int
-- Extract the month of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the Month `Jun` as defined below.
month : Date -> Month
-- Extract the day of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the integer `23`.
day : Date -> Int
-- Extract the day of the week for a given date. Given the date 23 June
-- 1990 at 11:45AM this returns the Day `Thu` as defined below.
dayOfWeek : Date -> Day
-- Extract the hour of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the integer `11`.
hour : Date -> Int
-- Extract the minute of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the integer `45`.
minute : Date -> Int
-- Extract the second of a given date. Given the date 23 June 1990 at 11:45AM
-- this returns the integer `0`.
second : Date -> Int

View file

@ -16,6 +16,7 @@ data NColor = Red | Black
data Dict k v = Node NColor k v (Dict k v) (Dict k v) | Empty
-- Create an empty dictionary.
empty : Dict k v
empty = Empty
@ -114,6 +115,7 @@ max t =
}
--}
-- Lookup the value associated with a key.
lookup : k -> Dict k v -> Maybe v
lookup k t =
case t of
@ -124,6 +126,7 @@ lookup k t =
EQ -> Just v
GT -> lookup k r
-- Find the value associated with a key. If the key is not found, return the default value.
findWithDefault : v -> k -> Dict k v -> v
findWithDefault base k t =
case t of
@ -135,6 +138,7 @@ findWithDefault base k t =
GT -> findWithDefault base k r
{--
-- Find the value associated with a key. If the key is not found, there will be a runtime error.
find k t =
case t of
{ Empty -> Error.raise "Key was not found in dictionary!"
@ -146,8 +150,9 @@ find k t =
}
--}
-- Does t contain k?
-- Determine if a key is in a dictionary.
member : k -> Dict k v -> Bool
-- Does t contain k?
member k t = Maybe.isJust $ lookup k t
rotateLeft : Dict k v -> Dict k v
@ -201,6 +206,7 @@ ensureBlackRoot t =
Node Red k v l r -> Node Black k v l r
_ -> t
-- Insert a key-value pair into a dictionary. Replaces value when there is a collision.
-- Invariant: t is a valid left-leaning rb tree *)
insert : k -> v -> Dict k v -> Dict k v
insert k v t =
@ -223,6 +229,7 @@ insert k v t =
else new_t)
--}
-- Create a dictionary with one key-value pair.
singleton : k -> v -> Dict k v
singleton k v = insert k v Empty
@ -303,6 +310,7 @@ deleteMax t =
in ensureBlackRoot (del t)
--}
-- Remove a key-value pair from a dictionary. If the key is not found, no changes are made.
remove : k -> Dict k v -> Dict k v
remove k t =
let eq_and_noRightNode t =
@ -335,43 +343,53 @@ remove k t =
Error.raise "invariants broken after remove")
--}
-- Apply a function to all values in a dictionary.
map : (a -> b) -> Dict k a -> Dict k b
map f t =
case t of
Empty -> Empty
Node c k v l r -> Node c k (f v) (map f l) (map f r)
-- Fold over the key-value pairs in a dictionary, in order from lowest key to highest key.
foldl : (k -> v -> b -> b) -> b -> Dict k v -> b
foldl f acc t =
case t of
Empty -> acc
Node _ k v l r -> foldl f (f k v (foldl f acc l)) r
-- Fold over the key-value pairs in a dictionary, in order from highest key to lowest key.
foldr : (k -> v -> b -> b) -> b -> Dict k v -> b
foldr f acc t =
case t of
Empty -> acc
Node _ k v l r -> foldr f (f k v (foldr f acc r)) l
-- Combine two dictionaries. If there is a collision, preference is given to the first dictionary.
union : Dict k v -> Dict k v -> Dict k v
union t1 t2 = foldl insert t2 t1
-- Keep a key-value pair when its key appears in the second dictionary. Preference is given to values in the first dictionary.
intersect : Dict k v -> Dict k v -> Dict k v
intersect t1 t2 =
let combine k v t = if k `member` t2 then insert k v t else t
in foldl combine empty t1
-- Keep a key-value pair when its key does not appear in the second dictionary. Preference is given to the first dictionary.
diff : Dict k v -> Dict k v -> Dict k v
diff t1 t2 = foldl (\k v t -> remove k t) t1 t2
-- Get all of the keys in a dictionary.
keys : Dict k v -> [k]
keys t = foldr (\k v acc -> k :: acc) [] t
-- Get all of the values in a dictionary.
values : Dict k v -> [v]
values t = foldr (\k v acc -> v :: acc) [] t
-- Convert a dictionary into an association list of key-value pairs.
toList : Dict k v -> [(k,v)]
toList t = foldr (\k v acc -> (k,v) :: acc) [] t
-- Convert an association list into a dictionary.
fromList : [(k,v)] -> Dict k v
fromList assocs = List.foldl (uncurry insert) empty assocs

View file

@ -3,24 +3,34 @@ module Either where
import List
-- Represents any data that can take two different types.
--
-- This can also be used for error handling `(Either String a)` where error
-- messages are stored on the left, and the correct values (&ldquo;right&rdquo; values) are stored on the right.
data Either a b = Left a | Right b
-- Apply the first function to a `Left` and the second function to a `Right`.
-- This allows the extraction of a value from an `Either`.
either : (a -> c) -> (b -> c) -> Either a b -> c
either f g e = case e of { Left x -> f x ; Right y -> g y }
-- True if the value is a `Left`.
isLeft : Either a b -> Bool
isLeft e = case e of { Left _ -> True ; _ -> False }
-- True if the value is a `Right`.
isRight : Either a b -> Bool
isRight e = case e of { Right _ -> True ; _ -> False }
-- Keep only the values held in `Left` values.
--lefts : [Either a b] -> [a]
lefts es = List.filter isLeft es
-- Keep only the values held in `Right` values.
--rights : [Either a b] -> [b]
rights es = List.filter isRight es
--partition : [Either a b] -> ([a],[b])
partition es = List.partition isLeft es
-- Split into two lists, lefts on the left and rights on the right. So we
-- have the equivalence: `(partition es == (lefts es, rights es))`
-- partition : [Either a b] -> ([a],[b])
partition es = List.partition isLeft es

View file

@ -11,7 +11,10 @@ module Graphics.Color (rgba,rgb,hsva,hsv,
data Color = Color Int Int Int Float
-- Create RGB colors with an alpha component for transparency. The alpha component is specified with numbers between 0 and 1.
rgba = Color
-- Create RGB colors from numbers between 0 and 255 inclusive.
rgb r g b = Color r g b 1
red = Color 255 0 0 1
@ -38,8 +41,22 @@ purple = Color 128 0 128 1
forestGreen = Color 34 139 34 1
violet = Color 238 130 238 1
-- Produce a &ldquo;complementary color&rdquo;. The two colors will accent each other.
complement : Color -> Color
-- Create HSV colors with an alpha component for transparency. The alpha component is specified with numbers between 0 and 1.
hsva : Int -> Float -> Float -> Float -> Color
-- Create HSV colors. HSV stands for hue-saturation-value.
--
-- Hue is a degree from 0 to 360 representing a color wheel: red at 0&deg;, green at 120&deg;, blue at 240&deg;, and red again at 360&deg;.
-- This makes it easy to cycle through colors and compute color complements, triads, tetrads, etc.
--
-- Saturation is a number between 1 and 0 where lowering this number makes your color more grey. This can help you tone a color down.
--
-- Value is also a number between 1 and 0. Lowering this number makes your color more black.
--
-- Look up the &ldquo;HSV cylinder&rdquo; for more information.
hsv : Int -> Float -> Float -> Color
data Gradient

View file

@ -4,21 +4,57 @@ module Graphics.Text where
import Native.Graphics.Text as T
-- Convert a string into text which can be styled and displayed.
toText : String -> Text
typeface : String -> Text -> Text
href : String -> Text -> Text
height : Float -> Text -> Text
color : Color -> Text -> Text
bold : Text -> Text
italic : Text -> Text
overline : Text -> Text
-- Set the typeface of some text. The first argument should be a comma separated listing of the desired typefaces
-- "helvetica, arial, sans-serif"
-- Works the same as the CSS font-family property.
typeface : String -> Text -> Text
-- Switch to a monospace typeface. Good for code snippets.
monospace : Text -> Text
-- Make text big and noticable.
header : Text -> Text
-- Create a link.
href : String -> Text -> Text
-- Set the height of text in \"ems\". 1em is the normal height of text. 2ems is twice that height.
height : Float -> Text -> Text
-- Set the color of a string.
color : Color -> Text -> Text
-- Make a string bold.
bold : Text -> Text
-- Italicize a string.
italic : Text -> Text
-- Draw a line above a string.
overline : Text -> Text
-- Underline a string.
underline : Text -> Text
-- Draw a line through a string.
strikeThrough : Text -> Text
-- Display justified, styled text.
justified : Text -> Element
centered : Text -> Element
righted : Text -> Element
text : Text -> Element
-- Display centered, styled text.
centered : Text -> Element
-- Display right justified, styled text.
righted : Text -> Element
-- Display styled text.
text : Text -> Element
-- Convert anything to it's textual representation and make it displayable in browser
-- asText = text . monospace . show
-- Excellent for debugging
asText : a -> Element

View file

@ -5,17 +5,39 @@ module JavaScript where
-- To Elm
toString : JSString -> String
-- Requires that the input array be uniform (all members have the same type)
toList : JSArray a -> [a]
toInt : JSNumber -> Int
toFloat : JSNumber -> Float
-- Conversion from JavaScript boolean values to Elm boolean values.
toBool : JSBool -> Bool
-- From Elm
fromString : String -> JSString
-- Produces a uniform JavaScript array with all members of the same type.
fromList : [a] -> JSArray a
fromInt : Int -> JSNumber
fromFloat : Float -> JSNumber
-- Conversion from Elm boolean values to JavaScript boolean values.
fromBool : Bool -> JSBool
{-- TODO: only found in docs
, ("castTupleToJSTuple2" , "(a,b) -> JSTuple2 a b", "A JSTupleN is an array of size N with nonuniform types. Each member can have a different type.")
, ("castJSTupleToTuple2" , "JSTuple2 a b -> (a,b)", "")
, ("castTupleToJSTuple3" , "(a,b,c) -> JSTuple3 a b c", "")
, ("castJSTupleToTuple3" , "JSTuple3 a b c > (a,b,c)", "")
, ("castTupleToJSTuple4" , "(a,b,c,d) -> JSTuple4 a b c d", "")
, ("castJSTupleToTuple4" , "JSTuple4 a b c d -> (a,b,c,d)", "")
, ("castTupleToJSTuple5" , "(a,b,c,d,e) -> JSTuple5 a b c d e", "")
, ("castJSTupleToTuple5" , "JSTuple5 a b c d e -> (a,b,c,d,e)", "")
--}

View file

@ -1,11 +1,14 @@
-- TOOD: Evan please review texts
module Json where
import Dict as Dict
import JavaScript as JS
import Native.Json as Native
-- This datatype can represent all valid values that can be held in a JSON object.
-- In Elm, a proper JSON object is represented as a (Dict String Value) which is a mapping from strings to Json Values.
data Value
= String String
| Number Float
@ -17,18 +20,25 @@ data Value
-- String Converters
-- Convert a proper JSON object into a string.
toString : Value -> String
toString v = JS.toString (Native.toPrettyJSString "" v)
-- Convert a proper JSON object into a prettified string.
-- The first argument is a separator token (e.g. \" \", \"\\n\", etc.) that will be used for indentation in the prettified string version of the JSON object.
toPrettyString : String -> Value -> String
toPrettyString sep v = JS.toString (Native.toPrettyJSString sep v)
-- Convert a proper JSON object into a JavaScript string.
-- Note that the type JSString seen here is not the same as the type constructor JsonString used elsewhere in this module.
toJSString : Value -> JSString
toJSString v = Native.toPrettyJSString "" v
-- Parse a string representation of a proper JSON object into its Elm's representation.
fromString : String -> Maybe Value
fromString s = Native.fromJSString (JS.fromString s)
-- Parse a JavaScript string representation of a proper JSON object into its Elm's representation.
fromJSString : JSString -> Maybe Value
@ -52,6 +62,7 @@ object v = case v of { Object o -> o ; _ -> Dict.empty }
-- Extract Elm values from dictionaries of Json values
-- Find a value in a Json Object using the passed get function. If the key is not found, this returns the given default/base value.
find get base =
let f key dict =
case Dict.lookup key dict of
@ -59,17 +70,22 @@ find get base =
Just v -> get v
in f
-- Find a string value in an Elm Json object. If the key is not found or the value found is not a string, this returns the empty string.
findString : String -> Dict String Value -> String
findString = find string ""
-- Find a number value in an Elm Json object. If the key is not found or the value found is not a number, this returns 0
findNumber : String -> Dict String Value -> Float
findNumber = find number 0
-- Find a boolean value in an Elm Json object. If the key is not found or the value found is not a boolean, this returns the False.
findBoolean : String -> Dict String Value -> Bool
findBoolean = find boolean False
-- Find an array value in an Elm Json object. If the key is not found or the value found is not an array, this returns an empty list.
findArray : String -> Dict String Value -> [Value]
findArray = find array []
-- Find an object value in an Elm Json object. If the key is not found or the value found is not an object, this returns an empty object.
findObject : String -> Dict String Value -> Dict String Value
findObject = find object Dict.empty

View file

@ -1,7 +1,6 @@
-- These are nicely curated inputs from the keyboard. See the
-- [Keyboard.Raw library](/docs/Signal/KeyboardRaw.elm) for a
-- lower-level interface that will let you define more complicated behavior.
module Keyboard where
import Native.Keyboard as N

View file

@ -4,36 +4,77 @@ module List where
import Native.Utils (min, max)
import Native.List as L
-- Extract the first element of a list. List must be non-empty.
head : [a] -> a
-- Extract the elements after the head of the list. List must be non-empty.
tail : [a] -> [a]
-- Extract the last element of a list. List must be non-empty.
last : [a] -> a
-- Apply a function to every element of a list.
map : (a -> b) -> [a] -> [b]
-- Reduce a list from the left.
foldl : (a -> b -> b) -> b -> [a] -> b
-- Reduce a list from the right.
foldr : (a -> b -> b) -> b -> [a] -> b
-- Reduce a list from the left without a base case. List must be non-empty.
foldl1 : (a -> a -> a) -> [a] -> a
-- Reduce a list from the right without a base case. List must be non-empty.
foldr1 : (a -> a -> a) -> [a] -> a
-- Reduce a list from the left, building up all of the intermediate results into a list.
scanl : (a -> b -> b) -> b -> [a] -> [b]
-- Same as scanl but it doesn't require a base case. List must be non-empty.
scanl1 : (a -> a -> a) -> [a] -> [a]
-- Filter out elements which do not satisfy the predicate.
filter : (a -> Bool) -> [a] -> [a]
-- Determine the length of a list.
length : [a] -> Int
-- Reverse a list.
reverse : [a] -> [a]
-- Check to see if all elements satisfy the predicate.
all : (a -> Bool) -> [a] -> Bool
-- Check to see if any elements satisfy the predicate.
any : (a -> Bool) -> [a] -> Bool
-- Check to see if all elements are True.
and : [Bool] -> Bool
-- Check to see if any elements are True.
or : [Bool] -> Bool
-- Flatten a list of lists.
concat : [[a]] -> [a]
-- Map a given function onto a list and flatten the resulting lists. (concatMap f xs == concat (map f xs))
concatMap : (a -> [b]) -> [a] -> [b]
concatMap f = L.concat . L.map f
-- Get the sum of the list elements.
sum = L.foldl (+) 0
-- Get the product of the list elements.
product = L.foldl (*) 1
-- Find the highest number in a non-empty list.
maximum = L.foldl1 max
-- Find the lowest number in a non-empty list.
minimum = L.foldl1 min
-- Split a list based on the predicate.
partition : (a -> Bool) -> [a] -> ([a],[a])
partition pred lst =
case lst of
@ -41,18 +82,28 @@ partition pred lst =
x::xs -> let (bs,cs) = partition pred xs in
if pred x then (x::bs,cs) else (bs,x::cs)
zipWith : (a -> b -> c) -> [a] -> [b] -> [c]
-- Combine two lists, combining them into tuples pairwise. If one input list has extra elements (it is longer), those elements are dropped.
zip : [a] -> [b] -> [(a,b)]
-- Combine two lists, combining them with the given function. If one input list has extra elements (it is longer), those elements are dropped.
zipWith : (a -> b -> c) -> [a] -> [b] -> [c]
-- Decompose a list of tuples
unzip : [(a,b)] -> ([a],[b])
unzip pairs =
case pairs of
[] -> ([],[])
(x,y)::ps -> let (xs,ys) = (unzip ps) in (x::xs,y::ys)
-- Split a list
-- split "," "hello,there,friend" == ["hello", "there", "friend"]
split : [a] -> [a] -> [[a]]
-- Places the given value between all of the lists in the second argument and concatenates the result.
-- join xs xss = concat (intersperse xs xss)
join : [a] -> [[a]] -> [a]
-- Places the given value between all members of the given list.
intersperse : a -> [a] -> [a]
intersperse sep xs =
case xs of
@ -60,3 +111,22 @@ intersperse sep xs =
[a] -> [a]
[] -> []
{-- TODO: only found in docs
-- Add an element to the front of a list
-- a :: [b,c] = [a,b,c]
(::) : a -> [a] -> [a]
-- Appends two lists.
(++) : [a] -> [a] -> [a]
-- Take the first n members of a list.
-- take 2 [1,2,3,4]) ==> [1,2]
take : Int -> [a] -> [a]
-- Drop the first n members of a list.
-- drop 2 [1,2,3,4]) ==> [3,4]
drop : Int -> [a] -> [a]
--}

View file

@ -11,41 +11,54 @@ import List as List
type Set t = Dict t ()
-- Create an empty set.
empty : Set t
empty = Dict.empty
-- Create a set with one value.
singleton : t -> Set t
singleton k = Dict.singleton k ()
-- Insert a value into a set.
insert : t -> Set t -> Set t
insert k = Dict.insert k ()
-- Remove a value from a set. If the value is not found, no changes are made.
remove : t -> Set t -> Set t
remove = Dict.remove
-- Determine if a value is in a set.
member : t -> Set t -> Bool
member = Dict.member
-- Get the union of two sets. Keep all values.
union : Set t -> Set t -> Set t
union = Dict.union
-- Get the intersection of two sets. Keeps values that appear in both sets.
intersect : Set t -> Set t -> Set t
intersect = Dict.intersect
-- Get the difference between the first set and the second. Keeps values that do not appear in the second set.
diff : Set t -> Set t -> Set t
diff = Dict.diff
-- Convert a set into a list.
toList : Set t -> [t]
toList = Dict.keys
-- Convert a list into a set, removing any duplicates.
fromList : [t] -> Set t
fromList xs = List.foldl (\k t -> Dict.insert k () t) empty xs
-- Fold over the values in a set, in order from lowest to highest.
foldl : (a -> b -> b) -> b -> Set a -> b
foldl f b s = Dict.foldl (\k _ b -> f k b) b s
-- Fold over the values in a set, in order from highest to lowest.
foldr : (a -> b -> b) -> b -> Set a -> b
foldr f b s = Dict.foldr (\k _ b -> f k b) b s
-- Map a function onto a set, creating a new set with no duplicates.
map : (a -> b) -> Set a -> Set b
map f s = fromList (List.map f (toList s))
map f s = fromList (List.map f (toList s))

View file

@ -1,12 +1,24 @@
-- The library for general signal manipulation. Some useful functions for
-- working with time (e.g. setting FPS) and combining signals and time (e.g.
-- delaying updates, getting timestamps) can be found in the
-- [`Time`](/docs/Signal/Time.elm) library.
--
-- Note: There are lift functions up to `lift8`.
module Signal where
import Native.Signal as Native
-- Create a constant signal that never changes.
constant : a -> Signal a
-- Transform a signal with a given function.
lift : (a -> b) -> Signal a -> Signal b
-- Combine two signals with a given function.
lift2 : (a -> b -> c) -> Signal a -> Signal b -> Signal c
-- Combine three signals with a given function.
lift3 : (a -> b -> c -> d) -> Signal a -> Signal b -> Signal c -> Signal d
lift4 : (a -> b -> c -> d -> e) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e
lift5 : (a -> b -> c -> d -> e -> f) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f
@ -14,21 +26,98 @@ lift6 : (a -> b -> c -> d -> e -> f -> g) -> Signal a -> Signal b -> Signal c ->
lift7 : (a -> b -> c -> d -> e -> f -> g -> h) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal g -> Signal h
lift8 : (a -> b -> c -> d -> e -> f -> g -> h -> i) -> Signal a -> Signal b -> Signal c -> Signal d -> Signal e -> Signal f -> Signal g -> Signal h -> Signal i
-- Create a past-dependent signal. Each value given on the input signal will
-- be accumulated, producing a new output value.
--
-- For instance, `(foldp (\\t acc -> acc + 1) 0 (Time.every second))` increments every second.
foldp : (a -> b -> b) -> b -> Signal a -> Signal b
-- Merge two signals into one, biased towards the first signal if both signals
-- update at the same time.
merge : Signal a -> Signal a -> Signal a
-- Merge many signals into one, biased towards the left-most signal if multiple
-- signals update simultaneously.
merges : [Signal a] -> Signal a
-- Merge two signals into one, but distinguishing the values by marking the first
-- signal as `Left` and the second signal as `Right`. This allows you to easily
-- fold over non-homogeneous inputs.
mergeEither : Signal a -> Signal b -> Signal (Either a b)
-- Count the number of events that have occured.
count : Signal a -> Signal Int
-- Count the number of events that have occured that satisfy a given predicate.
countIf : (a -> Bool) -> Signal a -> Signal Int
-- Keep only events that satisfy the given predicate. Elm does not allow
-- undefined signals, so a base case must be provided in case the predicate is
-- never satisfied.
keepIf : (a -> Bool) -> a -> Signal a -> Signal a
-- Drop events that satisfy the given predicate. Elm does not allow undefined
-- signals, so a base case must be provided in case the predicate is never
-- satisfied.
dropIf : (a -> Bool) -> a -> Signal a -> Signal a
-- Keep events only when the first signal is true. When the first signal becomes
-- true, the most recent value of the second signal will be propagated. Until
-- the first signal becomes false again, all events will be propagated. Elm does
-- not allow undefined signals, so a base case must be provided in case the first
-- signal is never true.
keepWhen : Signal Bool -> a -> Signal a -> Signal a
-- Drop events when the first signal is true. When the first signal becomes false,
-- the most recent value of the second signal will be propagated. Until the first
-- signal becomes true again, all events will be propagated. Elm does not allow
-- undefined signals, so a base case must be provided in case the first signal is
-- always true.
dropWhen : Signal Bool -> a -> Signal a -> Signal a
-- Drop sequential repeated values. For example, if a signal produces the
-- sequence `[1,1,2,2,1]`, it becomes `[1,2,1]` by dropping the values that
-- are the same as the previous value.
dropRepeats : Signal a -> Signal a
-- Sample from the second input every time an event occurs on the first input.
-- For example, `(sampleOn clicks (every second))` will give the approximate
-- time of the latest click.
sampleOn : Signal a -> Signal b -> Signal b
timestamp : Signal a -> Signal (Time, a)
-- Add a timestamp to any signal. Timestamps increase monotonically. Each timestamp is
-- related to a specfic event, so `Mouse.x` and `Mouse.y` will always have the same
-- timestamp because they both rely on the same underlying event.
timestamp : Signal a -> Signal (Time, a)
-- Delay a signal by a certain amount of time. So `(delay second Mouse.clicks)`
-- will update one second later than any mouse click.
delay : Time -> Signal a -> Signal a
{-- TODO: only found in docs
, ("average", "Int -> Signal Number -> Signal Float", [markdown|
Takes an integer `n` and a signal of numbers. Computes the running
average of the signal over the last `n` events.
So `(average 20 (fps 40))` would be the average time between the frames for
the last 20 frames.|])
, ("foldp1", "(a -> a -> a) -> Signal a -> Signal a", [markdown|
Create a past-dependent signal. The first value on the signal is used
as the base case.|])
, ("foldp'", "(a -> b -> b) -> (a -> b) -> Signal a -> Signal b", [markdown|
Just like foldp, but instead of a base case, you provide a function to be
applied to the first value, creating the base case.|])
[ ("(<~)", "(a -> b) -> Signal a -> Signal b", [markdown|
An alias for `lift`. A prettier way to apply a
function to the current value of a signal.|])
, ("(~)", "Signal (a -> b) -> Signal a -> Signal b", [markdown|
Signal application. This takes two signals, holding a function and
a value. It applies the current function to the current value.
So the following expressions are equivalent:
scene <~ Mouse.x ~ Mouse.y
lift2 scene Mouse.x Mouse.y|])
--}

View file

@ -1,6 +1,4 @@
-- Library for working with time. Type `Time` represents some number of
-- milliseconds.
-- Library for working with time. Type `Time` represents some number of milliseconds.
module Time where
import Native.Time as T
@ -50,3 +48,15 @@ fpsWhen : Number -> Signal Bool -> Signal Time
-- Takes a time interval t. The resulting signal is the current time,
-- updated every t.
every : Time -> Signal Time
-- Takes a time `t` and any signal. The resulting boolean signal
-- is true for time `t` after every event on the input signal.
-- So ``(second `since` Mouse.clicks)`` would result in a signal
-- that is true for one second after each mouse click and false
-- otherwise.
since : Time -> Signal a -> Signal Bool
{-- TODO: Only found in docs
, ("timeOf", "Signal a -> Signal Time", [markdown|
Same as `timestamp` but it throws out the incoming value. So `(timeOf == lift fst . timestamp)`.|])
--}

View file

@ -1,6 +1,5 @@
-- This is an early version of the touch library. It will likely grow to
-- include gestures that would be useful for both games and web-pages.
module Touch where
import Native.Touch as T

View file

@ -1,6 +1,5 @@
-- A library for low latency HTTP communication. See the HTTP library for
-- standard requests like GET, POST, etc.
module WebSocket where
import Native.WebSocket as WS