License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Foundation
Contents
Description
I tried to picture clusters of information As they moved through the computer What do they look like?
Alternative Prelude
- ($) :: (a -> b) -> a -> b
- ($!) :: (a -> b) -> a -> b
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- (.) :: Category k cat => forall b c a. cat b c -> cat a b -> cat a c
- not :: Bool -> Bool
- otherwise :: Bool
- data Tuple2 a b = Tuple2 !a !b
- data Tuple3 a b c = Tuple3 !a !b !c
- data Tuple4 a b c d = Tuple4 !a !b !c !d
- class Fstable a where
- type ProductFirst a
- fst :: a -> ProductFirst a
- class Sndable a where
- type ProductSecond a
- snd :: a -> ProductSecond a
- class Thdable a where
- type ProductThird a
- thd :: a -> ProductThird a
- id :: Category k cat => forall a. cat a a
- maybe :: b -> (a -> b) -> Maybe a -> b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- flip :: (a -> b -> c) -> b -> a -> c
- const :: a -> b -> a
- error :: String -> a
- putStr :: String -> IO ()
- putStrLn :: String -> IO ()
- getArgs :: IO [String]
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- swap :: (a, b) -> (b, a)
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- undefined :: a
- seq :: a -> b -> b
- class NormalForm a
- deepseq :: NormalForm a => a -> b -> b
- force :: NormalForm a => a -> a
- class Show a
- show :: Show a => a -> String
- class Eq a => Ord a where
- class Eq a where
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Functor f where
- class Integral a where
- fromInteger :: Integer -> a
- class Fractional a where
- fromRational :: Rational -> a
- class HasNegation a where
- negate :: a -> a
- class Bifunctor p where
- class Functor f => Applicative f where
- class Applicative m => Monad m where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class IsString a where
- fromString :: String -> a
- class IsList l where
- class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a where
- class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a where
- class Signed a where
- class Additive a where
- class Subtractive a where
- type Difference a
- (-) :: a -> a -> Difference a
- class Multiplicative a where
- midentity :: a
- (*) :: a -> a -> a
- (^) :: (IsNatural n, IDivisible n) => a -> n -> a
- class (Additive a, Multiplicative a) => IDivisible a where
- class Multiplicative a => Divisible a where
- (/) :: a -> a -> a
- data Maybe a :: * -> *
- data Ordering :: *
- data Bool :: *
- data Char :: *
- data IO a :: * -> *
- data Either a b :: * -> * -> *
- data Int8 :: *
- data Int16 :: *
- data Int32 :: *
- data Int64 :: *
- data Word8 :: *
- data Word16 :: *
- data Word32 :: *
- data Word64 :: *
- data Word :: *
- data Int :: *
- data Integer :: *
- data Natural :: *
- type Rational = Ratio Integer
- data Float :: *
- data Double :: *
- newtype CountOf ty = CountOf Int
- newtype Offset ty = Offset Int
- toCount :: Int -> CountOf ty
- fromCount :: CountOf ty -> Int
- data UArray ty
- class Eq ty => PrimType ty
- data Array a
- data String
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Monoid a where
- (<>) :: Monoid m => m -> m -> m
- class (IsList c, Item c ~ Element c) => Collection c where
- null :: c -> Bool
- length :: c -> CountOf (Element c)
- elem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
- notElem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
- maximum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
- minimum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
- any :: (Element c -> Bool) -> c -> Bool
- all :: (Element c -> Bool) -> c -> Bool
- and :: (Collection col, Element col ~ Bool) => col -> Bool
- or :: (Collection col, Element col ~ Bool) => col -> Bool
- class (IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where
- take :: CountOf (Element c) -> c -> c
- revTake :: CountOf (Element c) -> c -> c
- drop :: CountOf (Element c) -> c -> c
- revDrop :: CountOf (Element c) -> c -> c
- splitAt :: CountOf (Element c) -> c -> (c, c)
- revSplitAt :: CountOf (Element c) -> c -> (c, c)
- splitOn :: (Element c -> Bool) -> c -> [c]
- break :: (Element c -> Bool) -> c -> (c, c)
- breakElem :: Eq (Element c) => Element c -> c -> (c, c)
- takeWhile :: (Element c -> Bool) -> c -> c
- dropWhile :: (Element c -> Bool) -> c -> c
- intersperse :: Element c -> c -> c
- intercalate :: Monoid (Item c) => Element c -> c -> Element c
- span :: (Element c -> Bool) -> c -> (c, c)
- filter :: (Element c -> Bool) -> c -> c
- partition :: (Element c -> Bool) -> c -> (c, c)
- reverse :: c -> c
- uncons :: c -> Maybe (Element c, c)
- unsnoc :: c -> Maybe (c, Element c)
- snoc :: c -> Element c -> c
- cons :: Element c -> c -> c
- find :: (Element c -> Bool) -> c -> Maybe (Element c)
- sortBy :: (Element c -> Element c -> Ordering) -> c -> c
- singleton :: Element c -> c
- head :: NonEmpty c -> Element c
- last :: NonEmpty c -> Element c
- tail :: NonEmpty c -> c
- init :: NonEmpty c -> c
- replicate :: CountOf (Element c) -> Element c -> c
- isPrefixOf :: Eq (Element c) => c -> c -> Bool
- isSuffixOf :: Eq (Element c) => c -> c -> Bool
- isInfixOf :: Eq (Element c) => c -> c -> Bool
- stripPrefix :: Eq (Element c) => c -> c -> Maybe c
- stripSuffix :: Eq (Element c) => c -> c -> Maybe c
- data NonEmpty a
- nonEmpty :: Collection c => c -> Maybe (NonEmpty c)
- class Foldable collection where
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- catMaybes :: [Maybe a] -> [a]
- fromMaybe :: a -> Maybe a -> a
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- listToMaybe :: [a] -> Maybe a
- maybeToList :: Maybe a -> [a]
- partitionEithers :: [Either a b] -> ([a], [b])
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<|>) :: Alternative f => forall a. f a -> f a -> f a
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- class (Typeable * e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- class Typeable a
- data SomeException :: *
- data IOException :: *
- data Proxy t :: k -> * = Proxy
- asProxyTypeOf :: a -> Proxy * a -> a
- data Partial a
- partial :: a -> Partial a
- data PartialError
- fromPartial :: Partial a -> a
- ifThenElse :: Bool -> a -> a -> a
- type LString = String
Standard
Operators
($) :: (a -> b) -> a -> b infixr 0
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
($!) :: (a -> b) -> a -> b infixr 0
Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.
Functions
data Tuple2 a b
Strict tuple (a,b)
Constructors
Tuple2 !a !b |
Instances
Bifunctor Tuple2 | |
Nthable 1 (Tuple2 a b) | |
Nthable 2 (Tuple2 a b) | |
(Eq a, Eq b) => Eq (Tuple2 a b) | |
(Data a, Data b) => Data (Tuple2 a b) | |
(Ord a, Ord b) => Ord (Tuple2 a b) | |
(Show a, Show b) => Show (Tuple2 a b) | |
Generic (Tuple2 a b) | |
(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) | |
Sndable (Tuple2 a b) | |
Fstable (Tuple2 a b) | |
(Hashable a, Hashable b) => Hashable (Tuple2 a b) | |
type NthTy 1 (Tuple2 a b) = a | |
type NthTy 2 (Tuple2 a b) = b | |
type Rep (Tuple2 a b) | |
type ProductSecond (Tuple2 a b) = b | |
type ProductFirst (Tuple2 a b) = a |
data Tuple3 a b c
Strict tuple (a,b,c)
Constructors
Tuple3 !a !b !c |
Instances
Nthable 1 (Tuple3 a b c) | |
Nthable 2 (Tuple3 a b c) | |
Nthable 3 (Tuple3 a b c) | |
(Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) | |
(Data a, Data b, Data c) => Data (Tuple3 a b c) | |
(Ord a, Ord b, Ord c) => Ord (Tuple3 a b c) | |
(Show a, Show b, Show c) => Show (Tuple3 a b c) | |
Generic (Tuple3 a b c) | |
(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) | |
Thdable (Tuple3 a b c) | |
Sndable (Tuple3 a b c) | |
Fstable (Tuple3 a b c) | |
(Hashable a, Hashable b, Hashable c) => Hashable (Tuple3 a b c) | |
type NthTy 1 (Tuple3 a b c) = a | |
type NthTy 2 (Tuple3 a b c) = b | |
type NthTy 3 (Tuple3 a b c) = c | |
type Rep (Tuple3 a b c) | |
type ProductThird (Tuple3 a b c) = c | |
type ProductSecond (Tuple3 a b c) = b | |
type ProductFirst (Tuple3 a b c) = a |
data Tuple4 a b c d
Strict tuple (a,b,c,d)
Constructors
Tuple4 !a !b !c !d |
Instances
Nthable 1 (Tuple4 a b c d) | |
Nthable 2 (Tuple4 a b c d) | |
Nthable 3 (Tuple4 a b c d) | |
Nthable 4 (Tuple4 a b c d) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (Tuple4 a b c d) | |
(Data a, Data b, Data c, Data d) => Data (Tuple4 a b c d) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (Tuple4 a b c d) | |
(Show a, Show b, Show c, Show d) => Show (Tuple4 a b c d) | |
Generic (Tuple4 a b c d) | |
(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) | |
Thdable (Tuple4 a b c d) | |
Sndable (Tuple4 a b c d) | |
Fstable (Tuple4 a b c d) | |
(Hashable a, Hashable b, Hashable c, Hashable d) => Hashable (Tuple4 a b c d) | |
type NthTy 1 (Tuple4 a b c d) = a | |
type NthTy 2 (Tuple4 a b c d) = b | |
type NthTy 3 (Tuple4 a b c d) = c | |
type NthTy 4 (Tuple4 a b c d) = d | |
type Rep (Tuple4 a b c d) | |
type ProductThird (Tuple4 a b c d) = c | |
type ProductSecond (Tuple4 a b c d) = b | |
type ProductFirst (Tuple4 a b c d) = a |
class Fstable a where
Class of product types that have a first element
Associated Types
type ProductFirst a
Methods
fst :: a -> ProductFirst a
class Sndable a where
Class of product types that have a second element
Associated Types
type ProductSecond a
Methods
snd :: a -> ProductSecond a
class Thdable a where
Class of product types that have a third element
Associated Types
type ProductThird a
Methods
thd :: a -> ProductThird a
maybe :: b -> (a -> b) -> Maybe a -> b
The maybe
function takes a default value, a function, and a Maybe
value. If the Maybe
value is Nothing
, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just
and returns the result.
Examples
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
either :: (a -> c) -> (b -> c) -> Either a b -> c
Case analysis for the Either
type.
If the value is
, apply the first function to Left
aa
;
if it is
, apply the second function to Right
bb
.
Examples
We create two values of type
, one using the
Either
String
Int
Left
constructor and another using the Right
constructor. Then
we apply "either" the length
function (if we have a String
)
or the "times-two" function (if we have an Int
):
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
either length (*2) s
3>>>
either length (*2) n
6
flip :: (a -> b -> c) -> b -> a -> c
takes its (first) two arguments in the reverse order of flip
ff
.
const :: a -> b -> a
Constant function.
Returns a list of the program's command line arguments (not including the program name).
swap :: (a, b) -> (b, a)
Swap the components of a pair.
asTypeOf :: a -> a -> a
undefined :: a
seq :: a -> b -> b
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. 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.
class NormalForm a
Data that can be fully evaluated in Normal Form
Minimal complete definition
Instances
deepseq :: NormalForm a => a -> b -> b
force :: NormalForm a => a -> a
Type classes
class Show a
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
Use the Show class to create a String.
Note that this is not efficient, since an intermediate [Char] is going to be created before turning into a real String.
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined
datatype whose constituent types are in Ord
. The declared order
of the constructors in the data declaration determines the ordering
in derived Ord
instances. The Ordering
datatype allows a single
comparison to determine the precise ordering of two objects.
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Methods
(<=) :: a -> a -> Bool infix 4
(>=) :: a -> a -> Bool infix 4
max :: a -> a -> a
min :: a -> a -> a
Instances
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
.
Instances
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | |
Eq Int16 | |
Eq Int32 | |
Eq Int64 | |
Eq Integer | |
Eq Ordering | |
Eq Word | |
Eq Word8 | |
Eq Word16 | |
Eq Word32 | |
Eq Word64 | |
Eq CallStack | |
Eq TypeRep | |
Eq () | |
Eq BigNat | |
Eq SpecConstrAnnotation | |
Eq SomeNat | |
Eq SomeSymbol | |
Eq Natural | |
Eq Constr | Equality of constructors |
Eq DataRep | |
Eq ConstrRep | |
Eq Fixity | |
Eq Version | |
Eq HandlePosn | |
Eq IOMode | |
Eq ThreadId | |
Eq BlockReason | |
Eq ThreadStatus | |
Eq CDev | |
Eq CIno | |
Eq CMode | |
Eq COff | |
Eq CPid | |
Eq CSsize | |
Eq CGid | |
Eq CNlink | |
Eq CUid | |
Eq CCc | |
Eq CSpeed | |
Eq CTcflag | |
Eq CRLim | |
Eq Fd | |
Eq Errno | |
Eq AsyncException | |
Eq ArrayException | |
Eq ExitCode | |
Eq IOErrorType | |
Eq Handle | |
Eq BufferMode | |
Eq Newline | |
Eq NewlineMode | |
Eq IODeviceType | |
Eq SeekMode | |
Eq WordPtr | |
Eq IntPtr | |
Eq CChar | |
Eq CSChar | |
Eq CUChar | |
Eq CShort | |
Eq CUShort | |
Eq CInt | |
Eq CUInt | |
Eq CLong | |
Eq CULong | |
Eq CLLong | |
Eq CULLong | |
Eq CFloat | |
Eq CDouble | |
Eq CPtrdiff | |
Eq CSize | |
Eq CWchar | |
Eq CSigAtomic | |
Eq CClock | |
Eq CTime | |
Eq CUSeconds | |
Eq CSUSeconds | |
Eq CIntPtr | |
Eq CUIntPtr | |
Eq CIntMax | |
Eq CUIntMax | |
Eq MaskingState | |
Eq IOException | |
Eq ErrorCall | |
Eq ArithException | |
Eq All | |
Eq Any | |
Eq Arity | |
Eq Fixity | |
Eq Associativity | |
Eq TyCon | |
Eq Fingerprint | |
Eq GeneralCategory | |
Eq Lexeme | |
Eq Number | |
Eq PartialError | |
Eq Sign | |
Eq ValidationFailure | |
Eq Endianness | |
Eq String | |
Eq Encoding | |
Eq Seconds | |
Eq NanoSeconds | |
Eq Bitmap | |
Eq AsciiString | |
Eq FileName | |
Eq FilePath | |
Eq Relativity | |
Eq And | |
Eq Condition | |
Eq Arch | |
Eq OS | |
Eq IPv4 | |
Eq IPv6 | |
Eq UUID | |
Eq a => Eq [a] | |
Eq a => Eq (Ratio a) | |
Eq (StablePtr a) | |
Eq (Ptr a) | |
Eq (FunPtr a) | |
Eq (U1 p) | |
Eq p => Eq (Par1 p) | |
Eq a => Eq (Identity a) | |
Eq a => Eq (ZipList a) | |
Eq (TVar a) | |
Eq (ForeignPtr a) | |
Eq (IORef a) | |
Eq a => Eq (Dual a) | |
Eq a => Eq (Sum a) | |
Eq a => Eq (Product a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq a => Eq (Maybe a) | |
Eq (FinalPtr a) | |
Eq (CountOf ty) | |
Eq (Offset ty) | |
Eq a => Eq (NonEmpty a) | |
Eq a => Eq (BE a) | |
Eq a => Eq (LE a) | |
Eq a => Eq (Array a) | |
(PrimType ty, Eq ty) => Eq (Block ty) | |
(PrimType ty, Eq ty) => Eq (UArray ty) | |
PrimType ty => Eq (ChunkedUArray ty) | |
Eq a => Eq (DList a) | |
(Eq a, Eq b) => Eq (Either a b) | |
Eq (f p) => Eq (Rec1 f p) | |
(Eq a, Eq b) => Eq (a, b) | |
(Ix i, Eq e) => Eq (Array i e) | |
Eq a => Eq (Const a b) | |
Eq (Proxy k s) | |
Eq (STRef s a) | |
(Eq a, Eq b) => Eq (These a b) | |
(Eq a, Eq b) => Eq (Tuple2 a b) | |
Eq c => Eq (K1 i c p) | |
(Eq (f p), Eq (g p)) => Eq ((:+:) f g p) | |
(Eq (f p), Eq (g p)) => Eq ((:*:) f g p) | |
Eq (f (g p)) => Eq ((:.:) f g p) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq (STArray s i e) | |
Eq (f a) => Eq (Alt k f a) | |
Eq (Coercion k a b) | |
Eq ((:~:) k a b) | |
(Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) | |
Eq (f p) => Eq (M1 i c f p) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (Tuple4 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) |
class Bounded a where
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
class Enum a where
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
succ :: a -> a
the successor of a value. For numeric types, succ
adds 1.
pred :: a -> a
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
enumFrom :: a -> [a]
Used in Haskell's translation of [n..]
.
enumFromThen :: a -> a -> [a]
Used in Haskell's translation of [n,n'..]
.
enumFromTo :: a -> a -> [a]
Used in Haskell's translation of [n..m]
.
enumFromThenTo :: a -> a -> a -> [a]
Used in Haskell's translation of [n,n'..m]
.
Instances
Enum Bool | |
Enum Char | |
Enum Int | |
Enum Int8 | |
Enum Int16 | |
Enum Int32 | |
Enum Int64 | |
Enum Integer | |
Enum Ordering | |
Enum Word | |
Enum Word8 | |
Enum Word16 | |
Enum Word32 | |
Enum Word64 | |
Enum () | |
Enum Natural | |
Enum IOMode | |
Enum CDev | |
Enum CIno | |
Enum CMode | |
Enum COff | |
Enum CPid | |
Enum CSsize | |
Enum CGid | |
Enum CNlink | |
Enum CUid | |
Enum CCc | |
Enum CSpeed | |
Enum CTcflag | |
Enum CRLim | |
Enum Fd | |
Enum SeekMode | |
Enum WordPtr | |
Enum IntPtr | |
Enum CChar | |
Enum CSChar | |
Enum CUChar | |
Enum CShort | |
Enum CUShort | |
Enum CInt | |
Enum CUInt | |
Enum CLong | |
Enum CULong | |
Enum CLLong | |
Enum CULLong | |
Enum CFloat | |
Enum CDouble | |
Enum CPtrdiff | |
Enum CSize | |
Enum CWchar | |
Enum CSigAtomic | |
Enum CClock | |
Enum CTime | |
Enum CUSeconds | |
Enum CSUSeconds | |
Enum CIntPtr | |
Enum CUIntPtr | |
Enum CIntMax | |
Enum CUIntMax | |
Enum GeneralCategory | |
Enum Encoding | |
Enum Seconds | |
Enum NanoSeconds | |
Enum Arch | |
Enum OS | |
Integral a => Enum (Ratio a) | |
Enum (CountOf ty) | |
Enum (Offset ty) | |
Enum (Proxy k s) | |
Enum (f a) => Enum (Alt k f a) | |
Coercible k a b => Enum (Coercion k a b) | |
(~) k a b => Enum ((:~:) k a b) |
class Functor f where
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Minimal complete definition
Instances
Functor [] | |
Functor IO | |
Functor Id | |
Functor P | |
Functor Identity | |
Functor ZipList | |
Functor Handler | |
Functor STM | |
Functor First | |
Functor Last | |
Functor ReadP | |
Functor Maybe | |
Functor Partial | |
Functor Array | |
Functor DList | |
Functor Gen | |
Functor Check | |
Functor ((->) r) | |
Functor (Either a) | |
Functor ((,) a) | |
Functor (StateL s) | |
Functor (StateR s) | |
Ix i => Functor (Array i) | |
Functor (Const m) | |
Monad m => Functor (WrappedMonad m) | |
Arrow a => Functor (ArrowMonad a) | |
Functor (Proxy *) | |
Functor (ST s) | |
Functor (These a) | |
Functor m => Functor (ResourceT m) | |
Functor (MonadRandomState gen) | |
Functor (Parser input) | |
Functor (Result input) | |
Arrow a => Functor (WrappedArrow a b) | |
Functor f => Functor (Alt * f) | |
Functor m => Functor (ReaderT r m) | |
Functor m => Functor (StateT s m) | |
Monad m => Functor (ZipSink i m) | |
Functor (Conduit i o m) | |
Monad state => Functor (Builder collection mutCollection step state err) |
class Integral a where
Integral Literal support
e.g. 123 :: Integer 123 :: Word8
Methods
fromInteger :: Integer -> a
Instances
class Fractional a where
Fractional Literal support
e.g. 1.2 :: Double 0.03 :: Float
Methods
fromRational :: Rational -> a
class Bifunctor p where
Formally, the class Bifunctor
represents a bifunctor
from Hask
-> Hask
.
Intuitively it is a bifunctor where both the first and second arguments are covariant.
You can define a Bifunctor
by either defining bimap
or by
defining both first
and second
.
If you supply bimap
, you should ensure that:
bimap
id
id
≡id
If you supply first
and second
, ensure:
first
id
≡id
second
id
≡id
If you supply both, you should also ensure:
bimap
f g ≡first
f.
second
g
These ensure by parametricity:
bimap
(f.
g) (h.
i) ≡bimap
f h.
bimap
g ifirst
(f.
g) ≡first
f.
first
gsecond
(f.
g) ≡second
f.
second
g
Since: 4.8.0.0
class Functor f => Applicative f where
A functor with application, providing operations to
A minimal complete definition must include implementations of these functions satisfying the following laws:
- identity
pure
id
<*>
v = v- composition
pure
(.)<*>
u<*>
v<*>
w = u<*>
(v<*>
w)- homomorphism
pure
f<*>
pure
x =pure
(f x)- interchange
u
<*>
pure
y =pure
($
y)<*>
u
The other methods have the following default definitions, which may be overridden with equivalent specialized implementations:
As a consequence of these laws, the Functor
instance for f
will satisfy
If f
is also a Monad
, it should satisfy
(which implies that pure
and <*>
satisfy the applicative functor laws).
Methods
pure :: a -> f a
Lift a value.
(<*>) :: f (a -> b) -> f a -> f b infixl 4
Sequential application.
(*>) :: f a -> f b -> f b infixl 4
Sequence actions, discarding the value of the first argument.
(<*) :: f a -> f b -> f a infixl 4
Sequence actions, discarding the value of the second argument.
Instances
Applicative [] | |
Applicative IO | |
Applicative Id | |
Applicative P | |
Applicative Identity | |
Applicative ZipList | |
Applicative STM | |
Applicative First | |
Applicative Last | |
Applicative ReadP | |
Applicative Maybe | |
Applicative Partial | |
Applicative DList | |
Applicative Gen | |
Applicative Check | |
Applicative ((->) a) | |
Applicative (Either e) | |
Monoid a => Applicative ((,) a) | |
Applicative (StateL s) | |
Applicative (StateR s) | |
Monoid m => Applicative (Const m) | |
Monad m => Applicative (WrappedMonad m) | |
Arrow a => Applicative (ArrowMonad a) | |
Applicative (Proxy *) | |
Applicative (ST s) | |
Applicative m => Applicative (ResourceT m) | |
Applicative (MonadRandomState gen) | |
ParserSource input => Applicative (Parser input) | |
Arrow a => Applicative (WrappedArrow a b) | |
Applicative f => Applicative (Alt * f) | |
Applicative m => Applicative (ReaderT r m) | |
(Applicative m, Monad m) => Applicative (StateT s m) | |
Monad m => Applicative (ZipSink i m) | |
Applicative (Conduit i o m) | |
Monad state => Applicative (Builder collection mutCollection step state err) |
class Applicative m => Monad m where
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Minimal complete definition
Methods
(>>=) :: m a -> (a -> m b) -> m b infixl 1
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m b infixl 1
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
return :: a -> m a
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
Instances
Monad [] | |
Monad IO | |
Monad P | |
Monad Identity | |
Monad STM | |
Monad First | |
Monad Last | |
Monad ReadP | |
Monad Maybe | |
Monad Partial | |
Monad DList | |
Monad Gen | |
Monad Check | |
Monad ((->) r) | |
Monad (Either e) | |
Monad m => Monad (WrappedMonad m) | |
ArrowApply a => Monad (ArrowMonad a) | |
Monad (Proxy *) | |
Monad (ST s) | |
Monad m => Monad (ResourceT m) | |
Monad (MonadRandomState gen) | |
ParserSource input => Monad (Parser input) | |
Monad f => Monad (Alt * f) | |
Monad m => Monad (ReaderT r m) | |
(Functor m, Monad m) => Monad (StateT s m) | |
Monad (Conduit i o m) | |
Monad state => Monad (Builder collection mutCollection step state err) |
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1
Same as >>=
, but with the arguments interchanged.
class IsString a where
Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).
Methods
fromString :: String -> a
class IsList l where
The IsList
class and its methods are intended to be used in
conjunction with the OverloadedLists extension.
Since: 4.7.0.0
Associated Types
type Item l :: *
The Item
type function returns the type of items of the structure
l
.
Methods
The fromList
function constructs the structure l
from the given
list of Item l
fromListN :: Int -> [Item l] -> l
The fromListN
function takes the input list's length as a hint. Its
behaviour should be equivalent to fromList
. The hint can be used to
construct the structure l
more efficiently compared to fromList
. If
the given hint does not equal to the input list's length the behaviour of
fromListN
is not specified.
The toList
function extracts a list of Item l
from the structure l
.
It should satisfy fromList . toList = id.
Numeric type classes
class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a where
Number literals, convertible through the generic Integer type.
all number are Enum'erable, meaning that you can move to next element
class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a where
Non Negative Number literals, convertible through the generic Natural type
class Signed a where
types that have sign and can be made absolute
class Additive a where
Represent class of things that can be added together, contains a neutral element and is commutative.
x + azero = x azero + x = x x + y = y + x
Instances
class Subtractive a where
Represent class of things that can be subtracted.
Note that the result is not necessary of the same type as the operand depending on the actual type.
For example:
(-) :: Int -> Int -> Int (-) :: DateTime -> DateTime -> Seconds (-) :: Ptr a -> Ptr a -> PtrDiff (-) :: Natural -> Natural -> Maybe Natural
Associated Types
type Difference a
Methods
(-) :: a -> a -> Difference a infixl 6
Instances
class Multiplicative a where
Represent class of things that can be multiplied together
x * midentity = x midentity * x = x
Methods
midentity :: a
Identity element over multiplication
(*) :: a -> a -> a infixl 7
Multiplication of 2 elements that result in another element
(^) :: (IsNatural n, IDivisible n) => a -> n -> a infixr 8
Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (IsNatural n) => a -> n -> a
Instances
class (Additive a, Multiplicative a) => IDivisible a where
Represent types that supports an euclidian division
(x ‘div‘ y) * y + (x ‘mod‘ y) == x
class Multiplicative a => Divisible a where
Support for division between same types
This is likely to change to represent specific mathematic divisions
Methods
(/) :: a -> a -> a infixl 7
Data types
data Maybe a :: * -> *
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 | |
Functor Maybe | |
Applicative Maybe | |
Foldable Maybe | |
Traversable Maybe | |
Generic1 Maybe | |
Alternative Maybe | |
MonadPlus Maybe | |
MonadFailure Maybe | |
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) | |
Generic (Maybe a) | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
NormalForm a => NormalForm (Maybe a) | |
Arbitrary a => Arbitrary (Maybe a) | |
type Rep1 Maybe = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector Par1))) | |
type Failure Maybe = () | |
type Rep (Maybe a) = D1 D1Maybe ((:+:) (C1 C1_0Maybe U1) (C1 C1_1Maybe (S1 NoSelector (Rec0 a)))) | |
type (==) (Maybe k) a b = EqMaybe k a b |
data Ordering :: *
Instances
data Bool :: *
Instances
Bounded Bool | |
Enum Bool | |
Eq Bool | |
Data Bool | |
Ord Bool | |
Read Bool | |
Show Bool | |
Ix Bool | |
Generic Bool | |
Storable Bool | |
Bits Bool | |
FiniteBits Bool | |
NormalForm Bool | |
Arbitrary Bool | |
IsProperty Bool | |
IsProperty (String, Bool) | |
type Rep Bool = D1 D1Bool ((:+:) (C1 C1_0Bool U1) (C1 C1_1Bool U1)) | |
type (==) Bool a b = EqBool a b |
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
).
Instances
Bounded Char | |
Enum Char | |
Eq Char | |
Data Char | |
Ord Char | |
Read Char | |
Show Char | |
Ix Char | |
Generic Char | |
PrintfArg Char | |
IsChar Char | |
Storable Char | |
Subtractive Char | |
PrimType Char | |
NormalForm Char | |
StorableFixed Char | |
Storable Char | |
Arbitrary Char | |
IsString [Char] | |
type Rep Char = D1 D_Char (C1 C_Char (S1 NoSelector (Rec0 Char))) | |
type Difference Char = Int |
data IO a :: * -> *
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to
Main.main
in your program. When your program is run, the I/O will
be performed. It isn't possible to perform I/O from an arbitrary
function, unless that function is itself in the IO
monad and called
at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation
or the >>
and >>=
operations from the Monad
class.
Instances
Monad IO | |
Functor IO | |
Applicative IO | |
PrimMonad IO | |
MonadIO IO | |
MonadBracket IO | |
MonadCatch IO | |
MonadThrow IO | |
MonadRandom IO | |
(~) * a () => PrintfType (IO a) | |
(~) * a () => HPrintfType (IO a) | |
type PrimState IO = RealWorld | |
type PrimVar IO = IORef |
data Either a b :: * -> * -> *
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
Bifunctor Either | |
Monad (Either e) | |
Functor (Either a) | |
Applicative (Either e) | |
Foldable (Either a) | |
Traversable (Either a) | |
Generic1 (Either a) | |
MonadFailure (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) | |
Generic (Either a b) | |
(NormalForm l, NormalForm r) => NormalForm (Either l r) | |
(Arbitrary l, Arbitrary r) => Arbitrary (Either l r) | |
type Rep1 (Either a) = D1 D1Either ((:+:) (C1 C1_0Either (S1 NoSelector (Rec0 a))) (C1 C1_1Either (S1 NoSelector Par1))) | |
type Failure (Either a) = a | |
type Rep (Either a b) = D1 D1Either ((:+:) (C1 C1_0Either (S1 NoSelector (Rec0 a))) (C1 C1_1Either (S1 NoSelector (Rec0 b)))) | |
type (==) (Either k k1) a b = EqEither k k1 a b |
Numbers
data Int8 :: *
8-bit signed integer type
Instances
data Int16 :: *
16-bit signed integer type
Instances
data Int32 :: *
32-bit signed integer type
Instances
data Int64 :: *
64-bit signed integer type
Instances
data Word8 :: *
8-bit unsigned integer type
Instances
data Word16 :: *
16-bit unsigned integer type
Instances
data Word32 :: *
32-bit unsigned integer type
Instances
data Word64 :: *
64-bit unsigned integer type
Instances
data Word :: *
Instances
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
data Integer :: *
Invariant: Jn#
and Jp#
are used iff value doesn't fit in S#
Useful properties resulting from the invariants:
Instances
data Natural :: *
Type representing arbitrary-precision non-negative integers.
Operations whose result would be negative
.throw
(Underflow
:: ArithException
)
Since: 4.8.0.0
Instances
data Float :: *
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
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
newtype CountOf ty
CountOf of a data structure.
More specifically, it represents the number of elements of type ty
that fit
into the data structure.
>>>
length (fromList ['a', 'b', 'c', '🌟']) :: CountOf Char
CountOf 4
Same caveats as Offset
apply here.
Instances
IntegralCast Int (CountOf ty) | |
IntegralCast Word (CountOf ty) | |
Enum (CountOf ty) | |
Eq (CountOf ty) | |
Num (CountOf ty) | |
Ord (CountOf ty) | |
Show (CountOf ty) | |
Monoid (CountOf ty) | |
Integral (CountOf ty) | |
IsNatural (CountOf ty) | |
IsIntegral (CountOf ty) | |
Additive (CountOf ty) | |
Subtractive (CountOf ty) | |
NormalForm (CountOf a) | |
Arbitrary (CountOf ty) | |
type Difference (CountOf ty) = CountOf ty |
newtype Offset ty
Offset in a data structure consisting of elements of type ty
.
Int is a terrible backing type which is hard to get away from, considering that GHC/Haskell are mostly using this for offset. Trying to bring some sanity by a lightweight wrapping.
Instances
IntegralCast Int (Offset ty) | |
IntegralCast Word (Offset ty) | |
Enum (Offset ty) | |
Eq (Offset ty) | |
Num (Offset ty) | |
Ord (Offset ty) | |
Show (Offset ty) | |
Integral (Offset ty) | |
IsNatural (Offset ty) | |
IsIntegral (Offset ty) | |
Additive (Offset ty) | |
Subtractive (Offset ty) | |
NormalForm (Offset a) | |
type Difference (Offset ty) = CountOf ty |
Collection types
data UArray ty
An array of type built on top of GHC primitive.
The elements need to have fixed sized and the representation is a packed contiguous array in memory that can easily be passed to foreign interface
Instances
PrimType ty => IsList (UArray ty) | |
(PrimType ty, Eq ty) => Eq (UArray ty) | |
Data ty => Data (UArray ty) | |
(PrimType ty, Ord ty) => Ord (UArray ty) | |
(PrimType ty, Show ty) => Show (UArray ty) | |
PrimType ty => Monoid (UArray ty) | |
NormalForm (UArray ty) | |
PrimType ty => Buildable (UArray ty) | |
PrimType ty => Fold1able (UArray ty) | |
PrimType ty => Foldable (UArray ty) | |
PrimType ty => IndexedCollection (UArray ty) | |
PrimType ty => InnerFunctor (UArray ty) | |
PrimType ty => Collection (UArray ty) | |
PrimType ty => Sequential (UArray ty) | |
PrimType ty => Zippable (UArray ty) | |
PrimType ty => Copy (UArray ty) | |
PrimType a => Hashable (UArray a) | |
type Item (UArray ty) = ty | |
type Element (UArray ty) = ty | |
type Mutable (UArray ty) = MUArray ty | |
type Step (UArray ty) = ty |
Represent the accessor for types that can be stored in the UArray and MUArray.
Types need to be a instance of storable and have fixed sized.
Minimal complete definition
primSizeInBytes, primShiftToBytes, primBaUIndex, primMbaURead, primMbaUWrite, primAddrIndex, primAddrRead, primAddrWrite
Instances
data Array a
Array of a
Instances
Functor Array | |
Mappable Array | |
IsList (Array ty) | |
Eq a => Eq (Array a) | |
Data ty => Data (Array ty) | |
Ord a => Ord (Array a) | |
Show a => Show (Array a) | |
Monoid (Array a) | |
NormalForm a => NormalForm (Array a) | |
Buildable (Array ty) | |
Fold1able (Array ty) | |
Foldable (Array ty) | |
IndexedCollection (Array ty) | |
InnerFunctor (Array ty) | |
Collection (Array ty) | |
Sequential (Array ty) | |
BoxedZippable (Array ty) | |
Zippable (Array ty) | |
Copy (Array ty) | |
type Item (Array ty) = ty | |
type Element (Array ty) = ty | |
type Mutable (Array ty) = MArray ty | |
type Step (Array ty) = ty |
data String
Opaque packed array of characters in the UTF8 encoding
Instances
IsList String | |
Eq String | |
Data String | |
Ord String | |
Show String | |
IsString String | |
Monoid String | |
NormalForm String | |
Buildable String | |
IndexedCollection String | |
InnerFunctor String | |
Collection String | |
Sequential String | |
Zippable String | |
Copy String | |
ParserSource String | |
Arbitrary String | |
Hashable String | |
IsProperty (String, Bool) | |
type Item String = Char | |
type Element String = Char | |
type Mutable String | |
type Step String = Word8 | |
type Chunk String = String |
Numeric functions
(^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8
raise a number to an integral power
fromIntegral :: (Integral a, Num b) => a -> b
general coercion from integral types
realToFrac :: (Real a, Fractional b) => a -> b
general coercion to fractional types
Monoids
class Monoid a where
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat =
foldr
mappend mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
Methods
mempty :: a
Identity of mappend
mappend :: a -> a -> a
An associative operation
mconcat :: [a] -> a
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
Instances
Monoid Ordering | |
Monoid () | |
Monoid All | |
Monoid Any | |
Monoid String | |
Monoid Builder | |
Monoid Bitmap | |
Monoid AsciiString | |
Monoid FileName | |
Monoid [a] | |
Ord a => Monoid (Max a) | |
Ord a => Monoid (Min a) | |
Monoid a => Monoid (Dual a) | |
Monoid (Endo a) | |
Num a => Monoid (Sum a) | |
Num a => Monoid (Product a) | |
Monoid (First a) | |
Monoid (Last a) | |
Monoid a => Monoid (Maybe a) | Lift a semigroup into |
Monoid (CountOf ty) | |
Monoid (Array a) | |
PrimType ty => Monoid (Block ty) | |
PrimType ty => Monoid (UArray ty) | |
Monoid (ChunkedUArray a) | |
Monoid (DList a) | |
Monoid b => Monoid (a -> b) | |
(Monoid a, Monoid b) => Monoid (a, b) | |
Monoid a => Monoid (Const a b) | |
Monoid (Proxy k s) | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | |
Alternative f => Monoid (Alt * f a) | |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) |
Collection
class (IsList c, Item c ~ Element c) => Collection c where
A set of methods for ordered colection
Methods
Check if a collection is empty
length :: c -> CountOf (Element c)
Length of a collection (number of Element c)
elem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
Check if a collection contains a specific element
This is the inverse of notElem
.
notElem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
Check if a collection does *not* contain a specific element
This is the inverse of elem
.
maximum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
Get the maximum element of a collection
minimum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
Get the minimum element of a collection
any :: (Element c -> Bool) -> c -> Bool
Determine is any elements of the collection satisfy the predicate
all :: (Element c -> Bool) -> c -> Bool
Determine is all elements of the collection satisfy the predicate
Instances
Collection String | |
Collection Bitmap | |
Collection AsciiString | |
Collection [a] | |
Collection c => Collection (NonEmpty c) | |
Collection (Array ty) | |
PrimType ty => Collection (Block ty) | |
PrimType ty => Collection (UArray ty) | |
PrimType ty => Collection (ChunkedUArray ty) | |
Collection (DList a) |
and :: (Collection col, Element col ~ Bool) => col -> Bool
Return True if all the elements in the collection are True
or :: (Collection col, Element col ~ Bool) => col -> Bool
Return True if at least one element in the collection is True
class (IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where
A set of methods for ordered colection
Minimal complete definition
(take, drop | splitAt), (revTake, revDrop | revSplitAt), splitOn, (break | span), intersperse, filter, reverse, uncons, unsnoc, snoc, cons, find, sortBy, singleton, replicate
Methods
take :: CountOf (Element c) -> c -> c
Take the first @n elements of a collection
revTake :: CountOf (Element c) -> c -> c
Take the last @n elements of a collection
drop :: CountOf (Element c) -> c -> c
Drop the first @n elements of a collection
revDrop :: CountOf (Element c) -> c -> c
Drop the last @n elements of a collection
splitAt :: CountOf (Element c) -> c -> (c, c)
Split the collection at the @n'th elements
revSplitAt :: CountOf (Element c) -> c -> (c, c)
Split the collection at the @n'th elements from the end
splitOn :: (Element c -> Bool) -> c -> [c]
Split on a specific elements returning a list of colletion
break :: (Element c -> Bool) -> c -> (c, c)
Split a collection when the predicate return true
breakElem :: Eq (Element c) => Element c -> c -> (c, c)
Split a collection when the predicate return true
takeWhile :: (Element c -> Bool) -> c -> c
Return the longest prefix in the collection that satisfy the predicate
dropWhile :: (Element c -> Bool) -> c -> c
Return the longest prefix in the collection that satisfy the predicate
intersperse :: Element c -> c -> c
The intersperse
function takes an element and a list and
`intersperses' that element between the elements of the list.
For example,
intersperse ',' "abcde" == "a,b,c,d,e"
intercalate :: Monoid (Item c) => Element c -> c -> Element c
intercalate
xs xss
is equivalent to (
.
It inserts the list mconcat
(intersperse
xs xss))xs
in between the lists in xss
and concatenates the
result.
span :: (Element c -> Bool) -> c -> (c, c)
Split a collection while the predicate return true
filter :: (Element c -> Bool) -> c -> c
Filter all the elements that satisfy the predicate
partition :: (Element c -> Bool) -> c -> (c, c)
Partition the elements thtat satisfy the predicate and those that don't
reverse :: c -> c
Reverse a collection
uncons :: c -> Maybe (Element c, c)
Decompose a collection into its first element and the remaining collection. If the collection is empty, returns Nothing.
unsnoc :: c -> Maybe (c, Element c)
Decompose a collection into a collection without its last element, and the last element If the collection is empty, returns Nothing.
Prepend an element to an ordered collection
Append an element to an ordered collection
find :: (Element c -> Bool) -> c -> Maybe (Element c)
Find an element in an ordered collection
sortBy :: (Element c -> Element c -> Ordering) -> c -> c
Sort an ordered collection using the specified order function
Create a collection with a single element
head :: NonEmpty c -> Element c
get the first element of a non-empty collection
last :: NonEmpty c -> Element c
get the last element of a non-empty collection
Extract the elements after the first element of a non-empty collection.
Extract the elements before the last element of a non-empty collection.
replicate :: CountOf (Element c) -> Element c -> c
Create a collection where the element in parameter is repeated N time
isPrefixOf :: Eq (Element c) => c -> c -> Bool
Takes two collections and returns True iff the first collection is a prefix of the second.
isSuffixOf :: Eq (Element c) => c -> c -> Bool
Takes two collections and returns True iff the first collection is a suffix of the second.
isInfixOf :: Eq (Element c) => c -> c -> Bool
Takes two collections and returns True iff the first collection is an infix of the second.
stripPrefix :: Eq (Element c) => c -> c -> Maybe c
Try to strip a prefix from a collection
stripSuffix :: Eq (Element c) => c -> c -> Maybe c
Try to strip a suffix from a collection
Instances
Sequential String | |
Sequential Bitmap | |
Sequential AsciiString | |
Sequential [a] | |
Sequential (Array ty) | |
PrimType ty => Sequential (Block ty) | |
PrimType ty => Sequential (UArray ty) | |
PrimType ty => Sequential (ChunkedUArray ty) | |
Sequential (DList a) |
data NonEmpty a
NonEmpty property for any Collection
nonEmpty :: Collection c => c -> Maybe (NonEmpty c)
Smart constructor to create a NonEmpty collection
If the collection is empty, then Nothing is returned Otherwise, the collection is wrapped in the NonEmpty property
Folds
class Foldable collection where
Give the ability to fold a collection on itself
Methods
foldl' :: (a -> Element collection -> a) -> a -> collection -> a
Left-associative fold of a structure.
In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.
Note that Foundation only provides foldl'
, a strict version of foldl
because
the lazy version is seldom useful.
Left-associative fold of a structure with strict application of the operator.
foldr :: (Element collection -> a -> a) -> a -> collection -> a
Right-associative fold of a structure.
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
foldr' :: (Element collection -> a -> a) -> a -> collection -> a
Right-associative fold of a structure, but with strict application of the operator.
Maybe
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
The mapMaybe
function is a version of map
which can throw
out elements. In particular, the functional argument returns
something of type
. If this is Maybe
bNothing
, no element
is added on to the result list. If it is
, then Just
bb
is
included in the result list.
Examples
Using
is a shortcut for mapMaybe
f x
in most cases:catMaybes
$ map
f x
>>>
import Text.Read ( readMaybe )
>>>
let readMaybeInt = readMaybe :: String -> Maybe Int
>>>
mapMaybe readMaybeInt ["1", "Foo", "3"]
[1,3]>>>
catMaybes $ map readMaybeInt ["1", "Foo", "3"]
[1,3]
If we map the Just
constructor, the entire list should be returned:
>>>
mapMaybe Just [1,2,3]
[1,2,3]
The catMaybes
function takes a list of Maybe
s and returns
a list of all the Just
values.
Examples
Basic usage:
>>>
catMaybes [Just 1, Nothing, Just 3]
[1,3]
When constructing a list of Maybe
values, catMaybes
can be used
to return all of the "success" results (if the list is the result
of a map
, then mapMaybe
would be more appropriate):
>>>
import Text.Read ( readMaybe )
>>>
[readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[Just 1,Nothing,Just 3]>>>
catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
[1,3]
fromMaybe :: a -> Maybe a -> a
The fromMaybe
function takes a default value and and Maybe
value. If the Maybe
is Nothing
, it returns the default values;
otherwise, it returns the value contained in the Maybe
.
Examples
Basic usage:
>>>
fromMaybe "" (Just "Hello, World!")
"Hello, World!"
>>>
fromMaybe "" Nothing
""
Read an integer from a string using readMaybe
. If we fail to
parse an integer, we want to return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
fromMaybe 0 (readMaybe "5")
5>>>
fromMaybe 0 (readMaybe "")
0
listToMaybe :: [a] -> Maybe a
The listToMaybe
function returns Nothing
on an empty list
or
where Just
aa
is the first element of the list.
Examples
Basic usage:
>>>
listToMaybe []
Nothing
>>>
listToMaybe [9]
Just 9
>>>
listToMaybe [1,2,3]
Just 1
Composing maybeToList
with listToMaybe
should be the identity
on singleton/empty lists:
>>>
maybeToList $ listToMaybe [5]
[5]>>>
maybeToList $ listToMaybe []
[]
But not on lists with more than one element:
>>>
maybeToList $ listToMaybe [1,2,3]
[1]
maybeToList :: Maybe a -> [a]
The maybeToList
function returns an empty list when given
Nothing
or a singleton list when not given Nothing
.
Examples
Basic usage:
>>>
maybeToList (Just 7)
[7]
>>>
maybeToList Nothing
[]
One can use maybeToList
to avoid pattern matching when combined
with a function that (safely) works on lists:
>>>
import Text.Read ( readMaybe )
>>>
sum $ maybeToList (readMaybe "3")
3>>>
sum $ maybeToList (readMaybe "")
0
Either
partitionEithers :: [Either a b] -> ([a], [b])
Partitions a list of Either
into two lists.
All the Left
elements are extracted, in order, to the first
component of the output. Similarly the Right
elements are extracted
to the second component of the output.
Examples
Basic usage:
>>>
let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>>
partitionEithers list
(["foo","bar","baz"],[3,7])
The pair returned by
should be the same
pair as partitionEithers
x(
:lefts
x, rights
x)
>>>
let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>>
partitionEithers list == (lefts list, rights list)
True
Function
on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0
Applicative
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4
An infix synonym for fmap
.
Examples
Convert from a
to a Maybe
Int
using Maybe
String
show
:
>>>
show <$> Nothing
Nothing>>>
show <$> Just 3
Just "3"
Convert from an
to an Either
Int
Int
Either
Int
String
using show
:
>>>
show <$> Left 17
Left 17>>>
show <$> Right 17
Right "17"
Double each element of a list:
>>>
(*2) <$> [1,2,3]
[2,4,6]
Apply even
to the second element of a pair:
>>>
even <$> (2,2)
(2,True)
(<|>) :: Alternative f => forall a. f a -> f a -> f a
An associative binary operation
Monad
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1
Left-to-right Kleisli composition of monads.
Exceptions
class (Typeable * e, Show e) => Exception e where
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving (Show, Typeable) instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e deriving Typeable instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e deriving Typeable instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving (Typeable, Show) instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
Minimal complete definition
Nothing
Methods
toException :: e -> SomeException
fromException :: SomeException -> Maybe e
displayException :: e -> String
Instances
class Typeable a
The class Typeable
allows a concrete representation of a type to
be calculated.
Minimal complete definition
data SomeException :: *
The SomeException
type is the root of the exception type hierarchy.
When an exception of type e
is thrown, behind the scenes it is
encapsulated in a SomeException
.
Instances
data IOException :: *
Exceptions that occur in the IO
monad.
An IOException
records a more specific error type, a descriptive
string and maybe the handle that was used when the error was
flagged.
Instances
Proxy
data Proxy t :: k -> *
A concrete, poly-kinded proxy type
Constructors
Proxy |
Instances
Monad (Proxy *) | |
Functor (Proxy *) | |
Applicative (Proxy *) | |
Foldable (Proxy *) | |
Traversable (Proxy *) | |
Bounded (Proxy k s) | |
Enum (Proxy k s) | |
Eq (Proxy k s) | |
Data t => Data (Proxy * t) | |
Ord (Proxy k s) | |
Read (Proxy k s) | |
Show (Proxy k s) | |
Ix (Proxy k s) | |
Generic (Proxy * t) | |
Monoid (Proxy k s) | |
type Rep (Proxy k t) = D1 D1Proxy (C1 C1_0Proxy U1) |
asProxyTypeOf :: a -> Proxy * a -> a
asProxyTypeOf
is a type-restricted version of const
.
It is usually used as an infix operator, and its typing forces its first
argument (which is usually overloaded) to have the same type as the tag
of the second.
Partial
Create a value that is partial. this can only be
unwrap using the fromPartial
function
data PartialError
An error related to the evaluation of a Partial value that failed.
it contains the name of the function and the reason for failure
Instances
fromPartial :: Partial a -> a
Dewrap a possible partial value
ifThenElse :: Bool -> a -> a -> a
for support of if .. then .. else