Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Char
- type String = [Char]
- data Double
- data Int
- data Integer
- data Bool
- class Read a
- class Show a
- class Eq a
- (==) :: Eq a => a -> a -> Bool
- (/=) :: Eq a => a -> a -> Bool
- data Maybe a
- maybe :: t -> (t1 -> t) -> Maybe t1 -> t
- (>>=) :: Ptr (Fay a) -> Ptr (a -> Fay b) -> Ptr (Fay b)
- (>>) :: Ptr (Fay a) -> Ptr (Fay b) -> Ptr (Fay b)
- return :: a -> Fay a
- fail :: String -> Fay a
- when :: Bool -> Fay () -> Fay ()
- unless :: Bool -> Fay () -> Fay ()
- forM :: [a] -> (a -> Fay b) -> Fay [b]
- forM_ :: [a] -> (a -> Fay b) -> Fay ()
- mapM :: (a -> Fay b) -> [a] -> Fay [b]
- mapM_ :: (a -> Fay b) -> [a] -> Fay ()
- (=<<) :: (a -> Fay b) -> Fay a -> Fay b
- sequence :: [Fay a] -> Fay [a]
- sequence_ :: [Fay a] -> Fay ()
- void :: Fay a -> Fay ()
- (>=>) :: (a -> Fay b) -> (b -> Fay c) -> a -> Fay c
- (<=<) :: (b -> Fay c) -> (a -> Fay b) -> a -> Fay c
- (*) :: Num a => a -> a -> a
- (+) :: Num a => a -> a -> a
- (-) :: Num a => a -> a -> a
- class Eq a => Ord a
- data Ordering
- (<) :: Ord a => a -> a -> Bool
- (<=) :: Ord a => a -> a -> Bool
- (>) :: Ord a => a -> a -> Bool
- (>=) :: Ord a => a -> a -> Bool
- compare :: Ord a => a -> a -> Ordering
- succ :: Num a => a -> a
- pred :: Num a => a -> a
- enumFrom :: Num a => a -> [a]
- enumFromTo :: (Ord t, Num t) => t -> t -> [t]
- enumFromBy :: Num t => t -> t -> [t]
- enumFromThen :: Num t => t -> t -> [t]
- enumFromByTo :: (Ord t, Num t) => t -> t -> t -> [t]
- enumFromThenTo :: (Ord t, Num t) => t -> t -> t -> [t]
- (/) :: Fractional a => a -> a -> a
- fromIntegral :: (Num a, Num b) => Ptr a -> Ptr b
- fromInteger :: Num a => Ptr Integer -> Ptr a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- otherwise :: Bool
- show :: Automatic a -> String
- error :: String -> a
- undefined :: a
- data Either a b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- seq :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> b -> b
- const :: a -> b -> a
- id :: a -> a
- (.) :: (t1 -> t) -> (t2 -> t1) -> t2 -> t
- ($) :: (t1 -> t) -> t1 -> t
- flip :: (t1 -> t2 -> t) -> t2 -> t1 -> t
- curry :: ((a, b) -> c) -> a -> b -> c
- uncurry :: (a -> b -> c) -> (a, b) -> c
- snd :: (t, t1) -> t1
- fst :: (t, t1) -> t
- div :: Int -> Int -> Int
- mod :: Int -> Int -> Int
- divMod :: Int -> Int -> (Int, Int)
- min :: Num a => a -> a -> a
- max :: Num a => a -> a -> a
- recip :: Double -> Double
- negate :: Num a => a -> a
- abs :: (Num a, Ord a) => a -> a
- signum :: (Num a, Ord a) => a -> a
- pi :: Double
- exp :: Double -> Double
- sqrt :: Double -> Double
- log :: Double -> Double
- (**) :: Double -> Double -> Double
- (^^) :: Double -> Int -> Double
- unsafePow :: (Num a, Num b) => a -> b -> a
- (^) :: Num a => a -> Int -> a
- logBase :: Double -> Double -> Double
- sin :: Double -> Double
- tan :: Double -> Double
- cos :: Double -> Double
- asin :: Double -> Double
- atan :: Double -> Double
- acos :: Double -> Double
- sinh :: Double -> Double
- tanh :: Double -> Double
- cosh :: Double -> Double
- asinh :: Double -> Double
- atanh :: Double -> Double
- acosh :: Double -> Double
- properFraction :: Double -> (Int, Double)
- truncate :: Double -> Int
- round :: Double -> Int
- ceiling :: Double -> Int
- floor :: Double -> Int
- subtract :: Num a => a -> a -> a
- even :: Int -> Bool
- odd :: Int -> Bool
- gcd :: Int -> Int -> Int
- quot :: Int -> Int -> Int
- quot' :: Int -> Int -> Int
- quotRem :: Int -> Int -> (Int, Int)
- rem :: Int -> Int -> Int
- rem' :: Int -> Int -> Int
- lcm :: Int -> Int -> Int
- find :: (a -> Bool) -> [a] -> Maybe a
- filter :: (a -> Bool) -> [a] -> [a]
- null :: [t] -> Bool
- map :: (a -> b) -> [a] -> [b]
- nub :: Eq a => [a] -> [a]
- nub' :: Eq a => [a] -> [a] -> [a]
- elem :: Eq a => a -> [a] -> Bool
- notElem :: Eq a => a -> [a] -> Bool
- sort :: Ord a => [a] -> [a]
- sortBy :: (t -> t -> Ordering) -> [t] -> [t]
- insertBy :: (a -> a -> Ordering) -> a -> [a] -> [a]
- conc :: [a] -> [a] -> [a]
- concat :: [[a]] -> [a]
- concatMap :: (a -> [b]) -> [a] -> [b]
- foldr :: (t -> t1 -> t1) -> t1 -> [t] -> t1
- foldr1 :: (a -> a -> a) -> [a] -> a
- foldl :: (t1 -> t -> t1) -> t1 -> [t] -> t1
- foldl1 :: (a -> a -> a) -> [a] -> a
- (++) :: [a] -> [a] -> [a]
- (!!) :: [a] -> Int -> a
- head :: [a] -> a
- tail :: [a] -> [a]
- init :: [a] -> [a]
- last :: [a] -> a
- iterate :: (a -> a) -> a -> [a]
- repeat :: a -> [a]
- replicate :: Int -> a -> [a]
- cycle :: [a] -> [a]
- take :: Int -> [a] -> [a]
- drop :: Int -> [a] -> [a]
- splitAt :: Int -> [a] -> ([a], [a])
- takeWhile :: (a -> Bool) -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- span :: (a -> Bool) -> [a] -> ([a], [a])
- break :: (a -> Bool) -> [a] -> ([a], [a])
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zip :: [a] -> [b] -> [(a, b)]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- unzip :: [(a, b)] -> ([a], [b])
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- lines :: String -> [String]
- unlines :: [String] -> String
- words :: String -> [String]
- unwords :: [String] -> String
- and :: [Bool] -> Bool
- or :: [Bool] -> Bool
- any :: (a -> Bool) -> [a] -> Bool
- all :: (a -> Bool) -> [a] -> Bool
- intersperse :: a -> [a] -> [a]
- prependToAll :: a -> [a] -> [a]
- intercalate :: [a] -> [[a]] -> [a]
- maximum :: Num a => [a] -> a
- minimum :: Num a => [a] -> a
- product :: Num a => [a] -> a
- sum :: Num a => [a] -> a
- scanl :: (a -> b -> a) -> a -> [b] -> [a]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- lookup :: Eq a1 => a1 -> [(a1, a)] -> Maybe a
- length :: [a] -> Int
- length' :: Int -> [a] -> Int
- reverse :: [a] -> [a]
- print :: Automatic a -> Fay ()
- putStrLn :: String -> Fay ()
- ifThenElse :: Bool -> t -> t -> t
- data Fay a
Documentation
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. 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
).
Instances
Bounded Char | Since: base-2.1 |
Enum Char | Since: base-2.1 |
Eq Char | |
Data Char | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Char -> c Char # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char # dataTypeOf :: Char -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) # gmapT :: (forall b. Data b => b -> b) -> Char -> Char # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r # gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char # | |
Ord Char | |
Read Char | Since: base-2.1 |
Show Char | Since: base-2.1 |
ErrorList Char | |
Defined in Control.Monad.Trans.Error |
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
Eq Double | Note that due to the presence of
Also note that
|
Floating Double | Since: base-2.1 |
Data Double | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Double -> c Double # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double # toConstr :: Double -> Constr # dataTypeOf :: Double -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) # gmapT :: (forall b. Data b => b -> b) -> Double -> Double # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r # gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double # | |
Ord Double | Note that due to the presence of
Also note that, due to the same,
|
Read Double | Since: base-2.1 |
RealFloat Double | Since: base-2.1 |
Defined in GHC.Float floatRadix :: Double -> Integer # floatDigits :: Double -> Int # floatRange :: Double -> (Int, Int) # decodeFloat :: Double -> (Integer, Int) # encodeFloat :: Integer -> Int -> Double # significand :: Double -> Double # scaleFloat :: Int -> Double -> Double # isInfinite :: Double -> Bool # isDenormalized :: Double -> Bool # isNegativeZero :: Double -> Bool # |
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 | Since: base-2.1 |
Enum Int | Since: base-2.1 |
Eq Int | |
Integral Int | Since: base-2.0.1 |
Data Int | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int -> c Int # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int # dataTypeOf :: Int -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) # gmapT :: (forall b. Data b => b -> b) -> Int -> Int # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r # gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int # | |
Num Int | Since: base-2.1 |
Ord Int | |
Read Int | Since: base-2.1 |
Real Int | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Int -> Rational # | |
Show Int | Since: base-2.1 |
Arbitrary precision integers. In contrast with fixed-size integral types
such as Int
, the Integer
type represents the entire infinite range of
integers.
For more information about this type's representation, see the comments in its implementation.
Instances
Enum Integer | Since: base-2.1 |
Eq Integer | |
Integral Integer | Since: base-2.0.1 |
Defined in GHC.Real | |
Data Integer | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer # toConstr :: Integer -> Constr # dataTypeOf :: Integer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) # gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # | |
Num Integer | Since: base-2.1 |
Ord Integer | |
Read Integer | Since: base-2.1 |
Real Integer | Since: base-2.0.1 |
Defined in GHC.Real toRational :: Integer -> Rational # | |
Show Integer | Since: base-2.1 |
Instances
Bounded Bool | Since: base-2.1 |
Enum Bool | Since: base-2.1 |
Eq Bool | |
Data Bool | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool # dataTypeOf :: Bool -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # | |
Ord Bool | |
Read Bool | Since: base-2.1 |
Show Bool | Since: base-2.1 |
Parsing of String
s, producing values.
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
Why do both readsPrec
and readPrec
exist, and why does GHC opt to
implement readPrec
in derived Read
instances instead of readsPrec
?
The reason is that readsPrec
is based on the ReadS
type, and although
ReadS
is mentioned in the Haskell 2010 Report, it is not a very efficient
parser data structure.
readPrec
, on the other hand, is based on a much more efficient ReadPrec
datatype (a.k.a "new-style parsers"), but its definition relies on the use
of the RankNTypes
language extension. Therefore, readPrec
(and its
cousin, readListPrec
) are marked as GHC-only. Nevertheless, it is
recommended to use readPrec
instead of readsPrec
whenever possible
for the efficiency improvements it brings.
As mentioned above, derived Read
instances in GHC will implement
readPrec
instead of readsPrec
. The default implementations of
readsPrec
(and its cousin, readList
) will simply use readPrec
under
the hood. If you are writing a Read
instance by hand, it is recommended
to write it like so:
instanceRead
T wherereadPrec
= ...readListPrec
=readListPrecDefault
Instances
Read Bool | Since: base-2.1 |
Read Char | Since: base-2.1 |
Read Double | Since: base-2.1 |
Read Float | Since: base-2.1 |
Read Int | Since: base-2.1 |
Read Integer | Since: base-2.1 |
Read Natural | Since: base-4.8.0.0 |
Read Ordering | Since: base-2.1 |
Read Word | Since: base-4.5.0.0 |
Read Word8 | Since: base-2.1 |
Read Word16 | Since: base-2.1 |
Read Word32 | Since: base-2.1 |
Read Word64 | Since: base-2.1 |
Read () | Since: base-2.1 |
Read Lexeme | Since: base-2.1 |
Read GeneralCategory | Since: base-2.1 |
Defined in GHC.Read | |
Read a => Read [a] | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
(Integral a, Read a) => Read (Ratio a) | Since: base-2.1 |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Read a, Read b) => Read (a, b) | Since: base-2.1 |
(Ix a, Read a, Read b) => Read (Array a b) | Since: base-2.1 |
Read (Proxy t) | Since: base-4.7.0.0 |
(Read a, Read b, Read c) => Read (a, b, c) | Since: base-2.1 |
a ~ b => Read (a :~: b) | Since: base-4.7.0.0 |
(Read e, Read1 m, Read a) => Read (ErrorT e m a) | |
(Read a, Read b, Read c, Read d) => Read (a, b, c, d) | Since: base-2.1 |
a ~~ b => Read (a :~~: b) | Since: base-4.10.0.0 |
(Read a, Read b, Read c, Read d, Read e) => Read (a, b, c, d, e) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f) => Read (a, b, c, d, e, f) | Since: base-2.1 |
(Read a, Read b, Read c, Read d, Read e, Read f, Read g) => Read (a, b, c, d, e, f, g) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
Defined in GHC.Read |
Conversion of values to readable String
s.
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 thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
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,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
Instances
Show Bool | Since: base-2.1 |
Show Char | Since: base-2.1 |
Show Int | Since: base-2.1 |
Show Integer | Since: base-2.1 |
Show Natural | Since: base-4.8.0.0 |
Show Ordering | Since: base-2.1 |
Show Word | Since: base-2.1 |
Show RuntimeRep | Since: base-4.11.0.0 |
Defined in GHC.Show showsPrec :: Int -> RuntimeRep -> ShowS # show :: RuntimeRep -> String # showList :: [RuntimeRep] -> ShowS # | |
Show VecCount | Since: base-4.11.0.0 |
Show VecElem | Since: base-4.11.0.0 |
Show CallStack | Since: base-4.9.0.0 |
Show SomeTypeRep | Since: base-4.10.0.0 |
Defined in Data.Typeable.Internal showsPrec :: Int -> SomeTypeRep -> ShowS # show :: SomeTypeRep -> String # showList :: [SomeTypeRep] -> ShowS # | |
Show () | Since: base-2.1 |
Show TyCon | Since: base-2.1 |
Show Module | Since: base-4.9.0.0 |
Show TrName | Since: base-4.9.0.0 |
Show KindRep | |
Show TypeLitSort | Since: base-4.11.0.0 |
Defined in GHC.Show showsPrec :: Int -> TypeLitSort -> ShowS # show :: TypeLitSort -> String # showList :: [TypeLitSort] -> ShowS # | |
Show DataType | Since: base-4.0.0.0 |
Show Constr | Since: base-4.0.0.0 |
Show DataRep | Since: base-4.0.0.0 |
Show ConstrRep | Since: base-4.0.0.0 |
Show Fixity | Since: base-4.0.0.0 |
Show SrcLoc | Since: base-4.9.0.0 |
Show CompileState | |
Defined in Fay.Types showsPrec :: Int -> CompileState -> ShowS # show :: CompileState -> String # showList :: [CompileState] -> ShowS # | |
Show CompileWriter | |
Defined in Fay.Types showsPrec :: Int -> CompileWriter -> ShowS # show :: CompileWriter -> String # showList :: [CompileWriter] -> ShowS # | |
Show Rational Source # | |
Show Text Source # | |
Show Day Source # | |
Show UTCTime Source # | |
Show a => Show [a] | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Show a => Show (Ratio a) | Since: base-2.0.1 |
Show a => Show (NonEmpty a) | Since: base-4.11.0.0 |
Show l => Show (PragmasAndModuleName l) | |
Defined in Language.Haskell.Exts.Parser showsPrec :: Int -> PragmasAndModuleName l -> ShowS # show :: PragmasAndModuleName l -> String # showList :: [PragmasAndModuleName l] -> ShowS # | |
Show l => Show (PragmasAndModuleHead l) | |
Defined in Language.Haskell.Exts.Parser showsPrec :: Int -> PragmasAndModuleHead l -> ShowS # show :: PragmasAndModuleHead l -> String # showList :: [PragmasAndModuleHead l] -> ShowS # | |
Show l => Show (ModuleHeadAndImports l) | |
Defined in Language.Haskell.Exts.Parser showsPrec :: Int -> ModuleHeadAndImports l -> ShowS # show :: ModuleHeadAndImports l -> String # showList :: [ModuleHeadAndImports l] -> ShowS # | |
Show a => Show (NonGreedy a) | |
Show a => Show (ListOf a) | |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
Show (TypeRep a) | |
(Show a, Show b) => Show (a, b) | Since: base-2.1 |
Show (Proxy s) | Since: base-4.7.0.0 |
(Show a, Show b, Show c) => Show (a, b, c) | Since: base-2.1 |
Show (a :~: b) | Since: base-4.7.0.0 |
(Show e, Show1 m, Show a) => Show (ErrorT e m a) | |
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) | Since: base-2.1 |
Show (a :~~: b) | Since: base-4.10.0.0 |
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) | Since: base-2.1 |
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) | Since: base-2.1 |
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
(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) | Since: base-2.1 |
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
.
The Haskell Report defines no laws for Eq
. However, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
Eq Bool | |
Eq Char | |
Eq Double | Note that due to the presence of
Also note that
|
Eq Float | Note that due to the presence of
Also note that
|
Eq Int | |
Eq Integer | |
Eq Natural | Since: base-4.8.0.0 |
Eq Ordering | |
Eq Word | |
Eq SomeTypeRep | |
Defined in Data.Typeable.Internal (==) :: SomeTypeRep -> SomeTypeRep -> Bool # (/=) :: SomeTypeRep -> SomeTypeRep -> Bool # | |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq Constr | Equality of constructors Since: base-4.0.0.0 |
Eq DataRep | Since: base-4.0.0.0 |
Eq ConstrRep | Since: base-4.0.0.0 |
Eq Fixity | Since: base-4.0.0.0 |
Eq BigNat | |
Eq Text Source # | |
Eq Day Source # | |
Eq UTCTime Source # | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Eq a => Eq (Ratio a) | Since: base-2.1 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Eq l => Eq (PragmasAndModuleName l) | |
Defined in Language.Haskell.Exts.Parser (==) :: PragmasAndModuleName l -> PragmasAndModuleName l -> Bool # (/=) :: PragmasAndModuleName l -> PragmasAndModuleName l -> Bool # | |
Eq l => Eq (PragmasAndModuleHead l) | |
Defined in Language.Haskell.Exts.Parser (==) :: PragmasAndModuleHead l -> PragmasAndModuleHead l -> Bool # (/=) :: PragmasAndModuleHead l -> PragmasAndModuleHead l -> Bool # | |
Eq l => Eq (ModuleHeadAndImports l) | |
Defined in Language.Haskell.Exts.Parser (==) :: ModuleHeadAndImports l -> ModuleHeadAndImports l -> Bool # (/=) :: ModuleHeadAndImports l -> ModuleHeadAndImports l -> Bool # | |
Eq a => Eq (NonGreedy a) | |
Eq a => Eq (ListOf a) | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
Eq (TypeRep a) | Since: base-2.1 |
(Eq a, Eq b) => Eq (a, b) | |
Eq (Proxy s) | Since: base-4.7.0.0 |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (a :~: b) | Since: base-4.7.0.0 |
(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 :~~: b) | Since: base-4.10.0.0 |
(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) | |
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). 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.
Instances
Monad Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
Applicative Maybe | Since: base-2.1 |
Alternative Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) # toConstr :: Maybe a -> Constr # dataTypeOf :: Maybe a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # | |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
sequence :: [Fay a] -> Fay [a] Source #
Evaluate each action in the sequence from left to right, and collect the results.
Instances
Bounded Ordering | Since: base-2.1 |
Enum Ordering | Since: base-2.1 |
Eq Ordering | |
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering # toConstr :: Ordering -> Constr # dataTypeOf :: Ordering -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # | |
Ord Ordering | |
Defined in GHC.Classes | |
Read Ordering | Since: base-2.1 |
Show Ordering | Since: base-2.1 |
Semigroup Ordering | Since: base-4.9.0.0 |
Monoid Ordering | Since: base-2.1 |
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 #
fromIntegral :: (Num a, Num b) => Ptr a -> Ptr b Source #
fromInteger :: Num a => Ptr Integer -> Ptr a Source #
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.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").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but
will apply the supplied function to values contained in a Right
:
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
fmap (*2) s
Left "foo">>>
fmap (*2) n
Right 6
The Monad
instance for Either
allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int
from a Char
, or fail.
>>>
import Data.Char ( digitToInt, isDigit )
>>>
:{
let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>
:}
The following should work, since both '1'
and '2'
can be
parsed as Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 3
But the following should fail overall, since the first operation where
we attempt to parse 'm'
as an Int
will fail:
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Left "parse error"
Instances
Eq2 Either | Since: base-4.9.0.0 |
Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] # | |
Show2 Either | Since: base-4.9.0.0 |
Monad (Either e) | Since: base-4.4.0.0 |
Functor (Either a) | Since: base-3.0 |
Applicative (Either e) | Since: base-3.0 |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] # | |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) # toConstr :: Either a b -> Constr # dataTypeOf :: Either a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # | |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
seq :: forall (r :: RuntimeRep) a (b :: TYPE r). a -> b -> b infixr 0 #
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
properFraction :: Double -> (Int, Double) Source #
Implemented in Fay, not fast.
intersperse :: a -> [a] -> [a] Source #
prependToAll :: a -> [a] -> [a] Source #
intercalate :: [a] -> [[a]] -> [a] Source #
ifThenElse :: Bool -> t -> t -> t Source #
Default definition for using RebindableSyntax.