fay-base-0.1.0.0: The base package for Fay.

Safe HaskellNone

Prelude

Synopsis

Documentation

data Char

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) characters (see http://www.unicode.org/ for details). This set extends the ISO 8859-1 (Latin-1) character set (the first 256 characters), which is itself an extension of the ASCII character set (the first 128 characters). A character literal in Haskell has type Char.

To convert a Char to or from the corresponding Int value defined by Unicode, use toEnum and fromEnum from the Enum class respectively (or equivalently ord and chr).

type String = [Char]

A String is a list of characters. String constants in Haskell are values of type String.

data Double

Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.

Instances

Enum Double 
Eq Double 
Floating Double 
Fractional Double 
Data Double 
Num Double 
Ord Double 
Read Double 
Real Double 
RealFloat Double 
RealFrac Double 
Show Double 
Typeable Double 
Foreign Double

All numbers in JS are double.

Fractional Double 
Ord Double 
Num Double 

data Int

A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]. The exact range for a given implementation can be determined by using minBound and maxBound from the Bounded class.

Instances

Bounded Int 
Enum Int 
Eq Int 
Integral Int 
Data Int 
Num Int 
Ord Int 
Read Int 
Real Int 
Show Int 
Typeable Int 
Foreign Int

Some numbers in JS are int.

Integral Int 
Enum Int 
Ord Int 
Num Int 

data Bool

Constructors

False 
True 

class Read a

Parsing of Strings, producing values.

Minimal complete definition: readsPrec (or, for GHC only, readPrec)

Derived instances of Read make the following assumptions, which derived instances of Show obey:

  • If the constructor is defined to be an infix operator, then the derived Read instance will parse only infix applications of the constructor (not the prefix form).
  • Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
  • If the constructor is defined using record syntax, the derived Read will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration.
  • The derived Read instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.

For example, given the declarations

 infixr 5 :^:
 data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Read in Haskell 98 is equivalent to

 instance (Read a) => Read (Tree a) where

         readsPrec d r =  readParen (d > app_prec)
                          (\r -> [(Leaf m,t) |
                                  ("Leaf",s) <- lex r,
                                  (m,t) <- readsPrec (app_prec+1) s]) r

                       ++ readParen (d > up_prec)
                          (\r -> [(u:^:v,w) |
                                  (u,s) <- readsPrec (up_prec+1) r,
                                  (":^:",t) <- lex s,
                                  (v,w) <- readsPrec (up_prec+1) t]) r

           where app_prec = 10
                 up_prec = 5

Note that right-associativity of :^: is unused.

The derived instance in GHC is equivalent to

 instance (Read a) => Read (Tree a) where

         readPrec = parens $ (prec app_prec $ do
                                  Ident "Leaf" <- lexP
                                  m <- step readPrec
                                  return (Leaf m))

                      +++ (prec up_prec $ do
                                  u <- step readPrec
                                  Symbol ":^:" <- lexP
                                  v <- step readPrec
                                  return (u :^: v))

           where app_prec = 10
                 up_prec = 5

         readListPrec = readListPrecDefault

Instances

Read Bool 
Read Char 
Read Double 
Read Float 
Read Int 
Read Integer 
Read Ordering 
Read Word 
Read () 
Read Lexeme 
Read SerializeContext 
Read a => Read [a] 
(Integral a, Read a) => Read (Ratio a) 
Read a => Read (Maybe a) 
Read a => Read (Maybe a) 
(Read a, Read b) => Read (a, b) 
(Ix a, Read a, Read b) => Read (Array a b) 
(Read a, Read b, Read c) => Read (a, b, c) 
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) 
(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) 
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h) => Read (a, b, c, d, e, f, g, h) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i) => Read (a, b, c, d, e, f, g, h, i) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j) => Read (a, b, c, d, e, f, g, h, i, j) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k) => Read (a, b, c, d, e, f, g, h, i, j, k) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l) => Read (a, b, c, d, e, f, g, h, i, j, k, l) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Read a, Read b, Read c, Read d, Read e, Read f, Read g, Read h, Read i, Read j, Read k, Read l, Read m, Read n, Read o) => Read (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

class Show a

Conversion of values to readable Strings.

Minimal complete definition: showsPrec or show.

Derived instances of Show have the following properties, which are compatible with derived instances of Read:

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

For example, given the declarations

 infixr 5 :^:
 data Tree a =  Leaf a  |  Tree a :^: Tree a

the derived instance of Show is equivalent to

 instance (Show a) => Show (Tree a) where

        showsPrec d (Leaf m) = showParen (d > app_prec) $
             showString "Leaf " . showsPrec (app_prec+1) m
          where app_prec = 10

        showsPrec d (u :^: v) = showParen (d > up_prec) $
             showsPrec (up_prec+1) u .
             showString " :^: "      .
             showsPrec (up_prec+1) v
          where up_prec = 5

Note that right-associativity of :^: is ignored. For example,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)".

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Integer 
Show Ordering 
Show Word 
Show () 
Show DataType 
Show Constr 
Show DataRep 
Show ConstrRep 
Show Fixity 
Show TypeRep 
Show TyCon 
Show CompileConfig 
Show CompileState 
Show CompileReader 
Show Mapping 
Show CompileError 
Show JsStmt 
Show JsExp 
Show JsName 
Show JsLit 
Show FundamentalType 
Show SerializeContext 
Show ModuleScope 
Show Rational 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio a) 
Show a => Show (Maybe a) 
Show a => Show (Maybe a) 
(Show a, Show b) => Show (a, b) 
(Show a, Show b, Show c) => Show (a, b, c) 
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) 
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) 
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

class Eq a where

The Eq class defines equality (==) and inequality (/=). All the basic datatypes exported by the Prelude are instances of Eq, and Eq may be derived for any datatype whose constituents are also instances of Eq.

Minimal complete definition: either == or /=.

Methods

(==) :: a -> a -> Bool

(/=) :: a -> a -> Bool

Instances

Eq Bool 
Eq Char 
Eq Double 
Eq Float 
Eq Int 
Eq Integer 
Eq Ordering 
Eq Word 
Eq () 
Eq Constr

Equality of constructors

Eq DataRep 
Eq ConstrRep 
Eq Fixity 
Eq TypeRep 
Eq TyCon 
Eq JsStmt 
Eq JsExp 
Eq JsName 
Eq JsLit 
Eq SerializeContext 
Eq a => Eq [a] 
Eq a => Eq (Ratio a) 
Eq a => Eq (Maybe a) 
(Eq a, Eq b) => Eq (a, b) 
(Eq a, Eq b, Eq c) => Eq (a, b, c) 
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) 
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 

(==) :: Eq a => a -> a -> Bool

(/=) :: Eq a => a -> a -> Bool

data Maybe a Source

Maybe type.

Constructors

Just a 
Nothing 

Instances

(Typeable (Maybe a), Data a) => Data (Maybe a) 
Read a => Read (Maybe a) 
Show a => Show (Maybe a) 
Typeable a => Typeable (Maybe a) 

maybe :: t -> (t1 -> t) -> Maybe t1 -> tSource

(>>=) :: Fay a -> (a -> Fay b) -> Fay bSource

Monomorphic bind for Fay.

(>>) :: Fay a -> Fay b -> Fay bSource

Monomorphic then for Fay.

return :: a -> Fay aSource

Monomorphic return for Fay.

when :: Bool -> Fay a -> Fay ()Source

forM_ :: [t] -> (t -> Fay a) -> Fay ()Source

mapM_ :: (a -> Fay b) -> [a] -> Fay ()Source

(=<<) :: (a -> Fay b) -> Fay a -> Fay bSource

sequence :: [Fay a] -> Fay [a]Source

Evaluate each action in the sequence from left to right, and collect the results.

sequence_ :: [Fay a] -> Fay ()Source

(*) :: Num a => a -> a -> aSource

(+) :: Num a => a -> a -> aSource

(-) :: Num a => a -> a -> aSource

class (Eq a, Ord a) => Ord a whereSource

Methods

(<) :: a -> a -> BoolSource

(<=) :: a -> a -> BoolSource

(>) :: a -> a -> BoolSource

(>=) :: a -> a -> BoolSource

Instances

Ord Char 
Ord Double 
Ord Int 

data Ordering Source

Constructors

GT 
LT 
EQ 

compare :: Ord a => a -> a -> OrderingSource

succ :: Num a => a -> aSource

pred :: Num a => a -> aSource

enumFrom :: Num a => a -> [a]Source

enumFromTo :: (Ord t, Num t) => t -> t -> [t]Source

enumFromBy :: Num t => t -> t -> [t]Source

enumFromThen :: Num t => t -> t -> [t]Source

enumFromByTo :: (Ord t, Num t) => t -> t -> t -> [t]Source

enumFromThenTo :: (Ord t, Num t) => t -> t -> t -> [t]Source

(/) :: Fractional a => a -> a -> aSource

fromIntegral :: Int -> DoubleSource

fromIntegral :: Int -> DoubleSource

(&&) :: Bool -> Bool -> Bool

Boolean "and"

(||) :: Bool -> Bool -> Bool

Boolean "or"

show :: Automatic a -> StringSource

Uses JSON.stringify.

error :: String -> aSource

Throws a JavaScript error.

undefined :: aSource

Throws “undefined” via error.

data Either a b Source

Either type.

Constructors

Left a 
Right b 

either :: (a -> c) -> (b -> c) -> Either a b -> cSource

until :: (a -> Bool) -> (a -> a) -> a -> aSource

($!) :: (a -> b) -> a -> bSource

const :: a -> b -> aSource

id :: a -> aSource

(.) :: (t1 -> t) -> (t2 -> t1) -> t2 -> tSource

($) :: (t1 -> t) -> t1 -> tSource

flip :: (t1 -> t2 -> t) -> t2 -> t1 -> tSource

curry :: ((a, b) -> c) -> a -> b -> cSource

uncurry :: (a -> b -> c) -> (a, b) -> cSource

snd :: (t, t1) -> t1Source

fst :: (t, t1) -> tSource

div :: Int -> Int -> IntSource

mod :: Int -> Int -> IntSource

divMod :: Int -> Int -> (Int, Int)Source

min :: (Num a, Foreign a) => a -> a -> aSource

max :: (Num a, Foreign a) => a -> a -> aSource

recip :: Double -> DoubleSource

negate :: Num a => a -> aSource

Implemented in Fay.

abs :: (Num a, Ord a) => a -> aSource

Implemented in Fay.

signum :: (Num a, Ord a) => a -> aSource

Implemented in Fay.

pi :: DoubleSource

Uses Math.PI.

exp :: Double -> DoubleSource

Uses Math.exp.

sqrt :: Double -> DoubleSource

Uses Math.sqrt.

log :: Double -> DoubleSource

Uses Math.log.

(**) :: Double -> Double -> DoubleSource

Uses Math.pow.

(^^) :: Double -> Int -> DoubleSource

Uses Math.pow.

unsafePow :: (Num a, Num b) => a -> b -> aSource

Uses Math.pow.

(^) :: Num a => a -> Int -> aSource

Implemented in Fay, it's not fast.

logBase :: Double -> Double -> DoubleSource

Implemented in Fay, not fast.

sin :: Double -> DoubleSource

Uses Math.sin.

tan :: Double -> DoubleSource

Uses Math.tan.

cos :: Double -> DoubleSource

Uses Math.cos.

asin :: Double -> DoubleSource

Uses Math.asin.

atan :: Double -> DoubleSource

Uses Math.atan.

acos :: Double -> DoubleSource

Uses Math.acos.

sinh :: Double -> DoubleSource

Implemented in Fay, not fast.

tanh :: Double -> DoubleSource

Implemented in Fay, not fast.

cosh :: Double -> DoubleSource

Implemented in Fay, not fast.

asinh :: Double -> DoubleSource

Implemented in Fay, not fast.

atanh :: Double -> DoubleSource

Implemented in Fay, not fast.

acosh :: Double -> DoubleSource

Implemented in Fay, not fast.

properFraction :: Double -> (Int, Double)Source

Implemented in Fay, not fast.

truncate :: Double -> IntSource

Implemented in Fay, not fast.

round :: Double -> IntSource

Uses Math.round.

ceiling :: Double -> IntSource

Uses Math.ceil.

floor :: Double -> IntSource

Uses Math.floor.

subtract :: Num a => a -> a -> aSource

Flip (-).

even :: Int -> BoolSource

Implemented in Fay, not fast.

odd :: Int -> BoolSource

not (even x)

gcd :: Int -> Int -> IntSource

Implemented in Fay, not fast.

quot :: Int -> Int -> IntSource

Uses quot'.

quot' :: Int -> Int -> IntSource

Uses ~~(a/b).

quotRem :: Int -> Int -> (Int, Int)Source

(quot x y, rem x y)

rem :: Int -> Int -> IntSource

Uses rem'.

rem' :: Int -> Int -> IntSource

Uses %%.

lcm :: Int -> Int -> IntSource

find :: (a -> Bool) -> [a] -> Maybe aSource

filter :: (a -> Bool) -> [a] -> [a]Source

null :: [t] -> BoolSource

map :: (a -> b) -> [a] -> [b]Source

nub :: Eq a => [a] -> [a]Source

nub' :: Eq a => [a] -> [a] -> [a]Source

elem :: Eq a => a -> [a] -> BoolSource

notElem :: Eq a => a -> [a] -> BoolSource

sort :: Ord a => [a] -> [a]Source

sortBy :: (t -> t -> Ordering) -> [t] -> [t]Source

insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]Source

conc :: [a] -> [a] -> [a]Source

Append two lists.

concat :: [[a]] -> [a]Source

concatMap :: (a -> [b]) -> [a] -> [b]Source

foldr :: (t -> t1 -> t1) -> t1 -> [t] -> t1Source

foldr1 :: (a -> a -> a) -> [a] -> aSource

foldl :: (t1 -> t -> t1) -> t1 -> [t] -> t1Source

foldl1 :: (a -> a -> a) -> [a] -> aSource

(++) :: [a] -> [a] -> [a]Source

(!!) :: [a] -> Int -> aSource

head :: [a] -> aSource

tail :: [a] -> [a]Source

init :: [a] -> [a]Source

last :: [a] -> aSource

iterate :: (a -> a) -> a -> [a]Source

repeat :: a -> [a]Source

replicate :: Int -> a -> [a]Source

cycle :: [a] -> [a]Source

take :: Int -> [a] -> [a]Source

drop :: Int -> [a] -> [a]Source

splitAt :: Int -> [a] -> ([a], [a])Source

takeWhile :: (a -> Bool) -> [a] -> [a]Source

dropWhile :: (a -> Bool) -> [a] -> [a]Source

span :: (a -> Bool) -> [a] -> ([a], [a])Source

break :: (a -> Bool) -> [a] -> ([a], [a])Source

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]Source

zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]Source

zip :: [a] -> [b] -> [(a, b)]Source

zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]Source

unzip :: [(a, b)] -> ([a], [b])Source

unzip3 :: [(a, b, c)] -> ([a], [b], [c])Source

lines :: String -> [String]Source

unlines :: [String] -> StringSource

words :: String -> [String]Source

unwords :: [String] -> StringSource

any :: (a -> Bool) -> [a] -> BoolSource

all :: (a -> Bool) -> [a] -> BoolSource

intersperse :: a -> [a] -> [a]Source

prependToAll :: a -> [a] -> [a]Source

intercalate :: [a] -> [[a]] -> [a]Source

maximum :: (Num a, Foreign a) => [a] -> aSource

minimum :: (Num a, Foreign a) => [a] -> aSource

product :: Num a => [a] -> aSource

sum :: Num a => [a] -> aSource

scanl :: (a -> b -> a) -> a -> [b] -> [a]Source

scanl1 :: (a -> a -> a) -> [a] -> [a]Source

scanr :: (a -> b -> b) -> b -> [a] -> [b]Source

scanr1 :: (a -> a -> a) -> [a] -> [a]Source

lookup :: Eq a1 => a1 -> [(a1, a)] -> Maybe aSource

length :: [a] -> IntSource

length' :: Int -> [a] -> IntSource

reverse :: [a] -> [a]Source

putStrLn :: String -> Fay ()Source