-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Alternative prelude with batteries and no dependencies -- -- A custom prelude with no dependencies apart from base. -- -- This package has the following goals: -- -- @package foundation @version 0.0.1 -- | Enforce strictness when executing lambda module Foundation.Strict strict1 :: (a -> b) -> a -> b strict2 :: (a -> b -> c) -> a -> b -> c strict3 :: (a -> b -> c -> d) -> a -> b -> c -> d strict4 :: (a -> b -> c -> d -> e) -> a -> b -> c -> d -> e strict5 :: (a -> b -> c -> d -> e -> f) -> a -> b -> c -> d -> e -> f strict6 :: (a -> b -> c -> d -> e -> f -> g) -> a -> b -> c -> d -> e -> f -> g -- | Compared to the Haskell hierarchy of number classes this provide a -- more flexible approach that is closer to the mathematical foundation -- (group, field, etc) -- -- This try to only provide one feature per class, at the expense of the -- number of classes. module Foundation.Number -- | Number literals, convertible through the generic Integer type. -- -- all number are Enum'erable, meaning that you can move to next element class (Eq a, Ord a, Num a, Enum a, Additive a, Subtractive a, Difference a ~ a, Multiplicative a, Divisible a) => Number a toInteger :: Number a => a -> Integer -- | convert an Integer to a type having the Number constraint fromInteger :: Number a => Integer -> a -- | Number literals that can be negative class Number a => Signed a abs :: Signed a => a -> a signum :: Signed a => a -> Sign -- | Represent class of things that can be added together, contains a -- neutral element and is commutative. -- -- class Additive a where scale 0 _ = azero scale 1 a = a scale 2 a = a + a scale n a | n < 0 = error "cannot scale by negative number" | otherwise = a + scale (pred n) a azero :: Additive a => a (+) :: Additive a => a -> a -> a scale :: (Additive a, Number n) => n -> a -> a scale :: (Additive a, Number n) => n -> a -> a -- | Represent class of things that can be multiplied together -- -- class Multiplicative a where (^) = power -- | Identity element over multiplication midentity :: Multiplicative a => a -- | Multiplication of 2 elements that result in another element (*) :: Multiplicative a => a -> a -> a -- | Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a -- ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (Multiplicative a, Number n) => a -> n -> a -- | 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: e.g. (-) :: Int -> Int -> Int (-) :: DateTime -> -- DateTime -> Seconds (-) :: Ptr a -> Ptr a -> PtrDiff class Subtractive a where type Difference a where { type family Difference a; } (-) :: Subtractive a => a -> a -> Difference a -- | Represent class of things that can be divided -- -- (x ‘div‘ y) * y + (x ‘mod‘ y) == x class Multiplicative a => Divisible a where div a b = fst $ divMod a b mod a b = snd $ divMod a b divMod a b = (div a b, mod a b) div :: Divisible a => a -> a -> a mod :: Divisible a => a -> a -> a divMod :: Divisible a => a -> a -> (a, a) -- | Sign of a signed number data Sign Negative :: Sign Zero :: Sign Positive :: Sign instance GHC.Classes.Eq Foundation.Number.Sign instance Foundation.Number.Number GHC.Integer.Type.Integer instance Foundation.Number.Number GHC.Types.Int instance Foundation.Number.Number GHC.Int.Int8 instance Foundation.Number.Number GHC.Int.Int16 instance Foundation.Number.Number GHC.Int.Int32 instance Foundation.Number.Number GHC.Int.Int64 instance Foundation.Number.Signed GHC.Integer.Type.Integer instance Foundation.Number.Signed GHC.Types.Int instance Foundation.Number.Signed GHC.Int.Int8 instance Foundation.Number.Signed GHC.Int.Int16 instance Foundation.Number.Signed GHC.Int.Int32 instance Foundation.Number.Signed GHC.Int.Int64 instance Foundation.Number.Number GHC.Types.Word instance Foundation.Number.Number GHC.Word.Word8 instance Foundation.Number.Number GHC.Word.Word16 instance Foundation.Number.Number GHC.Word.Word32 instance Foundation.Number.Number GHC.Word.Word64 instance Foundation.Number.Additive GHC.Integer.Type.Integer instance Foundation.Number.Additive GHC.Types.Int instance Foundation.Number.Additive GHC.Int.Int8 instance Foundation.Number.Additive GHC.Int.Int16 instance Foundation.Number.Additive GHC.Int.Int32 instance Foundation.Number.Additive GHC.Int.Int64 instance Foundation.Number.Additive GHC.Types.Word instance Foundation.Number.Additive GHC.Word.Word8 instance Foundation.Number.Additive GHC.Word.Word16 instance Foundation.Number.Additive GHC.Word.Word32 instance Foundation.Number.Additive GHC.Word.Word64 instance Foundation.Number.Subtractive GHC.Integer.Type.Integer instance Foundation.Number.Subtractive GHC.Types.Int instance Foundation.Number.Subtractive GHC.Int.Int8 instance Foundation.Number.Subtractive GHC.Int.Int16 instance Foundation.Number.Subtractive GHC.Int.Int32 instance Foundation.Number.Subtractive GHC.Int.Int64 instance Foundation.Number.Subtractive GHC.Types.Word instance Foundation.Number.Subtractive GHC.Word.Word8 instance Foundation.Number.Subtractive GHC.Word.Word16 instance Foundation.Number.Subtractive GHC.Word.Word32 instance Foundation.Number.Subtractive GHC.Word.Word64 instance Foundation.Number.Multiplicative GHC.Integer.Type.Integer instance Foundation.Number.Multiplicative GHC.Types.Int instance Foundation.Number.Multiplicative GHC.Int.Int8 instance Foundation.Number.Multiplicative GHC.Int.Int16 instance Foundation.Number.Multiplicative GHC.Int.Int32 instance Foundation.Number.Multiplicative GHC.Int.Int64 instance Foundation.Number.Multiplicative GHC.Types.Word instance Foundation.Number.Multiplicative GHC.Word.Word8 instance Foundation.Number.Multiplicative GHC.Word.Word16 instance Foundation.Number.Multiplicative GHC.Word.Word32 instance Foundation.Number.Multiplicative GHC.Word.Word64 instance Foundation.Number.Divisible GHC.Integer.Type.Integer instance Foundation.Number.Divisible GHC.Types.Int instance Foundation.Number.Divisible GHC.Int.Int8 instance Foundation.Number.Divisible GHC.Int.Int16 instance Foundation.Number.Divisible GHC.Int.Int32 instance Foundation.Number.Divisible GHC.Int.Int64 instance Foundation.Number.Divisible GHC.Types.Word instance Foundation.Number.Divisible GHC.Word.Word8 instance Foundation.Number.Divisible GHC.Word.Word16 instance Foundation.Number.Divisible GHC.Word.Word32 instance Foundation.Number.Divisible GHC.Word.Word64 module Foundation.Convertible -- | Class of things that can be converted from a to b class Convertible a b where type Convert a b where { type family Convert a b; } convert :: Convertible a b => Proxy b -> a -> Convert a b instance Foundation.Convertible.Convertible a a module Foundation.VFS.Path -- | Path type class -- -- defines the Path associated types and basic functions to implement -- related to the path manipulation -- -- # TODO, add missing enhancement: -- -- ``` splitExtension :: PathEnt path -> (PathEnt path, PathEnt path) -- addExtension :: PathEnt path -> PathEnt path -> PathEnt path -- (.) :: path -> PathEnt path -> path (-.) :: path -- -> PathEnt path -> path ``` class Path path where type PathEnt path type PathPrefix path type PathSuffix path where { type family PathEnt path; type family PathPrefix path; type family PathSuffix path; } -- | join a path entity to a given path () :: Path path => path -> PathEnt path -> path -- | split the path into the associated elements splitPath :: Path path => path -> (PathPrefix path, [PathEnt path], PathSuffix path) -- | build the path from the associated elements buildPath :: Path path => (PathPrefix path, [PathEnt path], PathSuffix path) -> path -- | parent is only going to drop the filename. -- -- if you actually want to reference to the parent directory, simply -- uses: -- -- ``` parent "." = "." <> ".." ``` parent :: Path path => path -> path -- | get the filename of the given path -- -- If there is no filename, you will receive the mempty of the PathEnt filename :: (Path path, Monoid (PathEnt path)) => path -> PathEnt path -- | get the path prefix information -- -- ``` prefix "hometab" == () ``` -- -- or for URI (TODO, not yet accurate) -- -- ``` prefix "http://github.com/vincenthz/hs-foundation?w=1" == -- URISchema http Nothing Nothing "github.com" Nothing ``` prefix :: Path path => path -> PathPrefix path -- | get the path suffix information -- -- ``` suffix "hometab" == () ``` -- -- or for URI (TODO, not yet accurate) -- -- ``` suffix "http://github.com/vincenthz/hs-foundation?w=1" == -- URISuffix (["w", "1"], Nothing) ``` suffix :: Path path => path -> PathSuffix path module Foundation.VFS.URI -- | TODO this is not implemented yet data URI URI :: URI data URISchema URISchema :: URISchema data URIAuthority URIAuthority :: URIAuthority data URIQuery URIQuery :: URIQuery data URIFragment URIFragment :: URIFragment data URIPath URIPath :: URIPath instance Foundation.VFS.Path.Path Foundation.VFS.URI.URI -- | Different collections (list, vector, string, ..) unified under 1 API. -- an API to rules them all, and in the darkness bind them. module Foundation.Primitive -- | 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. class Eq ty => PrimType ty -- | get the size in bytes of a ty element primSizeInBytes :: PrimType ty => Proxy ty -> Size8 -- | return the element stored at a specific index primBaIndex :: PrimType ty => ByteArray# -> Offset ty -> ty -- | Read an element at an index in a mutable array primMbaRead :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty -- | Write an element to a specific cell in a mutable array. primMbaWrite :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () -- | Read from Address, without a state. the value read should be -- considered a constant for all pratical purpose, otherwise bad thing -- will happens. primAddrIndex :: PrimType ty => Addr# -> Offset ty -> ty -- | Read a value from Addr in a specific primitive monad primAddrRead :: (PrimType ty, PrimMonad prim) => Addr# -> Offset ty -> prim ty -- | Write a value to Addr in a specific primitive monad primAddrWrite :: (PrimType ty, PrimMonad prim) => Addr# -> Offset ty -> ty -> prim () -- | Primitive monad that can handle mutation. -- -- For example: IO and ST. class (Functor m, Monad m) => PrimMonad m where type PrimState m type PrimVar m :: * -> * where { type family PrimState m; type family PrimVar m :: * -> *; } -- | Unwrap the State# token to pass to a function a primitive function -- that returns an unboxed state and a value. primitive :: PrimMonad m => (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a -- | Throw Exception in the primitive monad primThrow :: (PrimMonad m, Exception e) => e -> m a -- | Run a Prim monad from a dedicated state# unPrimMonad :: PrimMonad m => m a -> State# (PrimState m) -> (# State# (PrimState m), a #) -- | Build a new variable in the Prim Monad primVarNew :: PrimMonad m => a -> m (PrimVar m a) -- | Read the variable in the Prim Monad primVarRead :: PrimMonad m => PrimVar m a -> m a -- | Write the variable in the Prim Monad primVarWrite :: PrimMonad m => PrimVar m a -> a -> m () -- | Give access to Array non public functions which can be used to make -- certains optimisations. -- -- Most of what is available here has no guarantees of stability. -- Anything can be removed and changed. module Foundation.Array.Internal -- | 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 data UArray ty UVecBA :: {-# UNPACK #-} !(Offset ty) -> {-# UNPACK #-} !(Size ty) -> {-# UNPACK #-} !PinnedStatus -> ByteArray# -> UArray ty UVecAddr :: {-# UNPACK #-} !(Offset ty) -> {-# UNPACK #-} !(Size ty) -> !(FinalPtr ty) -> UArray ty fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty recast :: (PrimType a, PrimType b) => UArray a -> UArray b module Foundation.Foreign -- | Create a pointer with an associated finalizer data FinalPtr a FinalPtr :: (Ptr a) -> FinalPtr a FinalForeign :: (ForeignPtr a) -> FinalPtr a -- | Check if 2 final ptr points on the same memory bits -- -- it stand to reason that provided a final ptr that is still being -- referenced and thus have the memory still valid, if 2 final ptrs have -- the same address, they should be the same final ptr finalPtrSameMemory :: FinalPtr a -> FinalPtr b -> Bool -- | Cast a finalized pointer from type a to type b castFinalPtr :: FinalPtr a -> FinalPtr b -- | create a new FinalPtr from a Pointer toFinalPtr :: PrimMonad prim => Ptr a -> (Ptr a -> IO ()) -> prim (FinalPtr a) -- | Create a new FinalPtr from a ForeignPtr toFinalPtrForeign :: ForeignPtr a -> FinalPtr a -- | Looks at the raw pointer inside a FinalPtr, making sure the data -- pointed by the pointer is not finalized during the call to f withFinalPtr :: PrimMonad prim => FinalPtr p -> (Ptr p -> prim a) -> prim a -- | Unsafe version of withFinalPtr withUnsafeFinalPtr :: PrimMonad prim => FinalPtr p -> (Ptr p -> prim a) -> a withFinalPtrNoTouch :: FinalPtr p -> (Ptr p -> a) -> a foreignMem :: PrimType ty => FinalPtr ty -> Int -> UArray ty mutableForeignMem :: (PrimMonad prim, PrimType ty) => FinalPtr ty -> Int -> prim (MUArray ty (PrimState prim)) -- | Different collections (list, vector, string, ..) unified under 1 API. -- an API to rules them all, and in the darkness bind them. module Foundation.Collection class Zippable col => BoxedZippable col where zip = zipWith (,) zip3 = zipWith3 (,,) zip4 = zipWith4 (,,,) zip5 = zipWith5 (,,,,) zip6 = zipWith6 (,,,,,) zip7 = zipWith7 (,,,,,,) unzip = go . toList where go [] = (mempty, mempty) go ((a, b) : xs) = let (as, bs) = go xs in (a `cons` as, b `cons` bs) unzip3 = go . toList where go [] = (mempty, mempty, mempty) go ((a, b, c) : xs) = let (as, bs, cs) = go xs in (a `cons` as, b `cons` bs, c `cons` cs) unzip4 = go . toList where go [] = (mempty, mempty, mempty, mempty) go ((a, b, c, d) : xs) = let (as, bs, cs, ds) = go xs in (a `cons` as, b `cons` bs, c `cons` cs, d `cons` ds) unzip5 = go . toList where go [] = (mempty, mempty, mempty, mempty, mempty) go ((a, b, c, d, e) : xs) = let (as, bs, cs, ds, es) = go xs in (a `cons` as, b `cons` bs, c `cons` cs, d `cons` ds, e `cons` es) unzip6 = go . toList where go [] = (mempty, mempty, mempty, mempty, mempty, mempty) go ((a, b, c, d, e, f) : xs) = let (as, bs, cs, ds, es, fs) = go xs in (a `cons` as, b `cons` bs, c `cons` cs, d `cons` ds, e `cons` es, f `cons` fs) unzip7 = go . toList where go [] = (mempty, mempty, mempty, mempty, mempty, mempty, mempty) go ((a, b, c, d, e, f, g) : xs) = let (as, bs, cs, ds, es, fs, gs) = go xs in (a `cons` as, b `cons` bs, c `cons` cs, d `cons` ds, e `cons` es, f `cons` fs, g `cons` gs) -- | zip takes two collections and returns a collections of -- corresponding pairs. If one input collection is short, excess elements -- of the longer collection are discarded. zip :: (BoxedZippable col, Sequential a, Sequential b, Element col ~ (Element a, Element b)) => a -> b -> col -- | Like zip, but works with 3 collections. zip3 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Element col ~ (Element a, Element b, Element c)) => a -> b -> c -> col -- | Like zip, but works with 4 collections. zip4 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Element col ~ (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> col -- | Like zip, but works with 5 collections. zip5 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element col ~ (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> col -- | Like zip, but works with 6 collections. zip6 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> col -- | Like zip, but works with 7 collections. zip7 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> col -- | unzip transforms a collection of pairs into a collection of -- first components and a collection of second components. unzip :: (BoxedZippable col, Sequential a, Sequential b, Element col ~ (Element a, Element b)) => col -> (a, b) -- | Like unzip, but works on a collection of 3-element tuples. unzip3 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Element col ~ (Element a, Element b, Element c)) => col -> (a, b, c) -- | Like unzip, but works on a collection of 4-element tuples. unzip4 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Element col ~ (Element a, Element b, Element c, Element d)) => col -> (a, b, c, d) -- | Like unzip, but works on a collection of 5-element tuples. unzip5 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element col ~ (Element a, Element b, Element c, Element d, Element e)) => col -> (a, b, c, d, e) -- | Like unzip, but works on a collection of 6-element tuples. unzip6 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f)) => col -> (a, b, c, d, e, f) -- | Like unzip, but works on a collection of 7-element tuples. unzip7 :: (BoxedZippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => col -> (a, b, c, d, e, f, g) -- | Element type of a collection -- | A monomorphic functor that maps the inner values to values of the same -- type class InnerFunctor c where imap = fmap imap :: InnerFunctor c => (Element c -> Element c) -> c -> c imap :: (InnerFunctor c, Functor f, Element (f a) ~ a, f a ~ c) => (a -> a) -> f a -> f a -- | Give the ability to fold a collection on itself class Foldable collection where foldr' f z0 xs = foldl f' id xs z0 where f' k x z = k $! f x z -- | 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. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is that latter -- does not force the "inner" results (e.g. z f x1 in the above example) -- before applying them to the operator (e.g. to (f x2)). This results in -- a thunk chain O(n) elements long, which then must be evaluated from -- the outside-in. foldl :: Foldable collection => (a -> Element collection -> a) -> a -> collection -> a -- | Left-associative fold of a structure but with strict application of -- the operator. foldl' :: Foldable collection => (a -> Element collection -> a) -> a -> collection -> a -- | Right-associative fold of a structure. -- --
--   foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
--   
foldr :: Foldable collection => (Element collection -> a -> a) -> a -> collection -> a -- | Right-associative fold of a structure, but with strict application of -- the operator. foldr' :: Foldable collection => (Element collection -> a -> a) -> a -> collection -> a -- | A set of methods for ordered colection class (IsList c, Item c ~ Element c, Monoid c) => Sequential c where take n = fst . splitAt n revTake n = fst . revSplitAt n drop n = snd . splitAt n revDrop n = snd . revSplitAt n splitAt n c = (take n c, drop n c) revSplitAt n c = (revTake n c, revDrop n c) break predicate = span (not . predicate) breakElem c = break (== c) intercalate xs xss = mconcatCollection (intersperse xs xss) span predicate = break (not . predicate) -- | Check if a collection is empty null :: Sequential c => c -> Bool -- | Take the first @n elements of a collection take :: Sequential c => Int -> c -> c -- | Take the last @n elements of a collection revTake :: Sequential c => Int -> c -> c -- | Drop the first @n elements of a collection drop :: Sequential c => Int -> c -> c -- | Drop the last @n elements of a collection revDrop :: Sequential c => Int -> c -> c -- | Split the collection at the @n'th elements splitAt :: Sequential c => Int -> c -> (c, c) -- | Split the collection at the @n'th elements from the end revSplitAt :: Sequential c => Int -> c -> (c, c) -- | Split on a specific elements returning a list of colletion splitOn :: Sequential c => (Element c -> Bool) -> c -> [c] -- | Split a collection when the predicate return true break :: Sequential c => (Element c -> Bool) -> c -> (c, c) -- | Split a collection when the predicate return true breakElem :: (Sequential c, Eq (Element c)) => Element c -> 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"
--   
intersperse :: Sequential c => Element c -> c -> c -- | intercalate xs xss is equivalent to -- (mconcat (intersperse xs xss)). It inserts the -- list xs in between the lists in xss and concatenates -- the result. intercalate :: (Sequential c, Monoid (Item c)) => Element c -> c -> Element c -- | Split a collection while the predicate return true span :: Sequential c => (Element c -> Bool) -> c -> (c, c) -- | Filter all the elements that satisfy the predicate filter :: Sequential c => (Element c -> Bool) -> c -> c -- | Reverse a collection reverse :: Sequential c => c -> c -- | Decompose a collection into its first element and the remaining -- collection. If the collection is empty, returns Nothing. uncons :: Sequential c => c -> Maybe (Element c, c) -- | Decompose a collection into a collection without its last element, and -- the last element If the collection is empty, returns Nothing. unsnoc :: Sequential c => c -> Maybe (c, Element c) -- | Prepend an element to an ordered collection snoc :: Sequential c => c -> Element c -> c -- | Append an element to an ordered collection cons :: Sequential c => Element c -> c -> c -- | Find an element in an ordered collection find :: Sequential c => (Element c -> Bool) -> c -> Maybe (Element c) -- | Sort an ordered collection using the specified order function sortBy :: Sequential c => (Element c -> Element c -> Ordering) -> c -> c -- | Length of a collection (number of Element c) length :: Sequential c => c -> Int -- | Create a collection with a single element singleton :: Sequential c => Element c -> c -- | Collection of things that can be made mutable, modified and then -- freezed into an immutable collection class MutableCollection c where type Collection c type MutableKey c type MutableValue c unsafeThaw = thaw unsafeFreeze = freeze where { type family Collection c; type family MutableKey c; type family MutableValue c; } unsafeThaw :: (MutableCollection c, PrimMonad prim) => Collection c -> prim (c (PrimState prim)) unsafeFreeze :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> prim (Collection c) thaw :: (MutableCollection c, PrimMonad prim) => Collection c -> prim (c (PrimState prim)) freeze :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> prim (Collection c) mutUnsafeWrite :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> MutableKey c -> MutableValue c -> prim () mutWrite :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> MutableKey c -> MutableValue c -> prim () mutUnsafeRead :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> MutableKey c -> prim (MutableValue c) mutRead :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> MutableKey c -> prim (MutableValue c) -- | Collection of elements that can indexed by int class IndexedCollection c (!) :: IndexedCollection c => c -> Int -> Maybe (Element c) findIndex :: IndexedCollection c => (Element c -> Bool) -> c -> Maybe Int -- | Collection of things that can be looked up by Key class KeyedCollection c where type Key c type Value c where { type family Key c; type family Value c; } lookup :: KeyedCollection c => Key c -> c -> Maybe (Value c) class Sequential col => Zippable col where zipWith f a b = go f (toList a, toList b) where go f' = maybe mempty (\ (x, xs) -> uncurry2 f' x `cons` go f' xs) . uncons2 zipWith3 f a b c = go f (toList a, toList b, toList c) where go f' = maybe mempty (\ (x, xs) -> uncurry3 f' x `cons` go f' xs) . uncons3 zipWith4 fn a b c d = go fn (toList a, toList b, toList c, toList d) where go f' = maybe mempty (\ (x, xs) -> uncurry4 f' x `cons` go f' xs) . uncons4 zipWith5 fn a b c d e = go fn (toList a, toList b, toList c, toList d, toList e) where go f' = maybe mempty (\ (x, xs) -> uncurry5 f' x `cons` go f' xs) . uncons5 zipWith6 fn a b c d e f = go fn (toList a, toList b, toList c, toList d, toList e, toList f) where go f' = maybe mempty (\ (x, xs) -> uncurry6 f' x `cons` go f' xs) . uncons6 zipWith7 fn a b c d e f g = go fn (toList a, toList b, toList c, toList d, toList e, toList f, toList g) where go f' = maybe mempty (\ (x, xs) -> uncurry7 f' x `cons` go f' xs) . uncons7 -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two collections to -- produce the collection of corresponding sums. zipWith :: (Zippable col, Sequential a, Sequential b) => (Element a -> Element b -> Element col) -> a -> b -> col -- | Like zipWith, but works with 3 collections. zipWith3 :: (Zippable col, Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element col) -> a -> b -> c -> col -- | Like zipWith, but works with 4 collections. zipWith4 :: (Zippable col, Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element col) -> a -> b -> c -> d -> col -- | Like zipWith, but works with 5 collections. zipWith5 :: (Zippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element col) -> a -> b -> c -> d -> e -> col -- | Like zipWith, but works with 6 collections. zipWith6 :: (Zippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element col) -> a -> b -> c -> d -> e -> f -> col -- | Like zipWith, but works with 7 collections. zipWith7 :: (Zippable col, Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element col) -> a -> b -> c -> d -> e -> f -> g -> col -- | Simple Array and Almost-Array-like data structure -- -- Generally accessible in o(1) module Foundation.Array -- | Array of a data Array a -- | Mutable Array of a data MArray a st -- | 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 data UArray ty -- | A Mutable array of types built on top of GHC primitive. -- -- Element in this array can be modified in place. data MUArray ty st data Bitmap data MutableBitmap st -- | 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. class Eq ty => PrimType ty -- | Exception during an operation accessing the vector out of bound -- -- Represent the type of operation, the index accessed, and the total -- length of the vector. data OutOfBound -- | Opaque packed String encoded in UTF8. -- -- The type is an instance of IsString and IsList, which allow -- OverloadedStrings for string literal, and fromList to convert -- a [Char] (Prelude String) to a packed representation -- --
--   {-# LANGUAGE OverloadedStrings #-}
--   s = "Hello World :: String
--   
-- --
--   s = fromList ("Hello World" :: Prelude.String) :: String
--   
-- -- Each unicode code point is represented by a variable encoding of 1 to -- 4 bytes, -- -- For more information about UTF8: -- https://en.wikipedia.org/wiki/UTF-8 module Foundation.String -- | Opaque packed array of characters in the UTF8 encoding data String data Encoding ASCII7 :: Encoding UTF8 :: Encoding UTF16 :: Encoding UTF32 :: Encoding ISO_8859_1 :: Encoding fromBytes :: Encoding -> UArray Word8 -> (String, Maybe ValidationFailure, UArray Word8) fromBytesLenient :: UArray Word8 -> (String, UArray Word8) -- | Convert a Byte Array directly to a string without checking for UTF8 -- validity fromBytesUnsafe :: UArray Word8 -> String -- | Convert a String to a bytearray toBytes :: Encoding -> String -> UArray Word8 data ValidationFailure InvalidHeader :: ValidationFailure InvalidContinuation :: ValidationFailure MissingByte :: ValidationFailure lines :: String -> [String] words :: String -> [String] -- | # Opaque implementation for FilePath -- -- The underlying type of a FilePath is a ByteArray. It is indeed -- like this because for some systems (Unix systems) a FilePath is -- a null terminated array of bytes. -- -- # FilePath and FileName for type checking validation -- -- In order to add some constraint at compile time, it is not possible to -- append (</>) a FilePath to another -- FilePath. You can only append (</>) a -- FileName to a given FilePath. module Foundation.VFS.FilePath -- | FilePath is a collection of FileName -- -- TODO: Eq and Ord are implemented using Show This is not very efficient -- and would need to be improved Also, it is possible the ordering is not -- necessary what we want in this case. -- -- A FilePath is one of the following: -- -- data FilePath -- | information about type of FilePath -- -- A file path being only Relative or Absolute. data Relativity Absolute :: Relativity Relative :: Relativity -- | A filename (or path entity) in the FilePath -- -- data FileName filePathToString :: FilePath -> String -- | conversion of a FilePath into a list of Char -- -- this function may throw exceptions filePathToLString :: FilePath -> [Char] -- | build a file path from a given list of filename -- -- this is unsafe and is mainly needed for testing purpose unsafeFilePath :: Relativity -> [FileName] -> FilePath -- | build a file name from a given ByteArray -- -- this is unsafe and is mainly needed for testing purpose unsafeFileName :: UArray Word8 -> FileName extension :: FileName -> Maybe FileName instance GHC.Show.Show Foundation.VFS.FilePath.FileName_Invalid instance GHC.Classes.Eq Foundation.VFS.FilePath.FileName instance GHC.Show.Show Foundation.VFS.FilePath.FilePath_Invalid instance GHC.Show.Show Foundation.VFS.FilePath.Relativity instance GHC.Classes.Eq Foundation.VFS.FilePath.Relativity instance GHC.Show.Show Foundation.VFS.FilePath.FilePath instance GHC.Classes.Eq Foundation.VFS.FilePath.FilePath instance GHC.Classes.Ord Foundation.VFS.FilePath.FilePath instance GHC.Exception.Exception Foundation.VFS.FilePath.FilePath_Invalid instance Data.String.IsString Foundation.VFS.FilePath.FilePath instance GHC.Exception.Exception Foundation.VFS.FilePath.FileName_Invalid instance GHC.Show.Show Foundation.VFS.FilePath.FileName instance Data.String.IsString Foundation.VFS.FilePath.FileName instance GHC.Base.Monoid Foundation.VFS.FilePath.FileName instance Foundation.VFS.Path.Path Foundation.VFS.FilePath.FilePath module Foundation.VFS -- | Path type class -- -- defines the Path associated types and basic functions to implement -- related to the path manipulation -- -- # TODO, add missing enhancement: -- -- ``` splitExtension :: PathEnt path -> (PathEnt path, PathEnt path) -- addExtension :: PathEnt path -> PathEnt path -> PathEnt path -- (.) :: path -> PathEnt path -> path (-.) :: path -- -> PathEnt path -> path ``` class Path path where type PathEnt path type PathPrefix path type PathSuffix path where { type family PathEnt path; type family PathPrefix path; type family PathSuffix path; } -- | join a path entity to a given path () :: Path path => path -> PathEnt path -> path -- | split the path into the associated elements splitPath :: Path path => path -> (PathPrefix path, [PathEnt path], PathSuffix path) -- | build the path from the associated elements buildPath :: Path path => (PathPrefix path, [PathEnt path], PathSuffix path) -> path -- | get the filename of the given path -- -- If there is no filename, you will receive the mempty of the PathEnt filename :: (Path path, Monoid (PathEnt path)) => path -> PathEnt path -- | parent is only going to drop the filename. -- -- if you actually want to reference to the parent directory, simply -- uses: -- -- ``` parent "." = "." <> ".." ``` parent :: Path path => path -> path -- | get the path prefix information -- -- ``` prefix "hometab" == () ``` -- -- or for URI (TODO, not yet accurate) -- -- ``` prefix "http://github.com/vincenthz/hs-foundation?w=1" == -- URISchema http Nothing Nothing "github.com" Nothing ``` prefix :: Path path => path -> PathPrefix path -- | get the path suffix information -- -- ``` suffix "hometab" == () ``` -- -- or for URI (TODO, not yet accurate) -- -- ``` suffix "http://github.com/vincenthz/hs-foundation?w=1" == -- URISuffix (["w", "1"], Nothing) ``` suffix :: Path path => path -> PathSuffix path -- | FilePath is a collection of FileName -- -- TODO: Eq and Ord are implemented using Show This is not very efficient -- and would need to be improved Also, it is possible the ordering is not -- necessary what we want in this case. -- -- A FilePath is one of the following: -- -- data FilePath -- | A filename (or path entity) in the FilePath -- -- data FileName filePathToString :: FilePath -> String -- | conversion of a FilePath into a list of Char -- -- this function may throw exceptions filePathToLString :: FilePath -> [Char] -- | IO Routine module Foundation.IO -- | Print a string with a newline to standard output putStrLn :: String -> IO () -- | Print a string to standard output putStr :: String -> IO () -- | See openFile data IOMode :: * ReadMode :: IOMode WriteMode :: IOMode AppendMode :: IOMode ReadWriteMode :: IOMode -- | list the file name in the given FilePath directory -- -- TODO: error management and not implemented yet getDirectory :: -- FilePath -> IO [FileName] getDirectory = undefined -- -- Open a new handle on the file openFile :: FilePath -> IOMode -> IO Handle -- | Close a handle closeFile :: Handle -> IO () -- | withFile filepath mode act opens a file using the -- mode and run act. the by-product handle will be closed when -- act finish, either normally or through an exception. -- -- The value returned is the result of act@ withFile :: FilePath -> IOMode -> (Handle -> IO r) -> IO r -- | Read binary data directly from the specified Handle. -- -- First argument is the Handle to read from, and the second is the -- number of bytes to read. It returns the bytes read, up to the -- specified size, or an empty array if EOF has been reached. -- -- hGet is implemented in terms of hGetBuf. hGet :: Handle -> Int -> IO (UArray Word8) -- | Read a binary file and return the whole content in one contiguous -- buffer. readFile :: FilePath -> IO (UArray Word8) -- | Fold over chunks file calling the callback function for each chunks -- read from the file, until the end of file. foldTextFile :: (String -> a -> IO a) -> a -> FilePath -> IO a -- | Note that the memory mapping is handled by the system, not at the -- haskell level. The system can modify the content of the memory as any -- moment under your feet. -- -- It also have the limitation of your system, no emulation or nice -- handling of all those corners cases is attempted here. -- -- for example mapping a large file (> 4G), on a 32 bits system is -- likely to just fail or returns inconsistent result. -- -- In doubt, use readFile or other simple routine that brings -- the content of the file in IO. module Foundation.IO.FileMap -- | Map in memory the whole content of a file. -- -- Once the array goes out of scope, the memory get (eventually) unmap fileMapRead :: FilePath -> IO (UArray Word8) -- | Map in memory the whole content of a file, fileMapReadWith :: FilePath -> (UArray Word8 -> IO a) -> IO a module Foundation.System.Info data OS Windows :: OS OSX :: OS Linux :: OS Android :: OS BSD :: OS -- | get the operating system on which the program is running. -- -- Either return the known OS or a strict String of the OS -- name. -- -- This function uses the base's os function. os :: Either String OS -- | get the machine architecture on which the program is running -- -- Either return the known architecture or a Strict String of the -- architecture name. -- -- This function uses the base's arch function. arch :: Either String Arch -- | returns the number of CPUs the machine has cpus :: IO Int data Endianness LittleEndian :: Endianness BigEndian :: Endianness -- | endianness of the current architecture endianness :: Endianness -- | get the compiler name -- -- get the compilerName from base package but convert it into a strict -- String compilerName :: String -- | The version of compilerName with which the program was compiled -- or is being interpreted. compilerVersion :: Version -- | A Version represents the version of a software entity. -- -- An instance of Eq is provided, which implements exact equality -- modulo reordering of the tags in the versionTags field. -- -- An instance of Ord is also provided, which gives lexicographic -- ordering on the versionBranch fields (i.e. 2.1 > 2.0, 1.2.3 -- > 1.2.2, etc.). This is expected to be sufficient for many uses, -- but note that you may need to use a more specific ordering for your -- versioning scheme. For example, some versioning schemes may include -- pre-releases which have tags "pre1", "pre2", and so -- on, and these would need to be taken into account when determining -- ordering. In some cases, date ordering may be more appropriate, so the -- application would have to look for date tags in the -- versionTags field and compare those. The bottom line is, don't -- always assume that compare and other Ord operations are -- the right thing for every Version. -- -- Similarly, concrete representations of versions may differ. One -- possible concrete representation is provided (see showVersion -- and parseVersion), but depending on the application a different -- concrete representation may be more appropriate. data Version :: * Version :: [Int] -> [String] -> Version -- | The numeric branch for this version. This reflects the fact that most -- software versions are tree-structured; there is a main trunk which is -- tagged with versions at various points (1,2,3...), and the first -- branch off the trunk after version 3 is 3.1, the second branch off the -- trunk after version 3 is 3.2, and so on. The tree can be branched -- arbitrarily, just by adding more digits. -- -- We represent the branch as a list of Int, so version 3.2.1 -- becomes [3,2,1]. Lexicographic ordering (i.e. the default instance of -- Ord for [Int]) gives the natural ordering of branches. [versionBranch] :: Version -> [Int] -- | A version can be tagged with an arbitrary list of strings. The -- interpretation of the list of tags is entirely dependent on the entity -- that this version applies to. [versionTags] :: Version -> [String] instance GHC.Show.Show Foundation.System.Info.Endianness instance GHC.Classes.Eq Foundation.System.Info.Endianness instance Data.Data.Data Foundation.System.Info.Arch instance GHC.Enum.Bounded Foundation.System.Info.Arch instance GHC.Enum.Enum Foundation.System.Info.Arch instance GHC.Classes.Ord Foundation.System.Info.Arch instance GHC.Classes.Eq Foundation.System.Info.Arch instance GHC.Show.Show Foundation.System.Info.Arch instance Data.Data.Data Foundation.System.Info.OS instance GHC.Enum.Bounded Foundation.System.Info.OS instance GHC.Enum.Enum Foundation.System.Info.OS instance GHC.Classes.Ord Foundation.System.Info.OS instance GHC.Classes.Eq Foundation.System.Info.OS instance GHC.Show.Show Foundation.System.Info.OS -- | I tried to picture clusters of information As they moved through the -- computer What do they look like? -- -- Alternative Prelude module Foundation -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ 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 map -- ($ 0) xs, or 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. ($!) :: (a -> b) -> a -> b infixr 0 $! -- | Boolean "and" (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or" (||) :: Bool -> Bool -> Bool infixr 2 || -- | morphism composition (.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c -- | Boolean "not" not :: Bool -> Bool -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | Strict tuple (a,b) data Tuple2 a b Tuple2 :: !a -> !b -> Tuple2 a b -- | Strict tuple (a,b,c) data Tuple3 a b c Tuple3 :: !a -> !b -> !c -> Tuple3 a b c -- | Strict tuple (a,b,c,d) data Tuple4 a b c d Tuple4 :: !a -> !b -> !c -> !d -> Tuple4 a b c d -- | Class of product types that have a first element class Fstable a where type FstTy a where { type family FstTy a; } fst :: Fstable a => a -> FstTy a -- | Class of product types that have a second element class Sndable a where type SndTy a where { type family SndTy a; } snd :: Sndable a => a -> SndTy a -- | Class of product types that have a third element class Thdable a where type ThdTy a where { type family ThdTy a; } thd :: Thdable a => a -> ThdTy a -- | the identity morphism id :: Category k cat => forall (a :: k). cat a a -- | 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
--   ""
--   
maybe :: b -> (a -> b) -> Maybe a -> b -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the 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
--   
either :: (a -> c) -> (b -> c) -> Either a b -> c -- | flip f takes its (first) two arguments in the reverse -- order of f. flip :: (a -> b -> c) -> b -> a -> c -- | const x is a unary function which evaluates to x for -- all inputs. -- -- For instance, -- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | error stops execution and displays an error message. error :: HasCallStack => [Char] -> a -- | Print a string to standard output putStr :: String -> IO () -- | Print a string with a newline to standard output putStrLn :: String -> IO () -- | Returns a list of the program's command line arguments (not including -- the program name). getArgs :: IO [String] -- | uncurry converts a curried function to a function on pairs. uncurry :: (a -> b -> c) -> (a, b) -> c -- | curry converts an uncurried function to a curried function. curry :: ((a, b) -> c) -> a -> b -> c -- | Swap the components of a pair. swap :: (a, b) -> (b, a) -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | asTypeOf 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 -- second. asTypeOf :: a -> a -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: HasCallStack => a -- | 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. seq :: a -> b -> b -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- 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, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: [a] -> ShowS -- | 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. class Eq a => Ord a compare :: a -> a -> Ordering (<) :: a -> a -> Bool (<=) :: a -> a -> Bool (>) :: a -> a -> Bool (>=) :: a -> a -> Bool max :: a -> a -> a min :: a -> a -> a -- | The Eq class defines equality (==) and inequality -- (/=). All the basic datatypes exported by the Prelude -- are instances of Eq, and Eq may be derived for any -- datatype whose constituents are also instances of Eq. -- -- Minimal complete definition: either == or /=. class Eq a (==) :: a -> a -> Bool (/=) :: a -> a -> Bool -- | 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. class Bounded a minBound :: a maxBound :: a -- | 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: -- -- -- --
--   enumFrom     x   = enumFromTo     x maxBound
--   enumFromThen x y = enumFromThenTo x y bound
--     where
--       bound | fromEnum y >= fromEnum x = maxBound
--             | otherwise                = minBound
--   
class Enum a -- | the successor of a value. For numeric types, succ adds 1. succ :: a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: a -> a -- | Convert from an Int. toEnum :: Int -> a -- | 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. fromEnum :: a -> Int -- | Used in Haskell's translation of [n..]. enumFrom :: a -> [a] -- | Used in Haskell's translation of [n,n'..]. enumFromThen :: a -> a -> [a] -- | Used in Haskell's translation of [n..m]. enumFromTo :: a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m]. enumFromThenTo :: a -> a -> a -> [a] -- | 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. class Functor (f :: * -> *) fmap :: (a -> b) -> f a -> f b -- | Replace all locations in the input with the same value. The default -- definition is fmap . const, but this may be -- overridden with a more efficient version. (<$) :: a -> f b -> f a -- | A functor with application, providing operations to -- -- -- -- A minimal complete definition must include implementations of these -- functions satisfying the following laws: -- -- -- -- 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). class Functor f => Applicative (f :: * -> *) -- | Lift a value. pure :: a -> f a -- | Sequential application. (<*>) :: f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. (*>) :: f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. (<*) :: f a -> f b -> f a -- | 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. class Applicative m => Monad (m :: * -> *) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: m a -> m b -> m b -- | Inject a value into the monadic type. return :: a -> m a -- | 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. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: String -> m a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: String -> a -- | The IsList class and its methods are intended to be used in -- conjunction with the OverloadedLists extension. class IsList l where type Item l :: * where { type family Item l :: *; } -- | The fromList function constructs the structure l from -- the given list of Item l fromList :: [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. fromListN :: Int -> [Item l] -> l -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: l -> [Item l] -- | Number literals, convertible through the generic Integer type. -- -- all number are Enum'erable, meaning that you can move to next element class (Eq a, Ord a, Num a, Enum a, Additive a, Subtractive a, Difference a ~ a, Multiplicative a, Divisible a) => Number a toInteger :: Number a => a -> Integer -- | Number literals that can be negative class Number a => Signed a abs :: Signed a => a -> a signum :: Signed a => a -> Sign -- | Represent class of things that can be added together, contains a -- neutral element and is commutative. -- -- class Additive a where scale 0 _ = azero scale 1 a = a scale 2 a = a + a scale n a | n < 0 = error "cannot scale by negative number" | otherwise = a + scale (pred n) a azero :: Additive a => a (+) :: Additive a => a -> a -> a scale :: (Additive a, Number n) => n -> a -> a scale :: (Additive a, Number n) => n -> a -> a -- | 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: e.g. (-) :: Int -> Int -> Int (-) :: DateTime -> -- DateTime -> Seconds (-) :: Ptr a -> Ptr a -> PtrDiff class Subtractive a where type Difference a where { type family Difference a; } (-) :: Subtractive a => a -> a -> Difference a -- | Represent class of things that can be multiplied together -- -- class Multiplicative a where (^) = power -- | Identity element over multiplication midentity :: Multiplicative a => a -- | Multiplication of 2 elements that result in another element (*) :: Multiplicative a => a -> a -> a -- | Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a -- ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (Multiplicative a, Number n) => a -> n -> a -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a :: * -> * Nothing :: Maybe a Just :: a -> Maybe a data Ordering :: * LT :: Ordering EQ :: Ordering GT :: Ordering data Bool :: * False :: Bool True :: Bool -- | 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). data Char :: * -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- 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. data IO a :: * -> * -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> 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 Ints. -- --
--   >>> :{
--       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"
--   
data Either a b :: * -> * -> * Left :: a -> Either a b Right :: b -> Either a b -- | 8-bit signed integer type data Int8 :: * -- | 16-bit signed integer type data Int16 :: * -- | 32-bit signed integer type data Int32 :: * -- | 64-bit signed integer type data Int64 :: * -- | 8-bit unsigned integer type data Word8 :: * -- | 16-bit unsigned integer type data Word16 :: * -- | 32-bit unsigned integer type data Word32 :: * -- | 64-bit unsigned integer type data Word64 :: * -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * -- | A fixed-precision integer type with at least the range [-2^29 .. -- 2^29-1]. The exact range for a given implementation can be -- determined by using minBound and maxBound from the -- Bounded class. data Int :: * -- | Invariant: Jn# and Jp# are used iff value doesn't fit in -- S# -- -- Useful properties resulting from the invariants: -- -- data Integer :: * -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | 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. data Float :: * -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double :: * -- | 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 data UArray 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. class Eq ty => PrimType ty -- | Array of a data Array a -- | Opaque packed array of characters in the UTF8 encoding data String -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- -- -- -- 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 -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. class Monoid a -- | Identity of mappend mempty :: a -- | An associative operation mappend :: a -> 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. mconcat :: [a] -> a -- | An infix synonym for mappend. (<>) :: Monoid m => m -> m -> m infixr 6 <> -- | Data structures that can be folded. -- -- For example, given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Foldable Tree where
--      foldMap f Empty = mempty
--      foldMap f (Leaf x) = f x
--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
--   
-- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
--   instance Foldable Tree where
--      foldr f z Empty = z
--      foldr f z (Leaf x) = f x z
--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable (t :: * -> *) -- | The sum of a collection of actions, generalizing concat. asum :: (Foldable t, Alternative f) => t (f a) -> f a -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Traversable Tree where
--      traverse f Empty = pure Empty
--      traverse f (Leaf x) = Leaf <$> f x
--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
--   
-- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- -- class (Functor t, Foldable t) => Traversable (t :: * -> *) -- | The mapMaybe function is a version of map which can -- throw out elements. In particular, the functional argument returns -- something of type Maybe b. If this is Nothing, -- no element is added on to the result list. If it is Just -- b, then b is included in the result list. -- --

Examples

-- -- Using mapMaybe f x is a shortcut for -- catMaybes $ map f x in most cases: -- --
--   >>> 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]
--   
mapMaybe :: (a -> Maybe b) -> [a] -> [b] -- | The catMaybes function takes a list of Maybes 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]
--   
catMaybes :: [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
--   
fromMaybe :: a -> Maybe a -> a -- | The isJust function returns True iff its argument is of -- the form Just _. -- --

Examples

-- -- Basic usage: -- --
--   >>> isJust (Just 3)
--   True
--   
-- --
--   >>> isJust (Just ())
--   True
--   
-- --
--   >>> isJust Nothing
--   False
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isJust (Just Nothing)
--   True
--   
isJust :: Maybe a -> Bool -- | The isNothing function returns True iff its argument is -- Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> isNothing (Just 3)
--   False
--   
-- --
--   >>> isNothing (Just ())
--   False
--   
-- --
--   >>> isNothing Nothing
--   True
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isNothing (Just Nothing)
--   False
--   
isNothing :: Maybe a -> Bool -- | The listToMaybe function returns Nothing on an empty -- list or Just a where a 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]
--   
listToMaybe :: [a] -> Maybe 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
--   
maybeToList :: Maybe a -> [a] -- | 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 partitionEithers x should be the -- same pair as (lefts x, rights x): -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list == (lefts list, rights list)
--   True
--   
partitionEithers :: [Either a b] -> ([a], [b]) -- | Extracts from a list of Either all the Left elements. -- All the Left elements are extracted in order. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> lefts list
--   ["foo","bar","baz"]
--   
lefts :: [Either a b] -> [a] -- | Extracts from a list of Either all the Right elements. -- All the Right elements are extracted in order. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> rights list
--   [3,7]
--   
rights :: [Either a b] -> [b] -- | (*) `on` f = \x y -> f x * f y. -- -- Typical usage: sortBy (compare `on` -- fst). -- -- Algebraic properties: -- -- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 `on` -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an 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)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | An associative binary operation (<|>) :: Alternative f => forall a. f a -> f a -> f a -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> -- | 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 MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
--   *** Exception: MismatchedParentheses
--   
class (Typeable * e, Show e) => Exception e toException :: e -> SomeException fromException :: SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: e -> String -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable k (a :: k) -- | 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. data SomeException :: * -- | 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. data IOException :: * -- | A concrete, poly-kinded proxy type data Proxy k (t :: k) :: forall k. k -> * Proxy :: Proxy k -- | 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. asProxyTypeOf :: a -> Proxy * a -> a -- | Partialiality wrapper. data Partial a -- | Create a value that is partial. this can only be unwrap using the -- fromPartial function partial :: a -> Partial a -- | An error related to the evaluation of a Partial value that failed. -- -- it contains the name of the function and the reason for failure data PartialError -- | Dewrap a possible partial value fromPartial :: Partial a -> a -- | Alias to Prelude String ([Char]) for compatibility purpose type LString = String