-- 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: -- --
-- x + azero = x -- azero + x = x -- x + y = y + x --class Additive a where scale 0 _ = azero scale 1 a = a scale 2 a = a + a scale n a = a + scale (pred n) a azero :: Additive a => a (+) :: Additive a => a -> a -> a scale :: (Additive a, IsNatural 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: -- --
-- (-) :: Int -> Int -> Int -- (-) :: DateTime -> DateTime -> Seconds -- (-) :: Ptr a -> Ptr a -> PtrDiff -- (-) :: Natural -> Natural -> Maybe Natural --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 -- --
-- x * midentity = x -- midentity * x = x --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) .. (^) :: (IsNatural n) => a -> n -> -- a (^) :: (Multiplicative a, IsNatural n, IDivisible n) => a -> n -> a -- | Represent types that supports an euclidian division -- --
-- (x ‘div‘ y) * y + (x ‘mod‘ y) == x --class (Additive a, Multiplicative a) => IDivisible 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 :: IDivisible a => a -> a -> a mod :: IDivisible a => a -> a -> a divMod :: IDivisible a => a -> a -> (a, a) -- | Support for division between same types -- -- This is likely to change to represent specific mathematic divisions class Multiplicative a => Divisible a (/) :: Divisible a => a -> a -> a -- | Sign of a signed number data Sign SignNegative :: Sign SignZero :: Sign SignPositive :: Sign recip :: Divisible a => a -> a class IntegralRounding a -- | Round up, to the next integral. -- -- Also known as ceiling roundUp :: (IntegralRounding a, Integral n) => a -> n -- | Round down, to the previous integral -- -- Also known as floor roundDown :: (IntegralRounding a, Integral n) => a -> n -- | Truncate to the closest integral to the fractional number closer to 0. -- -- This is equivalent to roundUp for negative Number and roundDown for -- positive Number roundTruncate :: (IntegralRounding a, Integral n) => a -> n -- | Round to the nearest integral -- --
-- roundNearest 3.6 ---- -- 4 > roundNearest 3.4 3 roundNearest :: (IntegralRounding a, Integral n) => a -> n -- | IEEE754 Floating Point class FloatingPoint a floatRadix :: FloatingPoint a => Proxy a -> Integer floatDigits :: FloatingPoint a => Proxy a -> Int floatRange :: FloatingPoint a => Proxy a -> (Int, Int) floatDecode :: FloatingPoint a => a -> (Integer, Int) floatEncode :: FloatingPoint a => Integer -> Int -> a instance GHC.Classes.Eq Foundation.Numerical.Sign instance Foundation.Numerical.Signed GHC.Integer.Type.Integer instance Foundation.Numerical.Signed GHC.Types.Int instance Foundation.Numerical.Signed GHC.Int.Int8 instance Foundation.Numerical.Signed GHC.Int.Int16 instance Foundation.Numerical.Signed GHC.Int.Int32 instance Foundation.Numerical.Signed GHC.Int.Int64 instance Foundation.Numerical.Signed GHC.Types.Float instance Foundation.Numerical.Signed GHC.Types.Double instance Foundation.Numerical.IntegralRounding GHC.Real.Rational instance Foundation.Numerical.IntegralRounding GHC.Types.Double instance Foundation.Numerical.IntegralRounding GHC.Types.Float module Foundation.Primitive.Nat -- | (Kind) This is the kind of type-level natural numbers. data Nat :: * -- | This class gives the integer associated with a type-level natural. -- There are instances of the class for every concrete literal: 0, 1, 2, -- etc. class KnownNat (n :: Nat) natVal :: KnownNat n => proxy n -> Integer -- | Comparison of type-level naturals, as a constraint. type (<=) (x :: Nat) (y :: Nat) = (~) Bool ((<=?) x y) True -- | Comparison of type-level naturals, as a function. NOTE: The -- functionality for this function should be subsumed by CmpNat, -- so this might go away in the future. Please let us know, if you -- encounter discrepancies between the two. -- | Addition of type-level naturals. -- | Multiplication of type-level naturals. -- | Exponentiation of type-level naturals. -- | Subtraction of type-level naturals. -- | Comparison of type-level naturals, as a function. natValInt :: forall n proxy. (KnownNat n, NatWithinBound Int n) => proxy n -> Int natValInt8 :: forall n proxy. (KnownNat n, NatWithinBound Int8 n) => proxy n -> Int8 natValInt16 :: forall n proxy. (KnownNat n, NatWithinBound Int16 n) => proxy n -> Int16 natValInt32 :: forall n proxy. (KnownNat n, NatWithinBound Int32 n) => proxy n -> Int32 natValInt64 :: forall n proxy. (KnownNat n, NatWithinBound Int64 n) => proxy n -> Int64 natValWord :: forall n proxy. (KnownNat n, NatWithinBound Word n) => proxy n -> Word natValWord8 :: forall n proxy. (KnownNat n, NatWithinBound Word8 n) => proxy n -> Word8 natValWord16 :: forall n proxy. (KnownNat n, NatWithinBound Word16 n) => proxy n -> Word16 natValWord32 :: forall n proxy. (KnownNat n, NatWithinBound Word32 n) => proxy n -> Word32 natValWord64 :: forall n proxy. (KnownNat n, NatWithinBound Word64 n) => proxy n -> Word64 -- | Get Maximum bounds of different Integral / Natural types related to -- Nat -- | Check if a Nat is in bounds of another integral / natural types -- | Constraint to check if a natural is within a specific bounds of a -- type. -- -- i.e. given a Nat n, is it possible to convert it to -- ty without losing information -- | A Nat-sized list abstraction -- -- Using this module is limited to GHC 7.10 and above. module Foundation.List.SList data SList (n :: Nat) a toSList :: forall (n :: Nat) a. (KnownNat n, NatWithinBound Int n) => [a] -> Maybe (SList n a) unSList :: SList n a -> [a] length :: forall a (n :: Nat). (KnownNat n, NatWithinBound Int n) => SList n a -> Int create :: forall a (n :: Nat). KnownNat n => (Integer -> a) -> SList n a createFrom :: forall a (n :: Nat) (start :: Nat). (KnownNat n, KnownNat start) => Proxy start -> (Integer -> a) -> SList n a empty :: SList 0 a singleton :: a -> SList 1 a uncons :: CmpNat n 0 ~ GT => SList n a -> (a, SList (n - 1) a) cons :: a -> SList n a -> SList (n + 1) a map :: (a -> b) -> SList n a -> SList n b elem :: Eq a => a -> SList n a -> Bool foldl :: (b -> a -> b) -> b -> SList n a -> b append :: SList n a -> SList m a -> SList (n + m) a minimum :: (Ord a, CmpNat n 0 ~ GT) => SList n a -> a maximum :: (Ord a, CmpNat n 0 ~ GT) => SList n a -> a head :: CmpNat n 0 ~ GT => SList n a -> a tail :: CmpNat n 0 ~ GT => SList n a -> SList (n - 1) a take :: forall a (m :: Nat) (n :: Nat). (KnownNat m, NatWithinBound Int m, m <= n) => SList n a -> SList m a drop :: forall a d (m :: Nat) (n :: Nat). (KnownNat d, NatWithinBound Int d, (n - m) ~ d, m <= n) => SList n a -> SList m a zip :: SList n a -> SList n b -> SList n (a, b) zip3 :: SList n a -> SList n b -> SList n c -> SList n (a, b, c) zip4 :: SList n a -> SList n b -> SList n c -> SList n d -> SList n (a, b, c, d) zip5 :: SList n a -> SList n b -> SList n c -> SList n d -> SList n e -> SList n (a, b, c, d, e) zipWith :: (a -> b -> x) -> SList n a -> SList n b -> SList n x zipWith3 :: (a -> b -> c -> x) -> SList n a -> SList n b -> SList n c -> SList n x zipWith4 :: (a -> b -> c -> d -> x) -> SList n a -> SList n b -> SList n c -> SList n d -> SList n x zipWith5 :: (a -> b -> c -> d -> e -> x) -> SList n a -> SList n b -> SList n c -> SList n d -> SList n e -> SList n x replicateM :: forall (n :: Nat) m a. (n <= 1048576, Monad m, KnownNat n) => m a -> m (SList n a) -- | A block of memory that contains elements of a type, very similar to an -- unboxed array but with the key difference: -- --
-- 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 ("foo.hs" :: FilePath) -- . ---- --
-- >>> parent ("foo/bar/baz.hs" :: FilePath) -- foo/bar --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 ("foo.hs" :: FilePath) -- foo.hs ---- --
-- >>> filename ("foo/bar/baz.hs" :: FilePath) -- baz.hs --filename :: (Path path, Monoid (PathEnt path)) => path -> PathEnt path -- | get the path prefix information -- --
-- >>> prefix ("/home/tab" :: FilePath) -- Absolute ---- --
-- >>> prefix ("home/tab" :: FilePath) -- Relative ---- -- 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 ("/home/tab" :: FilePath) -- () ---- -- 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 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 -- | 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. module Foundation.Class.Bifunctor -- | 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 i -- first (f . g) ≡ first f . first g -- second (f . g) ≡ second f . second g --class Bifunctor (p :: * -> * -> *) -- | Map over both arguments at the same time. -- --
-- bimap f g ≡ first f . second g --bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d -- | Map covariantly over the first argument. -- --
-- first f ≡ bimap f id --first :: Bifunctor p => (a -> b) -> p a c -> p b c -- | Map covariantly over the second argument. -- --
-- second ≡ bimap id --second :: Bifunctor p => (b -> c) -> p a b -> p a c -- | 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 primBaUIndex :: PrimType ty => ByteArray# -> Offset ty -> ty -- | Read an element at an index in a mutable array primMbaURead :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty -- | Write an element to a specific cell in a mutable array. primMbaUWrite :: (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, Applicative 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 () -- | Class of types that can be byte-swapped. -- -- e.g. Word16, Word32, Word64 class ByteSwap a -- | Little Endian value newtype LE a LE :: a -> LE a [unLE] :: LE a -> a -- | Convert a value in cpu endianess to little endian toLE :: ByteSwap a => a -> LE a -- | Convert from a little endian value to the cpu endianness fromLE :: ByteSwap a => LE a -> a -- | Big Endian value newtype BE a BE :: a -> BE a [unBE] :: BE a -> a -- | Convert a value in cpu endianess to big endian toBE :: ByteSwap a => a -> BE a -- | Convert from a big endian value to the cpu endianness fromBE :: ByteSwap a => BE a -> a -- | Upsize an integral value -- -- The destination type b size need to be greater or equal than -- the size type of a class IntegralUpsize a b integralUpsize :: IntegralUpsize a b => a -> b -- | Downsize an integral value class IntegralDownsize a b where integralDownsize = id integralDownsize :: IntegralDownsize a b => a -> b integralDownsize :: (IntegralDownsize a b, a ~ b) => a -> b integralDownsizeCheck :: IntegralDownsize a b => a -> Maybe b -- | Cast an integral value to another value that have the same -- representional size class IntegralCast a b where integralCast = id integralCast :: IntegralCast a b => a -> b integralCast :: (IntegralCast a b, a ~ b) => a -> b -- | Data that can be fully evaluated in Normal Form class NormalForm a toNormalForm :: NormalForm a => a -> () force :: NormalForm a => a -> a deepseq :: NormalForm a => a -> b -> b -- | Either a or b or both. data These a b This :: a -> These a b That :: b -> These a b These :: a -> b -> These a b -- | A block of memory containing unpacked bytes representing values of -- type ty data Block ty -- | A Mutable block of memory containing unpacked bytes representing -- values of type ty data MutableBlock ty st -- | a Generalized version of Fstable, Sndable, .. -- -- Using this module is limited to GHC 7.10 and above. module Foundation.Tuple.Nth -- | A generalized version of indexed accessor allowing access to tuples -- n'th element. -- -- Indexing starts at 1, as fst is used to get first element. class KnownNat n => Nthable n a where type NthTy n a where { type family NthTy n a; } nth :: Nthable n a => proxy n -> a -> NthTy n a instance Foundation.Tuple.Nth.Nthable 1 (a, b) instance Foundation.Tuple.Nth.Nthable 2 (a, b) instance Foundation.Tuple.Nth.Nthable 1 (Foundation.Tuple.Tuple2 a b) instance Foundation.Tuple.Nth.Nthable 2 (Foundation.Tuple.Tuple2 a b) instance Foundation.Tuple.Nth.Nthable 1 (a, b, c) instance Foundation.Tuple.Nth.Nthable 2 (a, b, c) instance Foundation.Tuple.Nth.Nthable 3 (a, b, c) instance Foundation.Tuple.Nth.Nthable 1 (Foundation.Tuple.Tuple3 a b c) instance Foundation.Tuple.Nth.Nthable 2 (Foundation.Tuple.Tuple3 a b c) instance Foundation.Tuple.Nth.Nthable 3 (Foundation.Tuple.Tuple3 a b c) instance Foundation.Tuple.Nth.Nthable 1 (a, b, c, d) instance Foundation.Tuple.Nth.Nthable 2 (a, b, c, d) instance Foundation.Tuple.Nth.Nthable 3 (a, b, c, d) instance Foundation.Tuple.Nth.Nthable 4 (a, b, c, d) instance Foundation.Tuple.Nth.Nthable 1 (Foundation.Tuple.Tuple4 a b c d) instance Foundation.Tuple.Nth.Nthable 2 (Foundation.Tuple.Tuple4 a b c d) instance Foundation.Tuple.Nth.Nthable 3 (Foundation.Tuple.Tuple4 a b c d) instance Foundation.Tuple.Nth.Nthable 4 (Foundation.Tuple.Tuple4 a b c d) module Foundation.Bits -- | Unsafe Shift Left Operator (.<<.) :: Bits a => a -> Int -> a -- | Unsafe Shift Right Operator (.>>.) :: Bits a => a -> Int -> a -- | The Bits class defines bitwise operations over integral types. -- --
clearBit zeroBits n == -- zeroBits
setBit zeroBits n == bit -- n
testBit zeroBits n == False
popCount zeroBits == 0
-- alignRoundDown 15 8 = 8 -- alignRoundDown 8 8 = 8 --alignRoundDown :: Int -> Int -> Int 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 -> CountOf ty -> UArray ty mutableForeignMem :: (PrimMonad prim, PrimType ty) => FinalPtr ty -> Int -> prim (MUArray ty (PrimState prim)) -- | 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 -- | Various String Encoding that can be use to convert to and from bytes data Encoding ASCII7 :: Encoding UTF8 :: Encoding UTF16 :: Encoding UTF32 :: Encoding ISO_8859_1 :: Encoding -- | Convert a ByteArray to a string assuming a specific encoding. -- -- It returns a 3-tuple of: -- --
-- words "Hello Foundation" ---- --
-- 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 -- | Functors representing data structures that can be traversed from left -- to right. -- -- Mostly like base's Traversable but applied to collections -- only. class Functor collection => Mappable collection where traverse f = sequenceA . fmap f sequenceA = traverse id mapM = traverse sequence = sequenceA -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Mappable collection, Applicative f) => (a -> f b) -> collection a -> f (collection b) -- | Evaluate each actions of the given collections, from left to right, -- and collect the results. For a version that ignores the results, see -- sequenceA_ sequenceA :: (Mappable collection, Applicative f) => collection (f a) -> f (collection a) -- | Map each element of the collection to an action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Mappable collection, Applicative m, Monad m) => (a -> m b) -> collection a -> m (collection b) -- | Evaluate each actions of the given collections, from left to right, -- and collect the results. For a version that ignores the results, see -- sequence_ sequence :: (Mappable collection, Applicative m, Monad m) => collection (m a) -> m (collection a) -- | Map each element of a collection to an action, evaluate these actions -- from left to right, and ignore the results. For a version that doesn't -- ignore the results see traverse traverse_ :: (Mappable col, Applicative f) => (a -> f b) -> col a -> f () -- | Evaluate each action in the collection from left to right, and ignore -- the results. For a version that doesn't ignore the results see -- sequenceA. sequenceA_ :: (Mappable col, Applicative f) => -- col (f a) -> f () sequenceA_ col = sequenceA col *> pure () -- -- Map each element of a collection to a monadic action, evaluate these -- actions from left to right, and ignore the results. For a version that -- doesn't ignore the results see mapM. mapM_ :: (Mappable col, Applicative m, Monad m) => (a -> m b) -> col a -> m () -- | forM is mapM with its arguments flipped. For a version -- that ignores the results see forM_. forM :: (Mappable col, Applicative m, Monad m) => col a -> (a -> m b) -> m (col b) -- | forM_ is mapM_ with its arguments flipped. For a version -- that doesn't ignore the results see forM. forM_ :: (Mappable col, Applicative m, Monad m) => col a -> (a -> m b) -> m () -- | A set of methods for ordered colection class (IsList c, Item c ~ Element c) => Collection c where elem e col = not $ e `notElem` col notElem e col = not $ e `elem` col -- | Check if a collection is empty null :: Collection c => c -> Bool -- | Length of a collection (number of Element c) length :: Collection c => c -> CountOf (Element c) -- | Check if a collection contains a specific element -- -- This is the inverse of notElem. elem :: forall a. (Collection c, 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. notElem :: forall a. (Collection c, Eq a, a ~ Element c) => Element c -> c -> Bool -- | Get the maximum element of a collection maximum :: forall a. (Collection c, Ord a, a ~ Element c) => NonEmpty c -> Element c -- | Get the minimum element of a collection minimum :: forall a. (Collection c, Ord a, a ~ Element c) => NonEmpty c -> Element c -- | Determine is any elements of the collection satisfy the predicate any :: Collection c => (Element c -> Bool) -> c -> Bool -- | Determine is all elements of the collection satisfy the predicate all :: Collection c => (Element c -> Bool) -> c -> Bool -- | NonEmpty property for any Collection -- -- This can only be made, through the nonEmpty smart contructor data NonEmpty a getNonEmpty :: NonEmpty a -> a -- | 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 nonEmpty :: Collection c => c -> Maybe (NonEmpty c) -- | same as nonEmpty, but assume that the collection is non empty, -- and return an asynchronous error if it is. nonEmpty_ :: Collection c => c -> NonEmpty c nonEmptyFmap :: Functor f => (a -> b) -> NonEmpty (f a) -> NonEmpty (f b) -- | A set of methods for ordered colection class (IsList c, Item c ~ Element c, Monoid c, Collection 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) partition predicate c = (filter predicate c, filter (not . predicate) c) head nel = maybe (error "head") fst $ uncons (getNonEmpty nel) last nel = maybe (error "last") snd $ unsnoc (getNonEmpty nel) tail nel = maybe (error "tail") snd $ uncons (getNonEmpty nel) init nel = maybe (error "init") fst $ unsnoc (getNonEmpty nel) isPrefixOf c1 c2 | len1 > len2 = False | len1 == len2 = c1 == c2 | otherwise = c1 == take len1 c2 where len1 = length c1 len2 = length c2 isSuffixOf c1 c2 | len1 > len2 = False | len1 == len2 = c1 == c2 | otherwise = c1 == revTake len1 c2 where len1 = length c1 len2 = length c2 isInfixOf c1 c2 | len1 > len2 = False | otherwise = loop 0 where endofs = len2 - len1 len1 = length c1 len2 = length c2 loop i | i == endofs = c1 == c2Sub | c1 == c2Sub = True | otherwise = loop (succ i) where c2Sub = take len1 $ drop i $ c2 -- | Take the first @n elements of a collection take :: Sequential c => CountOf (Element c) -> c -> c -- | Take the last @n elements of a collection revTake :: Sequential c => CountOf (Element c) -> c -> c -- | Drop the first @n elements of a collection drop :: Sequential c => CountOf (Element c) -> c -> c -- | Drop the last @n elements of a collection revDrop :: Sequential c => CountOf (Element c) -> c -> c -- | Split the collection at the @n'th elements splitAt :: Sequential c => CountOf (Element c) -> c -> (c, c) -- | Split the collection at the @n'th elements from the end revSplitAt :: Sequential c => CountOf (Element c) -> 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 -- | Partition the elements thtat satisfy the predicate and those that -- don't partition :: Sequential c => (Element c -> Bool) -> c -> (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 -- | Create a collection with a single element singleton :: Sequential c => Element c -> c -- | get the first element of a non-empty collection head :: Sequential c => NonEmpty c -> Element c -- | get the last element of a non-empty collection last :: Sequential c => NonEmpty c -> Element c -- | Extract the elements after the first element of a non-empty -- collection. tail :: Sequential c => NonEmpty c -> c -- | Extract the elements before the last element of a non-empty -- collection. init :: Sequential c => NonEmpty c -> c -- | Create a collection where the element in parameter is repeated N time replicate :: Sequential c => CountOf (Element c) -> Element c -> c -- | Takes two collections and returns True iff the first collection is a -- prefix of the second. isPrefixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- prefix of the second. isPrefixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- suffix of the second. isSuffixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- suffix of the second. isSuffixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is an -- infix of the second. isInfixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is an -- infix of the second. isInfixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | Collection of things that can be made mutable, modified and then -- freezed into an MutableFreezed collection class MutableCollection c where type MutableFreezed c type MutableKey c type MutableValue c unsafeThaw = thaw unsafeFreeze = freeze where { type family MutableFreezed c; type family MutableKey c; type family MutableValue c; } unsafeThaw :: (MutableCollection c, PrimMonad prim) => MutableFreezed c -> prim (c (PrimState prim)) unsafeFreeze :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> prim (MutableFreezed c) thaw :: (MutableCollection c, PrimMonad prim) => MutableFreezed c -> prim (c (PrimState prim)) freeze :: (MutableCollection c, PrimMonad prim) => c (PrimState prim) -> prim (MutableFreezed c) mutNew :: (MutableCollection c, PrimMonad prim) => CountOf (MutableValue c) -> prim (c (PrimState prim)) 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 -> Offset (Element c) -> Maybe (Element c) findIndex :: IndexedCollection c => (Element c -> Bool) -> c -> Maybe (Offset (Element c)) -- | 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 -- | Collections that can be built chunk by chunk. -- -- Use the Monad instance of Builder to chain append -- operations and feed it into build: -- --
-- >>> runST $ build 32 (append 'a' >> append 'b' >> append 'c') :: UArray Char -- "abc" --class Buildable col where type Mutable col :: * -> * type Step col where { type family Mutable col :: * -> *; type family Step col; } append :: (Buildable col, PrimMonad prim) => Element col -> Builder col (Mutable col) (Step col) prim () build :: (Buildable col, PrimMonad prim) => Int -> Builder col (Mutable col) (Step col) prim () -> prim col newtype Builder collection mutCollection step state a Builder :: State (Offset step, BuildingState collection mutCollection step (PrimState state)) state a -> Builder collection mutCollection step state a [runBuilder] :: Builder collection mutCollection step state a -> State (Offset step, BuildingState collection mutCollection step (PrimState state)) state a -- | The in-progress state of a building operation. -- -- The previous buffers are in reverse order, and this contains the -- current buffer and the state of progress packing the elements inside. data BuildingState collection mutCollection step state BuildingState :: [collection] -> !(CountOf step) -> mutCollection state -> !(CountOf step) -> BuildingState collection mutCollection step state [prevChunks] :: BuildingState collection mutCollection step state -> [collection] [prevChunksSize] :: BuildingState collection mutCollection step state -> !(CountOf step) [curChunk] :: BuildingState collection mutCollection step state -> mutCollection state [chunkSize] :: BuildingState collection mutCollection step state -> !(CountOf step) class Copy a copy :: Copy a => a -> a -- | https://github.com/haskell-foundation/issues/111 module Foundation.Class.Storable -- | Storable type of self determined size. class Storable a peek :: Storable a => Ptr a -> IO a poke :: Storable a => Ptr a -> a -> IO () -- | Extending the Storable type class to the types that can be sequenced -- in a structure. class Storable a => StorableFixed a size :: StorableFixed a => proxy a -> CountOf Word8 alignment :: StorableFixed a => proxy a -> CountOf Word8 -- | A value of type Ptr a represents a pointer to an -- object, or an array of objects, which may be marshalled to or from -- Haskell values of type a. -- -- The type a will often be an instance of class Storable -- which provides the marshalling operations. However this is not -- essential, and you can provide your own operations to access the -- pointer. For example you might write small foreign functions to get or -- set the fields of a C struct. data Ptr a :: * -> * plusPtr :: StorableFixed a => Ptr a -> CountOf a -> Ptr a -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b -- | like peek but at a given offset. peekOff :: StorableFixed a => Ptr a -> Offset a -> IO a -- | like poke but at a given offset. pokeOff :: StorableFixed a => Ptr a -> Offset a -> a -> IO () peekArray :: (Buildable col, StorableFixed (Element col)) => CountOf (Element col) -> Ptr (Element col) -> IO col peekArrayEndedBy :: (Buildable col, StorableFixed (Element col), Eq (Element col), Show (Element col)) => Element col -> Ptr (Element col) -> IO col pokeArray :: (Sequential col, StorableFixed (Element col)) => Ptr (Element col) -> col -> IO () pokeArrayEndedBy :: (Sequential col, StorableFixed (Element col)) => Element col -> Ptr (Element col) -> col -> IO () instance Foundation.Class.Storable.Storable Foreign.C.Types.CChar instance Foundation.Class.Storable.Storable Foreign.C.Types.CUChar instance Foundation.Class.Storable.Storable GHC.Types.Char instance Foundation.Class.Storable.Storable GHC.Types.Double instance Foundation.Class.Storable.Storable GHC.Types.Float instance Foundation.Class.Storable.Storable GHC.Int.Int8 instance Foundation.Class.Storable.Storable GHC.Int.Int16 instance Foundation.Class.Storable.Storable GHC.Int.Int32 instance Foundation.Class.Storable.Storable GHC.Int.Int64 instance Foundation.Class.Storable.Storable GHC.Word.Word8 instance Foundation.Class.Storable.Storable GHC.Word.Word16 instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.BE GHC.Word.Word16) instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.LE GHC.Word.Word16) instance Foundation.Class.Storable.Storable GHC.Word.Word32 instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.BE GHC.Word.Word32) instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.LE GHC.Word.Word32) instance Foundation.Class.Storable.Storable GHC.Word.Word64 instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.BE GHC.Word.Word64) instance Foundation.Class.Storable.Storable (Foundation.Primitive.Endianness.LE GHC.Word.Word64) instance Foundation.Class.Storable.Storable (GHC.Ptr.Ptr a) instance Foundation.Class.Storable.StorableFixed Foreign.C.Types.CChar instance Foundation.Class.Storable.StorableFixed Foreign.C.Types.CUChar instance Foundation.Class.Storable.StorableFixed GHC.Types.Char instance Foundation.Class.Storable.StorableFixed GHC.Types.Double instance Foundation.Class.Storable.StorableFixed GHC.Types.Float instance Foundation.Class.Storable.StorableFixed GHC.Int.Int8 instance Foundation.Class.Storable.StorableFixed GHC.Int.Int16 instance Foundation.Class.Storable.StorableFixed GHC.Int.Int32 instance Foundation.Class.Storable.StorableFixed GHC.Int.Int64 instance Foundation.Class.Storable.StorableFixed GHC.Word.Word8 instance Foundation.Class.Storable.StorableFixed GHC.Word.Word16 instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.BE GHC.Word.Word16) instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.LE GHC.Word.Word16) instance Foundation.Class.Storable.StorableFixed GHC.Word.Word32 instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.BE GHC.Word.Word32) instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.LE GHC.Word.Word32) instance Foundation.Class.Storable.StorableFixed GHC.Word.Word64 instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.BE GHC.Word.Word64) instance Foundation.Class.Storable.StorableFixed (Foundation.Primitive.Endianness.LE GHC.Word.Word64) instance Foundation.Class.Storable.StorableFixed (GHC.Ptr.Ptr a) -- | Data structure for optimised operations (append, cons, snoc) on list module Foundation.List.DList data DList a instance GHC.Classes.Eq a => GHC.Classes.Eq (Foundation.List.DList.DList a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Foundation.List.DList.DList a) instance GHC.Show.Show a => GHC.Show.Show (Foundation.List.DList.DList a) instance GHC.Exts.IsList (Foundation.List.DList.DList a) instance GHC.Base.Monoid (Foundation.List.DList.DList a) instance GHC.Base.Functor Foundation.List.DList.DList instance GHC.Base.Applicative Foundation.List.DList.DList instance GHC.Base.Monad Foundation.List.DList.DList instance Foundation.Collection.Foldable.Foldable (Foundation.List.DList.DList a) instance Foundation.Collection.Collection.Collection (Foundation.List.DList.DList a) instance Foundation.Collection.Sequential.Sequential (Foundation.List.DList.DList a) -- | The current implementation is mainly, if not copy/pasted, inspired -- from memory's Parser. -- -- A very simple bytearray parser related to Parsec and Attoparsec -- -- Simple example: -- --
-- > parse ((,,) <$> take 2 <*> element 0x20 <*> (elements "abc" *> anyElement)) "xx abctest" -- ParseOK "est" ("xx", 116) --module Foundation.Parser -- | Simple parser structure newtype Parser input a Parser :: (forall r. input -> Failure input r -> Success input a r -> Result input r) -> Parser input a [runParser] :: Parser input a -> forall r. input -> Failure input r -> Success input a r -> Result input r -- | Simple parsing result, that represent respectively: -- --
-- >>> toString (fromString "0:0:0:0:0:0:0:1" :: IPv6) --toString :: IPv6 -> String -- | create an IPv6 from the given tuple fromTuple :: (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -> IPv6 -- | decompose an IPv6 into a tuple toTuple :: IPv6 -> (Word16, Word16, Word16, Word16, Word16, Word16, Word16, Word16) -- | IPv6 Parser as described in RFC4291 -- -- for more details: -- https://tools.ietf.org/html/rfc4291.html#section-2.2 -- -- which is exactly: -- -- ``` ipv6ParserPreferred | ipv6ParserIPv4Embedded | -- ipv6ParserCompressed ``` ipv6Parser :: (Sequential input, Element input ~ Char) => Parser input IPv6 -- | IPv6 parser as described in RFC4291 section 2.2.1 -- -- The preferred form is x:x:x:x:x:x:x:x, where the xs are one -- to four hexadecimal digits of the eight 16-bit pieces of the address. -- --
-- hashMix (1 :: Integer) /= hashMix (1 :: Word8) ---- -- True class Hashable a hashMix :: (Hashable a, Hasher st) => a -> st -> st -- | Incremental Hashing state. Represent an hashing algorithm -- -- the base primitive of this class is hashMix8, append mix a -- Word8 in the state -- -- The class allow to define faster mixing function that works on bigger -- Word size and any unboxed array of any PrimType elements class Hasher st where hashMix16 w st = hashMix8 w2 $ hashMix8 w1 st where (# !w1, !w2 #) = unWord16 w hashMix32 w st = hashMix8 w4 $ hashMix8 w3 $ hashMix8 w2 $ hashMix8 w1 st where (# !w1, !w2, !w3, !w4 #) = unWord32 w hashMix64 w st = hashMix32 w2 $ hashMix32 w1 st where (# !w1, !w2 #) = unWord64_32 w hashMixBytes ba st = foldl' (flip hashMix8) st (unsafeRecast ba) -- | FNV1 32 bit state data FNV1_32 -- | FNV1 64 bit state data FNV1_64 -- | FNV1a 32 bit state data FNV1a_32 -- | FNV1a 64 bit state data FNV1a_64 -- | Sip State 1-3 (1 compression rounds, 3 digest rounds) data Sip1_3 -- | Sip State 2-4 (2 compression rounds, 4 digest rounds) data Sip2_4 -- | This module deals with the random subsystem abstractions. -- -- It provide 2 different set of abstractions: -- --
-- 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 ("foo.hs" :: FilePath) -- foo.hs ---- --
-- >>> filename ("foo/bar/baz.hs" :: FilePath) -- baz.hs --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 ("foo.hs" :: FilePath) -- . ---- --
-- >>> parent ("foo/bar/baz.hs" :: FilePath) -- foo/bar --parent :: Path path => path -> path -- | get the path prefix information -- --
-- >>> prefix ("/home/tab" :: FilePath) -- Absolute ---- --
-- >>> prefix ("home/tab" :: FilePath) -- Relative ---- -- 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 ("/home/tab" :: FilePath) -- () ---- -- 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: -- --
-- 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 ProductFirst a where { type family ProductFirst a; } fst :: Fstable a => a -> ProductFirst a -- | Class of product types that have a second element class Sndable a where type ProductSecond a where { type family ProductSecond a; } snd :: Sndable a => a -> ProductSecond a -- | Class of product types that have a third element class Thdable a where type ProductThird a where { type family ProductThird a; } thd :: Thdable a => a -> ProductThird 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. -- --
-- >>> 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. -- --
-- >>> 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 -- | stop execution and displays an error message error :: forall (r :: RuntimeRep). forall (a :: TYPE r). HasCallStack => String -> 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 -- | Data that can be fully evaluated in Normal Form class NormalForm a deepseq :: NormalForm a => a -> b -> b force :: NormalForm a => a -> a -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- --
-- 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, -- --
-- 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 :: Enum a => a -> a -- | the predecessor of a value. For numeric types, pred subtracts -- 1. pred :: Enum a => a -> a -- | Convert from an Int. toEnum :: Enum a => 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 :: Enum a => a -> Int -- | Used in Haskell's translation of [n..]. enumFrom :: Enum a => a -> [a] -- | Used in Haskell's translation of [n,n'..]. enumFromThen :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n..m]. enumFromTo :: Enum a => a -> a -> [a] -- | Used in Haskell's translation of [n,n'..m]. enumFromThenTo :: Enum a => 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 :: Functor f => (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. (<$) :: Functor f => a -> f b -> f a -- | Integral Literal support -- -- e.g. 123 :: Integer 123 :: Word8 class Integral a fromInteger :: Integral a => Integer -> a -- | Fractional Literal support -- -- e.g. 1.2 :: Double 0.03 :: Float class Fractional a fromRational :: Fractional a => Rational -> a -- | Negation support -- -- e.g. -(f x) class HasNegation a negate :: HasNegation a => a -> a -- | 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 i -- first (f . g) ≡ first f . first g -- second (f . g) ≡ second f . second g --class Bifunctor (p :: * -> * -> *) -- | Map over both arguments at the same time. -- --
-- bimap f g ≡ first f . second g --bimap :: Bifunctor p => (a -> b) -> (c -> d) -> p a c -> p b d -- | Map covariantly over the first argument. -- --
-- first f ≡ bimap f id --first :: Bifunctor p => (a -> b) -> p a c -> p b c -- | Map covariantly over the second argument. -- --
-- second ≡ bimap id --second :: Bifunctor p => (b -> c) -> p a b -> p a c -- | A functor with application, providing operations to -- --
pure id <*> -- v = v
pure (.) <*> u -- <*> v <*> w = u <*> (v -- <*> w)
pure f <*> -- pure x = pure (f x)
u <*> pure y = -- pure ($ y) <*> u
-- x + azero = x -- azero + x = x -- x + y = y + x --class Additive a where scale 0 _ = azero scale 1 a = a scale 2 a = a + a scale n a = a + scale (pred n) a azero :: Additive a => a (+) :: Additive a => a -> a -> a scale :: (Additive a, IsNatural 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: -- --
-- (-) :: Int -> Int -> Int -- (-) :: DateTime -> DateTime -> Seconds -- (-) :: Ptr a -> Ptr a -> PtrDiff -- (-) :: Natural -> Natural -> Maybe Natural --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 -- --
-- x * midentity = x -- midentity * x = x --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) .. (^) :: (IsNatural n) => a -> n -> -- a (^) :: (Multiplicative a, IsNatural n, IDivisible n) => a -> n -> a -- | Represent types that supports an euclidian division -- --
-- (x ‘div‘ y) * y + (x ‘mod‘ y) == x --class (Additive a, Multiplicative a) => IDivisible 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 :: IDivisible a => a -> a -> a mod :: IDivisible a => a -> a -> a divMod :: IDivisible a => a -> a -> (a, a) -- | Support for division between same types -- -- This is likely to change to represent specific mathematic divisions class Multiplicative a => Divisible a (/) :: Divisible a => a -> a -> 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"). -- --
-- >>> 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 :: * -- | Type representing arbitrary-precision non-negative integers. -- -- Operations whose result would be negative throw -- (Underflow :: ArithException). data Natural :: * -- | 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 :: * -- | 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. newtype CountOf ty CountOf :: Int -> CountOf 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. newtype Offset ty Offset :: Int -> Offset 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 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: -- --
mappend mempty x = x
mappend x mempty = x
mappend x (mappend y z) = mappend (mappend x y) z
mconcat = foldr mappend mempty
-- 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 -- | Partition the elements thtat satisfy the predicate and those that -- don't partition :: Sequential c => (Element c -> Bool) -> c -> (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 -- | Create a collection with a single element singleton :: Sequential c => Element c -> c -- | get the first element of a non-empty collection head :: Sequential c => NonEmpty c -> Element c -- | get the last element of a non-empty collection last :: Sequential c => NonEmpty c -> Element c -- | Extract the elements after the first element of a non-empty -- collection. tail :: Sequential c => NonEmpty c -> c -- | Extract the elements before the last element of a non-empty -- collection. init :: Sequential c => NonEmpty c -> c -- | Create a collection where the element in parameter is repeated N time replicate :: Sequential c => CountOf (Element c) -> Element c -> c -- | Takes two collections and returns True iff the first collection is a -- prefix of the second. isPrefixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- prefix of the second. isPrefixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- suffix of the second. isSuffixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is a -- suffix of the second. isSuffixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is an -- infix of the second. isInfixOf :: (Sequential c, Eq (Element c)) => c -> c -> Bool -- | Takes two collections and returns True iff the first collection is an -- infix of the second. isInfixOf :: (Sequential c, Eq c) => c -> c -> Bool -- | NonEmpty property for any Collection -- -- This can only be made, through the nonEmpty smart contructor data NonEmpty a -- | 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 nonEmpty :: Collection c => c -> Maybe (NonEmpty c) -- | 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 -- | 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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 _. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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. -- --
-- >>> 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` f) `on` g = (*) `on` (f . g)
flip on f . flip on g = flip on (g . -- f)
-- ($) :: (a -> b) -> a -> b -- (<$>) :: Functor f => (a -> b) -> f a -> f b ---- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --
-- >>> 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 :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => 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 -- | for support of if .. then .. else ifThenElse :: Bool -> a -> a -> a -- | Alias to Prelude String ([Char]) for compatibility purpose type LString = String module Foundation.Conduit -- | A component of a conduit pipeline, which takes a stream of -- input, produces a stream of output, performs actions -- in the underlying monad, and produces a value of -- result when no more output data is available. data Conduit input output monad result data ResourceT m a newtype ZipSink i m r ZipSink :: Conduit i () m r -> ZipSink i m r [getZipSink] :: ZipSink i m r -> Conduit i () m r -- | Await for a value from upstream. await :: Conduit i o m (Maybe i) awaitForever :: (input -> Conduit input output monad b) -> Conduit input output monad () -- | Send a value downstream. yield :: Monad m => o -> Conduit i o m () -- | Same as yield, but additionally takes a finalizer to be run if -- the downstream component terminates. yieldOr :: o -> m () -> Conduit i o m () -- | Provide leftover input to be consumed by the next component in the -- current monadic binding. leftover :: i -> Conduit i o m () -- | Run a conduit pipeline to completion. runConduit :: Monad m => Conduit () () m r -> m r -- | Run a pure conduit pipeline to completion. runConduitPure :: Conduit () () Identity r -> r -- | Run a conduit pipeline in a ResourceT context for acquiring -- resources. runConduitRes :: (MonadBracket m, MonadIO m) => Conduit () () (ResourceT m) r -> m r -- | Send the output of the first Conduit component to the second Conduit -- component. fuse :: Monad m => Conduit a b m () -> Conduit b c m r -> Conduit a c m r -- | Operator version of fuse. (.|) :: Monad m => Conduit a b m () -> Conduit b c m r -> Conduit a c m r infixr 2 .| sourceFile :: MonadResource m => FilePath -> Conduit i (UArray Word8) m () sourceHandle :: MonadIO m => Handle -> Conduit i (UArray Word8) m () sinkFile :: MonadResource m => FilePath -> Conduit (UArray Word8) i m () sinkHandle :: MonadIO m => Handle -> Conduit (UArray Word8) o m () sinkList :: Monad m => Conduit i o m [i] bracketConduit :: MonadResource m => IO a -> (a -> IO b) -> (a -> Conduit i o m r) -> Conduit i o m r