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

Safe HaskellNone

Prelude

Synopsis

Documentation

type String = [Char]

data Int

Instances

data Integer

Instances

Enum Integer 
Eq Integer 
Integral Integer 
Data Integer 
Num Integer 
Ord Integer 
Read Integer 
Real Integer 
Show Integer 
Typeable Integer 
ToJSON Integer 
FromJSON Integer

WARNING: Only parse Integers from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

Default Integer 
GTraversable c Integer 
ToJSON (Ratio Integer) 
FromJSON (Ratio Integer) 

class Read a

Instances

Read Bool 
Read Char 
Read Double 
Read Float 
Read Int 
Read Integer 
Read Ordering 
Read Word 
Read () 
Read Text 
Read UTCTime 
Read Text 
Read ZonedTime 
Read Day 
Read TimeZone 
Read TimeOfDay 
Read LocalTime 
Read Lexeme 
Read a => Read [a] 
(Integral a, Read a) => Read (Ratio a) 
Read a => Read (Maybe a) 
(Read a, Unbox a) => Read (Vector 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

Instances

Show Bool 
Show Char 
Show Double 
Show Float 
Show Int 
Show Integer 
Show Ordering 
Show Word 
Show () 
Show Text 
Show UTCTime 
Show CompileState 
Show CompileWriter 
Show Symbols 
Show GName 
Show OrigName 
Show PkgDBError 
Show PkgInfoError 
Show Constr 
Show ConstrRep 
Show DataRep 
Show DataType 
Show Fixity 
Show TyCon 
Show TypeRep 
Show Text 
Show PWarning 
Show PError 
Show Field 
Show ZonedTime 
Show Doc 
Show Day 
Show Padding 
Show DateFormatSpec 
Show LocalTime 
Show Rational 
Show Day 
Show UTCTime 
Show a => Show [a] 
(Integral a, Show a) => Show (Ratio a) 
Show a => Show (Maybe a) 
Show name => Show (SymValueInfo name) 
Show name => Show (SymTypeInfo name) 
Show l => Show (Scoped l) 
Show l => Show (NameInfo l) 
Show l => Show (Error l) 
(Show a, Unbox a) => Show (Vector a) 
Show a => Show (ParseResult 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

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 Text 
Eq Symbols 
Eq GName 
Eq OrigName 
Eq Constr 
Eq ConstrRep 
Eq DataRep 
Eq Fixity 
Eq TyCon 
Eq TypeRep 
Eq Text 
Eq Field 
Eq LocalTime 
Eq Text 
Eq Day 
Eq UTCTime 
Eq a => Eq [a] 
Eq a => Eq (Ratio a) 
Eq a => Eq (Maybe a) 
Eq name => Eq (SymValueInfo name) 
Eq name => Eq (SymTypeInfo name) 
Eq l => Eq (Scoped l) 
Eq l => Eq (NameInfo l) 
Eq l => Eq (Error l) 
(Unbox a, Eq a) => Eq (Vector a) 
(Eq a, Eq b) => Eq (Either a b) 
(Eq a, Eq b) => Eq (a, b) 
Eq a => Eq (Stream Id a) 
(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

Constructors

Nothing 
Just a 

Instances

Monad Maybe 
Functor Maybe 
Typeable1 Maybe 
MonadPlus Maybe 
Eq1 Maybe 
Ord1 Maybe 
Read1 Maybe 
Show1 Maybe 
c0 a0 => GTraversable c0 (Maybe a0) 
Eq a => Eq (Maybe a) 
Data a => Data (Maybe a) 
Ord a => Ord (Maybe a) 
Read a => Read (Maybe a) 
Show a => Show (Maybe a) 
ToJSON a => ToJSON (Maybe a) 
FromJSON a => FromJSON (Maybe a) 
Default (Maybe a) 
(Selector s, ToJSON a) => RecordToPairs (S1 s (K1 i (Maybe a))) 
(Selector s, FromJSON a) => FromRecord (S1 s (K1 i (Maybe a))) 

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

Maybe type.

Either type.

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

Monomorphic bind for Fay.

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

Monomorphic then for Fay.

return :: a -> Fay aSource

Monomorphic return for Fay.

fail :: String -> Fay aSource

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

unless :: Bool -> Fay a -> 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 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

void :: Fay a -> Fay ()Source

(>=>) :: (a -> Fay b) -> (b -> Fay c) -> a -> Fay cSource

(<=<) :: (b -> Fay c) -> (a -> Fay b) -> a -> Fay cSource

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

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

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

class Eq a => Ord a whereSource

Methods

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

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

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

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

Instances

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 :: (Num a, Num b) => Ptr a -> Ptr bSource

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

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

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

show :: Automatic a -> StringSource

Uses JSON.stringify.

error :: String -> aSource

Throws a JavaScript error.

data Either a b

Constructors

Left a 
Right b 

Instances

Typeable2 Either 
(c0 a0, c0 b0) => GTraversable c0 (Either a0 b0) 
Monad (Either e) 
Functor (Either a) 
Error e => MonadPlus (Either e) 
Error e => Alternative (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) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 
(FromJSON a, FromJSON b) => FromJSON (Either a b) 

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

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

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

seq :: a -> b -> b

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 => a -> a -> aSource

max :: Num 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 => [a] -> aSource

minimum :: Num 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

ifThenElse :: Bool -> t -> t -> tSource

Default definition for using RebindableSyntax.

data Fay a

The JavaScript FFI interfacing monad.

Instances

Monad Fay 
Functor Fay 
Applicative Fay