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

Safe HaskellNone
LanguageHaskell98

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.

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.

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 2010 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

Minimal complete definition

readsPrec | readPrec

Instances

Read Bool 
Read Char 
Read Double 
Read Float 
Read Int 
Read Integer 
Read Ordering 
Read Word 
Read () 
Read Text 
Read Text 
Read Lexeme 
Read a => Read [a] 
(Integral a, Read a) => Read (Ratio a) 
Read a => Read (Maybe a) 
Read a => Read (ZipList a) 
(Read a, Read b) => Read (Either a b) 
(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 e, Read1 m, Read a) => Read (ErrorT e m a) 
(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)".

Minimal complete definition

showsPrec | show

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Integer 
Show Ordering 
Show Word 
Show () 
Show Text 
Show Text 
Show DataType 
Show Constr 
Show DataRep 
Show ConstrRep 
Show Fixity 
Show TypeRep 
Show TyCon 
Show CompileState 
Show CompileWriter 
Show Doc 
Show Rational 
Show Day 
Show UTCTime 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio a) 
Show a => Show (Maybe a) 
Show a => Show (ZipList a) 
(Show a, Show b) => Show (Either a b) 
(Show a, Show b) => Show (a, b) 
(Show a, Show b, Show c) => Show (a, b, c) 
(Show e, Show1 m, Show a) => Show (ErrorT e m a) 
(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 /=.

Minimal complete definition

(==) | (/=)

Methods

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

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

Instances

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

Equality of constructors

Eq DataRep 
Eq ConstrRep 
Eq Fixity 
Eq TypeRep 
Eq TyCon 
Eq Text 
Eq Day 
Eq UTCTime 
Eq a => Eq [a] 
Eq a => Eq (Ratio a) 
Eq a => Eq (Maybe a) 
Eq a => Eq (ZipList a) 
(Eq a, Eq b) => Eq (Either a b) 
(Eq a, Eq b) => Eq (a, b) 
(Eq a, Eq b, Eq c) => Eq (a, b, c) 
(Eq e, Eq1 m, Eq a) => Eq (ErrorT e m a) 
(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 :: * -> *

The Maybe type encapsulates an optional value. A value of type Maybe a either contains a value of type a (represented as Just a), or it is empty (represented as Nothing). Using Maybe is a good way to deal with errors or exceptional cases without resorting to drastic measures such as error.

The Maybe type is also a monad. It is a simple kind of error monad, where all errors are represented by Nothing. A richer error monad can be built using the Either type.

Constructors

Nothing 
Just a 

Instances

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

Maybe type.

Either type.

(>>=) :: Ptr (Fay a) -> Ptr (a -> Fay b) -> Ptr (Fay b) infixl 1 Source

Monomorphic bind for Fay.

(>>) :: Ptr (Fay a) -> Ptr (Fay b) -> Ptr (Fay b) infixl 1 Source

Monomorphic then for Fay.

return :: a -> Fay a Source

Monomorphic return for Fay.

fail :: String -> Fay a Source

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

unless :: Bool -> Fay () -> Fay () Source

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

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

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

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

(=<<) :: (a -> Fay b) -> Fay a -> Fay b infixr 1 Source

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

void :: Fay a -> Fay () Source

(>=>) :: (a -> Fay b) -> (b -> Fay c) -> a -> Fay c infixr 1 Source

(<=<) :: (b -> Fay c) -> (a -> Fay b) -> a -> Fay c infixr 1 Source

(*) :: Num a => a -> a -> a infixl 7 Source

(+) :: Num a => a -> a -> a infixl 6 Source

(-) :: Num a => a -> a -> a infixl 6 Source

class Eq a => Ord a where Source

Methods

(<) :: a -> a -> Bool infixr 4 Source

(<=) :: a -> a -> Bool infixr 4 Source

(>) :: a -> a -> Bool infixr 4 Source

(>=) :: a -> a -> Bool infixr 4 Source

Instances

compare :: Ord a => a -> a -> Ordering Source

succ :: Num a => a -> a Source

pred :: Num a => a -> a Source

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 -> a infixl 7 Source

fromIntegral :: (Num a, Num b) => Ptr a -> Ptr b Source

fromInteger :: Num a => Ptr Integer -> Ptr a Source

(&&) :: Bool -> Bool -> Bool infixr 3

Boolean "and"

(||) :: Bool -> Bool -> Bool infixr 2

Boolean "or"

show :: Automatic a -> String Source

Uses JSON.stringify.

error :: String -> a Source

Throws a JavaScript error.

undefined :: a Source

Throws "undefined" via "error".

data Either a b :: * -> * -> *

The Either type represents values with two possibilities: a value of type Either a b is either Left a or Right b.

The Either type is sometimes used to represent a value which is either correct or an error; by convention, the Left constructor is used to hold an error value and the Right constructor is used to hold a correct value (mnemonic: "right" also means "correct").

Constructors

Left a 
Right b 

Instances

(c0 a0, c0 b0) => GTraversable c0 (Either a0 b0) 
Error e => Alternative (Either e) 
Monad (Either e) 
Functor (Either a) 
Error e => MonadPlus (Either e) 
Applicative (Either e) 
Eq a => Eq1 (Either a) 
Ord a => Ord1 (Either a) 
Read a => Read1 (Either a) 
Show a => Show1 (Either a) 
(Eq a, Eq b) => Eq (Either a b) 
(Data a, Data b) => Data (Either a b) 
(Ord a, Ord b) => Ord (Either a b) 
(Read a, Read b) => Read (Either a b) 
(Show a, Show b) => Show (Either a b) 
Typeable (* -> * -> *) Either 
type (==) (Either k k1) a b = EqEither k k1 a b 

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

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

($!) :: (a -> b) -> a -> b infixr 0 Source

seq :: a -> b -> b

Evaluates its first argument to head normal form, and then returns its second argument as the result.

const :: a -> b -> a Source

id :: a -> a Source

(.) :: (t1 -> t) -> (t2 -> t1) -> t2 -> t infixr 9 Source

($) :: (t1 -> t) -> t1 -> t infixr 0 Source

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

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

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

snd :: (t, t1) -> t1 Source

fst :: (t, t1) -> t Source

div :: Int -> Int -> Int infixl 7 Source

mod :: Int -> Int -> Int infixl 7 Source

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

min :: Num a => a -> a -> a Source

max :: Num a => a -> a -> a Source

recip :: Double -> Double Source

negate :: Num a => a -> a Source

Implemented in Fay.

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

Implemented in Fay.

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

Implemented in Fay.

pi :: Double Source

Uses Math.PI.

exp :: Double -> Double Source

Uses Math.exp.

sqrt :: Double -> Double Source

Uses Math.sqrt.

log :: Double -> Double Source

Uses Math.log.

(**) :: Double -> Double -> Double infixr 8 Source

Uses Math.pow.

(^^) :: Double -> Int -> Double infixr 8 Source

Uses Math.pow.

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

Uses Math.pow.

(^) :: Num a => a -> Int -> a infixr 8 Source

Implemented in Fay, it's not fast.

logBase :: Double -> Double -> Double Source

Implemented in Fay, not fast.

sin :: Double -> Double Source

Uses Math.sin.

tan :: Double -> Double Source

Uses Math.tan.

cos :: Double -> Double Source

Uses Math.cos.

asin :: Double -> Double Source

Uses Math.asin.

atan :: Double -> Double Source

Uses Math.atan.

acos :: Double -> Double Source

Uses Math.acos.

sinh :: Double -> Double Source

Implemented in Fay, not fast.

tanh :: Double -> Double Source

Implemented in Fay, not fast.

cosh :: Double -> Double Source

Implemented in Fay, not fast.

asinh :: Double -> Double Source

Implemented in Fay, not fast.

atanh :: Double -> Double Source

Implemented in Fay, not fast.

acosh :: Double -> Double Source

Implemented in Fay, not fast.

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

Implemented in Fay, not fast.

truncate :: Double -> Int Source

Implemented in Fay, not fast.

round :: Double -> Int Source

Uses Math.round.

ceiling :: Double -> Int Source

Uses Math.ceil.

floor :: Double -> Int Source

Uses Math.floor.

subtract :: Num a => a -> a -> a Source

Flip (-).

even :: Int -> Bool Source

Implemented in Fay, not fast.

odd :: Int -> Bool Source

not (even x)

gcd :: Int -> Int -> Int Source

Implemented in Fay, not fast.

quot :: Int -> Int -> Int infixl 7 Source

Uses quot'.

quot' :: Int -> Int -> Int Source

Uses ~~(a/b).

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

(quot x y, rem x y)

rem :: Int -> Int -> Int infixl 7 Source

Uses rem'.

rem' :: Int -> Int -> Int Source

Uses %%.

lcm :: Int -> Int -> Int Source

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

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

null :: [t] -> Bool Source

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

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

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

elem :: Eq a => a -> [a] -> Bool infix 4 Source

notElem :: Eq a => a -> [a] -> Bool infix 4 Source

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] -> t1 Source

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

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

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

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

(!!) :: [a] -> Int -> a infixl 9 Source

head :: [a] -> a Source

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

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

last :: [a] -> a Source

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] -> String Source

words :: String -> [String] Source

unwords :: [String] -> String Source

or :: [Bool] -> Bool Source

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

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

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

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

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

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

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

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

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

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 a Source

length :: [a] -> Int Source

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

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

putStrLn :: String -> Fay () Source

ifThenElse :: Bool -> t -> t -> t Source

Default definition for using RebindableSyntax.

data Fay a :: * -> *

The JavaScript FFI interfacing monad.