-- 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.8 module Foundation.System.Bindings.PosixDef type CErrno = CInt type CFd = CInt type CMemProtFlags = CInt type CMemMappingFlags = CInt type CMemAdvice = CInt type CMemSyncFlags = CInt type CSysconfName = CInt type COpenFlags = CInt newtype COff :: * COff :: Int64 -> COff newtype CMode :: * CMode :: Word32 -> CMode module Foundation.System.Bindings.Hs sysHsCoreGetErrno :: IO CInt -- | 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 module Foundation.Monad -- | Monads in which IO computations may be embedded. Any monad -- built by applying a sequence of monad transformers to the IO -- monad will be an instance of this class. -- -- Instances should satisfy the following laws, which state that -- liftIO is a transformer of monads: -- -- class Monad m => MonadIO (m :: * -> *) -- | Lift a computation from the IO monad. liftIO :: MonadIO m => IO a -> m a -- | Monad that can represent failure -- -- Similar to MonadFail but with a parametrized Failure linked to the -- Monad class Monad m => MonadFailure m where type Failure m where { type family Failure m; } -- | Raise a Failure through a monad. mFail :: MonadFailure m => Failure m -> m () -- | Monad that can throw exception class Monad m => MonadThrow m -- | Throw immediatity an exception. Only a MonadCatch monad will be -- able to catch the exception using catch throw :: (MonadThrow m, Exception e) => e -> m a -- | Monad that can catch exception class MonadThrow m => MonadCatch m catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a -- | Monad that can ensure cleanup actions are performed even in the case -- of exceptions, both synchronous and asynchronous. This usually -- excludes continuation-based monads. class MonadCatch m => MonadBracket m -- | A generalized version of the standard bracket function which allows -- distinguishing different exit cases. generalBracket :: MonadBracket m => m a -> (a -> b -> m ignored1) -> (a -> SomeException -> m ignored2) -> (a -> m b) -> m b -- | Basic Transformer class class MonadTrans trans -- | Lift a computation from an inner monad to the current transformer -- monad lift :: (MonadTrans trans, Monad m) => m a -> trans m a -- | Identity functor and monad. (a non-strict monad) newtype Identity a :: * -> * Identity :: a -> Identity a [runIdentity] :: Identity a -> a -- | The Reader monad transformer. -- -- This is useful to keep a non-modifiable value in a context module Foundation.Monad.Reader class Monad m => MonadReader m where type ReaderContext m where { type family ReaderContext m; } ask :: MonadReader m => m (ReaderContext m) -- | Reader Transformer data ReaderT r m a runReaderT :: ReaderT r m a -> r -> m a instance GHC.Base.Functor m => GHC.Base.Functor (Foundation.Monad.Reader.ReaderT r m) instance GHC.Base.Applicative m => GHC.Base.Applicative (Foundation.Monad.Reader.ReaderT r m) instance GHC.Base.Monad m => GHC.Base.Monad (Foundation.Monad.Reader.ReaderT r m) instance Foundation.Monad.Transformer.MonadTrans (Foundation.Monad.Reader.ReaderT r) instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Foundation.Monad.Reader.ReaderT r m) instance Foundation.Monad.Exception.MonadFailure m => Foundation.Monad.Exception.MonadFailure (Foundation.Monad.Reader.ReaderT r m) instance Foundation.Monad.Exception.MonadThrow m => Foundation.Monad.Exception.MonadThrow (Foundation.Monad.Reader.ReaderT r m) instance Foundation.Monad.Exception.MonadCatch m => Foundation.Monad.Exception.MonadCatch (Foundation.Monad.Reader.ReaderT r m) instance GHC.Base.Monad m => Foundation.Monad.Reader.MonadReader (Foundation.Monad.Reader.ReaderT r m) module Foundation.Monad.State class Monad m => MonadState m where type State m where { type family State m; } withState :: MonadState m => (State m -> (a, State m)) -> m a get :: MonadState m => m (State m) put :: MonadState m => State m -> m () -- | State Transformer data StateT s m a runStateT :: StateT s m a -> s -> m (a, s) instance GHC.Base.Functor m => GHC.Base.Functor (Foundation.Monad.State.StateT s m) instance (GHC.Base.Applicative m, GHC.Base.Monad m) => GHC.Base.Applicative (Foundation.Monad.State.StateT s m) instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Monad (Foundation.Monad.State.StateT s m) instance Foundation.Monad.Transformer.MonadTrans (Foundation.Monad.State.StateT s) instance (GHC.Base.Functor m, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Foundation.Monad.State.StateT s m) instance (GHC.Base.Functor m, Foundation.Monad.Exception.MonadFailure m) => Foundation.Monad.Exception.MonadFailure (Foundation.Monad.State.StateT s m) instance (GHC.Base.Functor m, Foundation.Monad.Exception.MonadThrow m) => Foundation.Monad.Exception.MonadThrow (Foundation.Monad.State.StateT s m) instance (GHC.Base.Functor m, Foundation.Monad.Exception.MonadCatch m) => Foundation.Monad.Exception.MonadCatch (Foundation.Monad.State.StateT s m) instance (GHC.Base.Functor m, GHC.Base.Monad m) => Foundation.Monad.State.MonadState (Foundation.Monad.State.StateT s m) -- | 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.Numerical -- | Number literals, convertible through the generic Integer type. -- -- all number are Enum'erable, meaning that you can move to next element class (Enum a, Eq a, Ord a, Integral a) => IsIntegral a toInteger :: IsIntegral a => a -> Integer -- | Non Negative Number literals, convertible through the generic Natural -- type class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a toNatural :: IsNatural a => a -> Natural -- | types that have sign and can be made absolute class 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. -- --
--   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.Math.Trigonometry -- | Method to support basic trigonometric functions class Trigonometry a -- | the famous pi value pi :: Trigonometry a => a -- | sine sin :: Trigonometry a => a -> a -- | cosine cos :: Trigonometry a => a -> a -- | tan tan :: Trigonometry a => a -> a -- | sine-1 asin :: Trigonometry a => a -> a -- | cosine-1 acos :: Trigonometry a => a -> a -- | tangent-1 atan :: Trigonometry a => a -> a -- | hyperbolic sine sinh :: Trigonometry a => a -> a -- | hyperbolic cosine cosh :: Trigonometry a => a -> a -- | hyperbolic tangent tanh :: Trigonometry a => a -> a -- | hyperbolic sine-1 asinh :: Trigonometry a => a -> a -- | hyperbolic cosine-1 acosh :: Trigonometry a => a -> a -- | hyperbolic tangent-1 atanh :: Trigonometry a => a -> a instance Foundation.Math.Trigonometry.Trigonometry Foundation.Internal.Base.FP32 instance Foundation.Math.Trigonometry.Trigonometry Foundation.Internal.Base.FP64 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) -- | 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 -- | Functions defined by the POSIX standards module Foundation.System.Bindings.Posix data CDir data CDirent sysPosix_E2BIG :: CErrno sysPosix_EACCES :: CErrno sysPosix_EADDRINUSE :: CErrno sysPosix_EADDRNOTAVAIL :: CErrno sysPosix_EAFNOSUPPORT :: CErrno sysPosix_EAGAIN :: CErrno sysPosix_EALREADY :: CErrno sysPosix_EBADF :: CErrno sysPosix_EBUSY :: CErrno sysPosix_ECANCELED :: CErrno sysPosix_ECHILD :: CErrno sysPosix_ECONNABORTED :: CErrno sysPosix_ECONNREFUSED :: CErrno sysPosix_ECONNRESET :: CErrno sysPosix_EDEADLK :: CErrno sysPosix_EDESTADDRREQ :: CErrno sysPosix_EDOM :: CErrno sysPosix_EDQUOT :: CErrno sysPosix_EEXIST :: CErrno sysPosix_EFAULT :: CErrno sysPosix_EFBIG :: CErrno sysPosix_EHOSTUNREACH :: CErrno sysPosix_EIDRM :: CErrno sysPosix_EILSEQ :: CErrno sysPosix_EINPROGRESS :: CErrno sysPosix_EINTR :: CErrno sysPosix_EINVAL :: CErrno sysPosix_EIO :: CErrno sysPosix_EISCONN :: CErrno sysPosix_EISDIR :: CErrno sysPosix_ELOOP :: CErrno sysPosix_EMFILE :: CErrno sysPosix_EMLINK :: CErrno sysPosix_EMSGSIZE :: CErrno sysPosix_ENAMETOOLONG :: CErrno sysPosix_ENETDOWN :: CErrno sysPosix_ENETRESET :: CErrno sysPosix_ENETUNREACH :: CErrno sysPosix_ENFILE :: CErrno sysPosix_ENOBUFS :: CErrno sysPosix_ENODEV :: CErrno sysPosix_ENOENT :: CErrno sysPosix_ENOEXEC :: CErrno sysPosix_ENOLCK :: CErrno sysPosix_ENOMEM :: CErrno sysPosix_ENOMSG :: CErrno sysPosix_ENOPROTOOPT :: CErrno sysPosix_ENOSPC :: CErrno sysPosix_ENOSYS :: CErrno sysPosix_ENOTCONN :: CErrno sysPosix_ENOTDIR :: CErrno sysPosix_ENOTEMPTY :: CErrno sysPosix_ENOTSOCK :: CErrno sysPosix_ENOTSUP :: CErrno sysPosix_ENOTTY :: CErrno sysPosix_ENXIO :: CErrno sysPosix_EOPNOTSUPP :: CErrno sysPosix_EOVERFLOW :: CErrno sysPosix_EPERM :: CErrno sysPosix_EPIPE :: CErrno sysPosix_EPROTONOSUPPORT :: CErrno sysPosix_EPROTOTYPE :: CErrno sysPosix_ERANGE :: CErrno sysPosix_EROFS :: CErrno sysPosix_ESPIPE :: CErrno sysPosix_ESRCH :: CErrno sysPosix_ESTALE :: CErrno sysPosix_ETIMEDOUT :: CErrno sysPosix_ETXTBSY :: CErrno sysPosix_EWOULDBLOCK :: CErrno sysPosix_EXDEV :: CErrno sysPosix_ENODATA :: CErrno sysPosix_ENOSR :: CErrno sysPosix_ENOSTR :: CErrno sysPosix_ETIME :: CErrno sysPosix_EBADMSG :: CErrno sysPosix_EMULTIHOP :: CErrno sysPosix_ENOLINK :: CErrno sysPosix_ENOTRECOVERABLE :: CErrno sysPosix_EOWNERDEAD :: CErrno sysPosix_EPROTO :: CErrno sysPosix_O_RDONLY :: COpenFlags sysPosix_O_WRONLY :: COpenFlags sysPosix_O_RDWR :: COpenFlags sysPosix_O_NONBLOCK :: COpenFlags sysPosix_O_APPEND :: COpenFlags sysPosix_O_CREAT :: COpenFlags sysPosix_O_TRUNC :: COpenFlags sysPosix_O_EXCL :: COpenFlags sysPosix_O_NOFOLLOW :: COpenFlags sysPosix_O_CLOEXEC :: COpenFlags sysPosix_PROT_NONE :: CMemProtFlags sysPosix_PROT_READ :: CMemProtFlags sysPosix_PROT_WRITE :: CMemProtFlags sysPosix_PROT_EXEC :: CMemProtFlags sysPosix_MAP_SHARED :: CMemMappingFlags sysPosix_MAP_PRIVATE :: CMemMappingFlags sysPosix_MAP_FIXED :: CMemMappingFlags sysPosix_MAP_ANONYMOUS :: CMemMappingFlags sysPosix_MADV_NORMAL :: CMemAdvice sysPosix_MADV_RANDOM :: CMemAdvice sysPosix_MADV_SEQUENTIAL :: CMemAdvice sysPosix_MADV_WILLNEED :: CMemAdvice sysPosix_MADV_DONTNEED :: CMemAdvice sysPosix_MS_ASYNC :: CMemSyncFlags sysPosix_MS_SYNC :: CMemSyncFlags sysPosix_MS_INVALIDATE :: CMemSyncFlags sysPosixMmap :: Ptr a -> CSize -> CMemProtFlags -> CMemMappingFlags -> CFd -> COff -> IO (Ptr a) sysPosixMunmap :: Ptr a -> CSize -> IO CInt sysPosixMadvise :: Ptr a -> CSize -> CMemAdvice -> IO CInt sysPosixMsync :: Ptr a -> CSize -> CMemSyncFlags -> IO CInt sysPosixMprotect :: Ptr a -> CSize -> CMemProtFlags -> IO CInt sysPosixMlock :: Ptr a -> CSize -> IO CInt sysPosixMunlock :: Ptr a -> CSize -> IO CInt sysPosix_SC_PAGESIZE :: CSysconfName sysPosixSysconf :: CSysconfName -> CLong sysPosixOpen :: Ptr CChar -> COpenFlags -> CMode -> IO CFd sysPosixOpenAt :: CFd -> Ptr CChar -> COpenFlags -> CMode -> IO CFd sysPosixClose :: CFd -> IO CInt sysPosixFnctlNoArg :: CFd -> CInt -> IO CInt sysPosixFnctlPtr :: CFd -> CInt -> Ptr a -> IO CInt sysPosixFtruncate :: CFd -> COff -> IO CInt sysPosixOpendir :: Ptr CChar -> IO (Ptr CDir) sysPosixFdopendir :: CFd -> IO (Ptr CDir) sysPosixReaddir :: Ptr CDir -> IO (Ptr CDirent) sysPosixReaddirR :: Ptr CDir -> Ptr CDirent -> Ptr (Ptr CDirent) -> IO CInt sysPosixTelldir :: Ptr CDir -> IO CLong sysPosixSeekdir :: Ptr CDir -> CLong -> IO () sysPosixRewinddir :: Ptr CDir -> IO () sysPosixClosedir :: Ptr CDir -> IO CInt sysPosixDirfd :: Ptr CDir -> IO CFd module Foundation.System.Bindings -- | Functions defined only for linux module Foundation.System.Bindings.Linux type CInotifyFlags = CInt type CInotifyMask = CInt type CWatchDescriptor = CInt sysLinux_O_TMPFILE :: COpenFlags sysLinux_IN_NONBLOCK :: CInotifyFlags sysLinux_IN_CLOEXEC :: CInotifyFlags sysLinux_IN_ACCESS :: CInotifyMask sysLinux_IN_ATTRIB :: CInotifyMask sysLinux_IN_CLOSE_WRITE :: CInotifyMask sysLinux_IN_CLOSE_NOWRITE :: CInotifyMask sysLinux_IN_CREATE :: CInotifyMask sysLinux_IN_DELETE :: CInotifyMask sysLinux_IN_DELETE_SELF :: CInotifyMask sysLinux_IN_MODIFY :: CInotifyMask sysLinux_IN_MOVE_SELF :: CInotifyMask sysLinux_IN_MOVED_FROM :: CInotifyMask sysLinux_IN_MOVED_TO :: CInotifyMask sysLinux_IN_OPEN :: CInotifyMask sysLinux_IN_DONT_FOLLOW :: CInotifyMask sysLinux_IN_MASK_ADD :: CInotifyMask sysLinux_IN_ONESHOT :: CInotifyMask sysLinux_IN_ONLYDIR :: CInotifyMask sysLinux_IN_EXCL_UNLINK :: CInotifyMask sysLinux_IN_IGNORED :: CInotifyMask sysLinux_IN_ISDIR :: CInotifyMask sysLinux_IN_Q_OVERFLOW :: CInotifyMask sysLinux_IN_UNMOUNT :: CInotifyMask cinotifyEventSize :: CSize sysLinuxInotifyInit :: CInotifyFlags -> IO CFd sysLinuxInotifyAddWatch :: CFd -> Ptr CChar -> CInotifyMask -> IO CWatchDescriptor sysLinuxInotifyRmWatch :: CFd -> CWatchDescriptor -> IO Int 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 ("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 idid
--   
-- -- If you supply first and second, ensure: -- --
--   first idid
--   second idid
--   
-- -- 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. -- --
--   secondbimap id
--   
second :: Bifunctor p => (b -> c) -> p a b -> p a c -- | 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. -- -- class Eq a => Bits a -- | Bitwise "and" (.&.) :: Bits a => a -> a -> a -- | Bitwise "or" (.|.) :: Bits a => a -> a -> a -- | Bitwise "xor" xor :: Bits a => a -> a -> a -- | Reverse all the bits in the argument complement :: Bits a => a -> a -- | shift x i shifts x left by i bits if -- i is positive, or right by -i bits otherwise. Right -- shifts perform sign extension on signed number types; i.e. they fill -- the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- An instance can define either this unified shift or -- shiftL and shiftR, depending on which is more convenient -- for the type in question. shift :: Bits a => a -> Int -> a -- | rotate x i rotates x left by i bits -- if i is positive, or right by -i bits otherwise. -- -- For unbounded types like Integer, rotate is equivalent -- to shift. -- -- An instance can define either this unified rotate or -- rotateL and rotateR, depending on which is more -- convenient for the type in question. rotate :: Bits a => a -> Int -> a -- | zeroBits is the value with all bits unset. -- -- The following laws ought to hold (for all valid bit indices -- n): -- -- -- -- This method uses clearBit (bit 0) 0 as its -- default implementation (which ought to be equivalent to -- zeroBits for types which possess a 0th bit). zeroBits :: Bits a => a -- | bit i is a value with the ith bit set -- and all other bits clear. -- -- Can be implemented using bitDefault if a is also an -- instance of Num. -- -- See also zeroBits. bit :: Bits a => Int -> a -- | x `setBit` i is the same as x .|. bit i setBit :: Bits a => a -> Int -> a -- | x `clearBit` i is the same as x .&. complement (bit -- i) clearBit :: Bits a => a -> Int -> a -- | x `complementBit` i is the same as x `xor` bit i complementBit :: Bits a => a -> Int -> a -- | Return True if the nth bit of the argument is 1 -- -- Can be implemented using testBitDefault if a is also -- an instance of Num. testBit :: Bits a => a -> Int -> Bool -- | Return the number of bits in the type of the argument. The actual -- value of the argument is ignored. Returns Nothing for types that do -- not have a fixed bitsize, like Integer. bitSizeMaybe :: Bits a => a -> Maybe Int -- | Return the number of bits in the type of the argument. The actual -- value of the argument is ignored. The function bitSize is -- undefined for types that do not have a fixed bitsize, like -- Integer. bitSize :: Bits a => a -> Int -- | Return True if the argument is a signed type. The actual value -- of the argument is ignored isSigned :: Bits a => a -> Bool -- | Shift the argument left by the specified number of bits (which must be -- non-negative). -- -- An instance can define either this and shiftR or the unified -- shift, depending on which is more convenient for the type in -- question. shiftL :: Bits a => a -> Int -> a -- | Shift the argument left by the specified number of bits. The result is -- undefined for negative shift amounts and shift amounts greater or -- equal to the bitSize. -- -- Defaults to shiftL unless defined explicitly by an instance. unsafeShiftL :: Bits a => a -> Int -> a -- | Shift the first argument right by the specified number of bits. The -- result is undefined for negative shift amounts and shift amounts -- greater or equal to the bitSize. -- -- Right shifts perform sign extension on signed number types; i.e. they -- fill the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- An instance can define either this and shiftL or the unified -- shift, depending on which is more convenient for the type in -- question. shiftR :: Bits a => a -> Int -> a -- | Shift the first argument right by the specified number of bits, which -- must be non-negative an smaller than the number of bits in the type. -- -- Right shifts perform sign extension on signed number types; i.e. they -- fill the top bits with 1 if the x is negative and with 0 -- otherwise. -- -- Defaults to shiftR unless defined explicitly by an instance. unsafeShiftR :: Bits a => a -> Int -> a -- | Rotate the argument left by the specified number of bits (which must -- be non-negative). -- -- An instance can define either this and rotateR or the unified -- rotate, depending on which is more convenient for the type in -- question. rotateL :: Bits a => a -> Int -> a -- | Rotate the argument right by the specified number of bits (which must -- be non-negative). -- -- An instance can define either this and rotateL or the unified -- rotate, depending on which is more convenient for the type in -- question. rotateR :: Bits a => a -> Int -> a -- | Return the number of set bits in the argument. This number is known as -- the population count or the Hamming weight. -- -- Can be implemented using popCountDefault if a is also -- an instance of Num. popCount :: Bits a => a -> Int -- | Round up (if needed) to a multiple of alignment closst to -- m -- -- alignment needs to be a power of two -- -- alignRoundUp 16 8 = 16 alignRoundUp 15 8 = 16 alignRoundUp :: Int -> Int -> Int -- | Round down (if needed) to a multiple of alignment closest to -- m -- -- alignment needs to be a power of two -- --
--   alignRoundDown 15 8 = 8
--   alignRoundDown 8 8  = 8
--   
alignRoundDown :: Int -> Int -> Int -- | 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 withPtr :: (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a recast :: (PrimType a, PrimType b) => UArray a -> UArray b toHexadecimal :: PrimType ty => UArray ty -> UArray Word8 -- | Create a new mutable array of size @n. -- -- When memory for a new array is allocated, we decide if that memory -- region should be pinned (will not be copied around by GC) or unpinned -- (can be moved around by GC) depending on its size. -- -- You can change the threshold value used by setting the environment -- variable HS_FOUNDATION_UARRAY_UNPINNED_MAX. new :: (PrimMonad prim, PrimType ty) => Size ty -> prim (MUArray ty (PrimState prim)) -- | Create a new pinned mutable array of size @n. -- -- all the cells are uninitialized and could contains invalid values. -- -- All mutable arrays are allocated on a 64 bits aligned addresses newPinned :: (PrimMonad prim, PrimType ty) => Size ty -> prim (MUArray ty (PrimState prim)) -- | Create a pointer on the beginning of the mutable array and call a -- function f. -- -- The mutable buffer can be mutated by the f function and the -- change will be reflected in the mutable array -- -- If the mutable array is unpinned, a trampoline buffer is created and -- the data is only copy when f return. withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a 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)) -- | 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: -- -- -- -- Considering a stream of data that is fetched chunk by chunk, it's -- valid to assume that some sequence might fall in a chunk boundary. -- When converting chunks, if the error is Nothing and the remaining -- buffer is not empty, then this buffer need to be prepended to the next -- chunk fromBytes :: Encoding -> UArray Word8 -> (String, Maybe ValidationFailure, UArray Word8) -- | Convert a UTF8 array of bytes to a String. -- -- If there's any error in the stream, it will automatically insert -- replacement bytes to replace invalid sequences. -- -- In the case of sequence that fall in the middle of 2 chunks, the -- remaining buffer is supposed to be preprended to the next chunk, and -- resume the parsing. fromBytesLenient :: UArray Word8 -> (String, UArray Word8) -- | Convert a Byte Array representing UTF8 data directly to a string -- without checking for UTF8 validity -- -- If the input contains invalid sequences, it will trigger runtime async -- errors when processing data. -- -- In doubt, use fromBytes fromBytesUnsafe :: UArray Word8 -> String -- | Convert a String to a bytearray in a specific encoding -- -- if the encoding is UTF8, the underlying buffer is returned without -- extra allocation or any processing -- -- In any other encoding, some allocation and processing are done to -- convert. toBytes :: Encoding -> String -> UArray Word8 -- | Possible failure related to validating bytes of UTF8 sequences. data ValidationFailure InvalidHeader :: ValidationFailure InvalidContinuation :: ValidationFailure MissingByte :: ValidationFailure -- | Split lines in a string using newline as separation lines :: String -> [String] -- | Split words in a string using spaces as separation -- --
--   words "Hello Foundation"
--   
-- -- words :: String -> [String] 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 [Char] OS -- | Enumeration of the known GHC supported architecture. data Arch I386 :: Arch X86_64 :: Arch PowerPC :: Arch PowerPC64 :: Arch Sparc :: Arch Sparc64 :: Arch ARM :: Arch ARM64 :: Arch -- | 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 [Char] 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 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 module Foundation.String.Read readInteger :: String -> Maybe Integer -- | Read an Integer from a String -- -- Consume an optional minus sign and many digits until end of string. readIntegral :: (HasNegation i, IntegralUpsize Word8 i, Additive i, Multiplicative i, IsIntegral i) => String -> Maybe i -- | Read a Natural from a String -- -- Consume many digits until end of string. readNatural :: String -> Maybe Natural -- | Try to read a Double readDouble :: String -> Maybe Double -- | Try to read a floating number as a Rational -- -- Note that for safety reason, only exponent between -10000 and 10000 is -- allowed as otherwise DoS/OOM is very likely. if you don't want this -- behavior, switching to a scientific type (not provided yet) that -- represent the exponent separately is the advised solution. readRational :: String -> Maybe Rational -- | Read an Floating like number of the form: -- -- -- -- Call a function with: -- -- -- -- The code is structured as a simple state machine that: -- -- readFloatingExact :: String -> ReadFloatingCallback a -> Maybe a module Foundation.System.Entropy -- | Get some of the system entropy getEntropy :: Size Word8 -> IO (UArray Word8) -- | 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) => (Element c -> Element c) -> c -> 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 -- | 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 () -- | 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 -> Int -- | 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 -- | 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 -- | 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 => Word -> 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 -- | 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) => Int -> 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] -> !(Size step) -> mutCollection state -> !(Size step) -> BuildingState collection mutCollection step state [prevChunks] :: BuildingState collection mutCollection step state -> [collection] [prevChunksSize] :: BuildingState collection mutCollection step state -> !(Size step) [curChunk] :: BuildingState collection mutCollection step state -> mutCollection state [chunkSize] :: BuildingState collection mutCollection step state -> !(Size 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 -> Size Word8 alignment :: StorableFixed a => proxy a -> Size 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 -> Size 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)) => Size (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) module Foundation.Conduit.Textual -- | Split conduit of string to its lines -- -- This is very similar to Prelude lines except it work directly on -- Conduit -- -- Note that if the newline character is not coming, this function will -- keep accumulating data until OOM lines :: Monad m => Conduit String String m () fromBytes :: MonadThrow m => Encoding -> Conduit (UArray Word8) String m () toBytes :: Monad m => Encoding -> Conduit String (UArray Word8) m () -- | 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: -- -- data Result input a ParseFail :: (ParserError input) -> Result input a ParseMore :: (Maybe input -> Result input a) -> Result input a ParseOK :: input -> a -> Result input a data ParserError input Expected :: !input -> !input -> ParserError input -- | the expected input [expectedInput] :: ParserError input -> !input -- | but received this data [receivedInput] :: ParserError input -> !input -- | some bytes didn't satisfy predicate DoesNotSatify :: ParserError input -- | not enough data to complete the parser NotEnough :: ParserError input -- | only use in the event of Monad.fail function MonadFail :: String -> ParserError input -- | Run a Parser on a ByteString and return a Result parse :: Sequential input => Parser input a -> input -> Result input a -- | Run a parser on an @initial input. -- -- If the Parser need more data than available, the @feeder function is -- automatically called and fed to the More continuation. parseFeed :: (Sequential input, Monad m) => m (Maybe input) -> Parser input a -> input -> m (Result input a) -- | parse only the given input -- -- The left-over `Element input` will be ignored, if the parser call for -- more data it will be continuously fed with Nothing (up to 256 -- iterations). parseOnly :: (Typeable input, Show input, Sequential input, Element input ~ Char) => Parser input a -> input -> a hasMore :: Sequential input => Parser input Bool -- | Parse a specific `Element input` at current position -- -- if the `Element input` is different than the expected one, this parser -- will raise a failure. element :: (Sequential input, Eq (Element input)) => Element input -> Parser input () -- | take one element if satisfy the given predicate satisfy :: Sequential input => (Element input -> Bool) -> Parser input (Element input) -- | Get the next `Element input` from the parser anyElement :: Sequential input => Parser input (Element input) -- | Parse a sequence of elements from current position -- -- if the following `Element input` don't match the expected -- input completely, the parser will raise a failure elements :: (Show input, Eq input, Sequential input) => input -> Parser input () string :: String -> Parser String () -- | Take @n elements from the current position in the stream take :: Sequential input => Int -> Parser input input -- | Take elements while the @predicate hold from the current position in -- the stream takeWhile :: Sequential input => (Element input -> Bool) -> Parser input input -- | Take the remaining elements from the current position in the stream takeAll :: Sequential input => Parser input input -- | Skip @n elements from the current position in the stream skip :: Sequential input => Int -> Parser input () -- | Skip `Element input` while the @predicate hold from the current -- position in the stream skipWhile :: Sequential input => (Element input -> Bool) -> Parser input () -- | Skip all the remaining `Element input` from the current position in -- the stream skipAll :: Sequential input => Parser input () -- | One or none. optional :: Alternative f => f a -> f (Maybe a) -- | Zero or more. many :: Alternative f => forall a. f a -> f [a] -- | One or more. some :: Alternative f => forall a. f a -> f [a] -- | An associative binary operation (<|>) :: Alternative f => forall a. f a -> f a -> f a data Count Never :: Count Once :: Count Twice :: Count Other :: Int -> Count data Condition Exactly :: Count -> Condition Between :: Count -> Count -> Condition -- | repeat the given Parser a given amount of time -- -- If you know you want it to exactly perform a given amount of time: -- -- ``` repeat (Exactly Twice) (element a) ``` -- -- If you know your parser must performs from 0 to 8 times: -- -- ``` repeat (Between Never (Other 8)) ``` -- -- repeat :: Sequential input => Condition -> Parser input a -> Parser input [a] instance GHC.Show.Show Foundation.Parser.Condition instance GHC.Show.Show Foundation.Parser.Count instance GHC.Classes.Ord input => GHC.Classes.Ord (Foundation.Parser.ParserError input) instance GHC.Classes.Eq input => GHC.Classes.Eq (Foundation.Parser.ParserError input) instance GHC.Show.Show input => GHC.Show.Show (Foundation.Parser.ParserError input) instance (GHC.Show.Show input, Data.Typeable.Internal.Typeable input) => GHC.Exception.Exception (Foundation.Parser.ParserError input) instance (GHC.Show.Show ba, GHC.Show.Show a) => GHC.Show.Show (Foundation.Parser.Result ba a) instance GHC.Base.Functor (Foundation.Parser.Parser input) instance GHC.Base.Applicative (Foundation.Parser.Parser input) instance GHC.Base.Monad (Foundation.Parser.Parser input) instance GHC.Base.MonadPlus (Foundation.Parser.Parser input) instance GHC.Base.Alternative (Foundation.Parser.Parser input) instance GHC.Enum.Enum Foundation.Parser.Count -- | A AsciiString type backed by a ASCII encoded byte array and -- all the necessary functions to manipulate the string. -- -- The recommended type is AsciiString from UTF8 module Foundation.String.ASCII -- | Opaque packed array of characters in the ASCII encoding data AsciiString create :: PrimMonad prim => Int -> (MutableAsciiString (PrimState prim) -> prim Int) -> prim AsciiString replicate :: Int -> CUChar -> AsciiString -- | Convert a Byte Array representing UTF8 data directly to a string -- without checking for UTF8 validity -- -- If the input contains invalid sequences, it will trigger runtime async -- errors when processing data. -- -- In doubt, use fromBytes fromBytesUnsafe :: UArray CUChar -> AsciiString toBytes :: AsciiString -> UArray CUChar -- | Copy the AsciiString copy :: AsciiString -> AsciiString lines :: AsciiString -> [AsciiString] words :: AsciiString -> [AsciiString] instance GHC.Classes.Ord Foundation.String.ASCII.AsciiString instance GHC.Classes.Eq Foundation.String.ASCII.AsciiString instance GHC.Base.Monoid Foundation.String.ASCII.AsciiString instance GHC.Show.Show Foundation.String.ASCII.AsciiString instance Data.String.IsString Foundation.String.ASCII.AsciiString instance GHC.Exts.IsList Foundation.String.ASCII.AsciiString instance Foundation.Collection.InnerFunctor.InnerFunctor Foundation.String.ASCII.AsciiString instance Foundation.Collection.Collection.Collection Foundation.String.ASCII.AsciiString instance Foundation.Collection.Sequential.Sequential Foundation.String.ASCII.AsciiString instance Foundation.Collection.Zippable.Zippable Foundation.String.ASCII.AsciiString -- | 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 ChunkedUArray ty 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 -- | IPv4 data type module Foundation.Network.IPv4 -- | IPv4 data type data IPv4 -- | "0.0.0.0" any :: IPv4 -- | "127.0.0.1" loopback :: IPv4 fromString :: IsString a => String -> a toString :: IPv4 -> String fromTuple :: (Word8, Word8, Word8, Word8) -> IPv4 toTuple :: IPv4 -> (Word8, Word8, Word8, Word8) -- | Parse a IPv4 address ipv4Parser :: (Sequential input, Element input ~ Char) => Parser input IPv4 instance Foundation.Hashing.Hashable.Hashable Foundation.Network.IPv4.IPv4 instance GHC.Classes.Ord Foundation.Network.IPv4.IPv4 instance GHC.Classes.Eq Foundation.Network.IPv4.IPv4 instance GHC.Show.Show Foundation.Network.IPv4.IPv4 instance Foundation.Primitive.NormalForm.NormalForm Foundation.Network.IPv4.IPv4 instance Data.String.IsString Foundation.Network.IPv4.IPv4 instance Foundation.Class.Storable.Storable Foundation.Network.IPv4.IPv4 instance Foundation.Class.Storable.StorableFixed Foundation.Network.IPv4.IPv4 -- | IPv6 data type module Foundation.Network.IPv6 -- | IPv6 data type data IPv6 -- | equivalent to `::` any :: IPv6 -- | equivalent to `::1` loopback :: IPv6 fromString :: IsString a => String -> a -- | serialise to human readable IPv6 -- --
--   >>> 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. -- -- ipv6ParserPreferred :: (Sequential input, Element input ~ Char) => Parser input IPv6 -- | IPv6 parser as described in RFC4291 section 2.2.2 -- -- The use of "::" indicates one or more groups of 16 bits of zeros. The -- "::" can only appear once in an address. The "::" can also be used to -- compress leading or trailing zeros in an address. -- -- ipv6ParserCompressed :: (Sequential input, Element input ~ Char) => Parser input IPv6 -- | IPv6 address with embedded IPv4 address -- -- when dealing with a mixed environment of IPv4 and IPv6 nodes is -- x:x:x:x:x:x:d.d.d.d, where the xs are the hexadecimal values -- of the six high-order 16-bit pieces of the address, and the -- ds are the decimal values of the four low-order 8-bit pieces -- of the address (standard IPv4 representation). -- -- ipv6ParserIpv4Embedded :: (Sequential input, Element input ~ Char) => Parser input IPv6 instance GHC.Classes.Ord Foundation.Network.IPv6.IPv6 instance GHC.Classes.Eq Foundation.Network.IPv6.IPv6 instance Foundation.Primitive.NormalForm.NormalForm Foundation.Network.IPv6.IPv6 instance Foundation.Hashing.Hashable.Hashable Foundation.Network.IPv6.IPv6 instance GHC.Show.Show Foundation.Network.IPv6.IPv6 instance Data.String.IsString Foundation.Network.IPv6.IPv6 instance Foundation.Class.Storable.Storable Foundation.Network.IPv6.IPv6 instance Foundation.Class.Storable.StorableFixed Foundation.Network.IPv6.IPv6 module Foundation.UUID data UUID UUID :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> UUID nil :: UUID fromBinary :: UArray Word8 -> Maybe UUID instance GHC.Classes.Ord Foundation.UUID.UUID instance GHC.Classes.Eq Foundation.UUID.UUID instance GHC.Show.Show Foundation.UUID.UUID instance Foundation.Primitive.NormalForm.NormalForm Foundation.UUID.UUID instance Foundation.Hashing.Hashable.Hashable Foundation.UUID.UUID instance Foundation.Class.Storable.Storable Foundation.UUID.UUID instance Foundation.Class.Storable.StorableFixed Foundation.UUID.UUID module Foundation.Hashing -- | Type with the ability to be hashed -- -- Hashable doesn't have any specific rules, and it's made for raw speed. -- More specifically don't expect different type representing the same -- data to hash to the same value -- --
--   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: -- -- module Foundation.Random -- | A monad constraint that allows to generate random bytes class (Functor m, Applicative m, Monad m) => MonadRandom m getRandomBytes :: MonadRandom m => Size Word8 -> m (UArray Word8) -- | A simple Monad class very similar to a State Monad with the state -- being a RandomGenerator. newtype MonadRandomState gen a MonadRandomState :: (gen -> (a, gen)) -> MonadRandomState gen a [runRandomState] :: MonadRandomState gen a -> gen -> (a, gen) -- | A Deterministic Random Generator (DRG) class class RandomGen gen -- | Initialize a new random generator randomNew :: (RandomGen gen, MonadRandom m) => m gen -- | Initialize a new random generator from a binary seed. -- -- If Nothing is returned, then the data is not acceptable for -- creating a new random generator. randomNewFrom :: RandomGen gen => UArray Word8 -> Maybe gen -- | Generate N bytes of randomness from a DRG randomGenerate :: RandomGen gen => Size Word8 -> gen -> (UArray Word8, gen) getRandomPrimType :: forall randomly ty. (PrimType ty, MonadRandom randomly) => randomly ty -- | Run a pure computation with a Random Generator in the -- MonadRandomState withRandomGenerator :: RandomGen gen => gen -> MonadRandomState gen a -> (a, gen) -- | An alias to the default choice of deterministic random number -- generator -- -- Unless, you want to have the stability of a specific random number -- generator, e.g. for tests purpose, it's recommended to use this alias -- so that you would keep up to date with possible bugfixes, or change of -- algorithms. type RNG = RNGv1 -- | RNG based on ChaCha core. -- -- The algorithm is identical to the arc4random found in recent BSDs, -- namely a ChaCha core provide 64 bytes of random from 32 bytes of key. data RNGv1 instance Foundation.Random.MonadRandom GHC.Types.IO instance GHC.Base.Functor (Foundation.Random.MonadRandomState gen) instance GHC.Base.Applicative (Foundation.Random.MonadRandomState gen) instance GHC.Base.Monad (Foundation.Random.MonadRandomState gen) instance Foundation.Random.RandomGen gen => Foundation.Random.MonadRandom (Foundation.Random.MonadRandomState gen) instance Foundation.Random.RandomGen Foundation.Random.RNGv1 module Foundation.Check -- | Generator monad data Gen a -- | How to generate an arbitrary value for a class Arbitrary a arbitrary :: Arbitrary a => Gen a oneof :: NonEmpty [Gen a] -> Gen a elements :: NonEmpty [a] -> Gen a -- | Call one of the generator weighted frequency :: NonEmpty [(Word, Gen a)] -> Gen a between :: (Word, Word) -> Gen Word data Test [Unit] :: String -> IO () -> Test [Property] :: IsProperty prop => String -> prop -> Test [Group] :: String -> [Test] -> Test -- | Name of a test testName :: Test -> String -- | The type of check this test did for a property data PropertyCheck data Property Prop :: Gen PropertyTestArg -> Property [unProp] :: Property -> Gen PropertyTestArg class IsProperty p property :: IsProperty p => p -> Property (===) :: (Show a, Eq a) => a -> a -> PropertyCheck infix 4 === propertyCompare :: Show a => String -> (a -> a -> Bool) -> a -> a -> PropertyCheck propertyAnd :: PropertyCheck -> PropertyCheck -> PropertyCheck propertyFail :: String -> PropertyCheck forAll :: (Show a, IsProperty prop) => Gen a -> (a -> prop) -> Property -- | Run tests defaultMain :: Test -> IO () instance GHC.Show.Show Foundation.Check.TestResult instance GHC.Classes.Eq Foundation.Check.PropertyResult instance GHC.Show.Show Foundation.Check.PropertyResult -- | # 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 ("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: -- -- 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 () -- | A handle managing input from the Haskell program's standard input -- channel. stdin :: Handle -- | A handle managing output to the Haskell program's standard output -- channel. stdout :: Handle -- | 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) hPut :: Handle -> (UArray Word8) -> IO () -- | 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 -- | 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 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. -- --

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 -- | 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: -- -- -- -- 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 -- | Use the Show class to create a String. -- -- Note that this is not efficient, since an intermediate [Char] is going -- to be created before turning into a real String. show :: Show a => a -> String -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: Ord a => a -> a -> Ordering (<) :: Ord a => a -> a -> Bool (<=) :: Ord a => a -> a -> Bool (>) :: Ord a => a -> a -> Bool (>=) :: Ord a => a -> a -> Bool max :: Ord a => a -> a -> a min :: Ord a => 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 (==) :: Eq a => a -> a -> Bool (/=) :: Eq a => 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 :: Bounded a => a maxBound :: Bounded a => 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 :: 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 idid
--   
-- -- If you supply first and second, ensure: -- --
--   first idid
--   second idid
--   
-- -- 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. -- --
--   secondbimap id
--   
second :: Bifunctor p => (b -> c) -> p a b -> p a c -- | 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 :: Applicative f => a -> f a -- | Sequential application. (<*>) :: Applicative f => f (a -> b) -> f a -> f b -- | Sequence actions, discarding the value of the first argument. (*>) :: Applicative f => f a -> f b -> f b -- | Sequence actions, discarding the value of the second argument. (<*) :: Applicative f => 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. (>>=) :: Monad m => 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. (>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => 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 :: Monad m => 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 :: IsString a => 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 :: IsList l => [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 :: IsList l => Int -> [Item l] -> l -- | The toList function extracts a list of Item l from the -- structure l. It should satisfy fromList . toList = id. toList :: IsList l => 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 (Enum a, Eq a, Ord a, Integral a) => IsIntegral a toInteger :: IsIntegral a => a -> Integer -- | Non Negative Number literals, convertible through the generic Natural -- type class (Enum a, Eq a, Ord a, Integral a, IsIntegral a) => IsNatural a toNatural :: IsNatural a => a -> Natural -- | types that have sign and can be made absolute class 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. -- --
--   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"). -- --

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 :: * -- | 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 :: * -- | Size of a data structure. -- -- More specifically, it represents the number of elements of type -- ty that fit into the data structure. -- --
--   >>> lengthSize (fromList ['a', 'b', 'c', '🌟']) :: Size Char
--   Size 4
--   
-- -- Same caveats as Offset apply here. newtype Size ty Size :: Int -> Size 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: -- -- -- -- 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 :: Monoid a => a -- | An associative operation mappend :: Monoid a => 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 :: Monoid a => [a] -> a -- | An infix synonym for mappend. (<>) :: Monoid m => m -> m -> m infixr 6 <> -- | 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 -> Int -- | 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 -- | 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 -- | 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 -- | 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 => Word -> 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 -- | 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. -- --

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