-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Foundation scrap box of array & string -- -- Foundation most basic primitives without any dependencies @package basement @version 0.0.2 -- | conveniently provide support for legacy and modern base module Basement.Compat.Typeable -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable k (a :: k) module Basement.Compat.PrimTypes -- | File size in bytes type FileSize# = Word64# -- | Offset in a bytearray, string, type alias -- -- for code documentation purpose only, just a simple type alias on Int# type Offset# = Int# -- | CountOf in bytes type alias -- -- for code documentation purpose only, just a simple type alias on Int# type CountOf# = Int# -- | Lowlevel Boolean type Bool# = Int# -- | Pinning status type Pinned# = Bool# module Basement.Compat.Primitive -- | turn an Int# into a Bool -- -- Since GHC 7.8, boolean primitive don't return Bool but Int#. bool# :: Int# -> Bool -- | Flag record whether a specific byte array is pinned or not data PinnedStatus Pinned :: PinnedStatus Unpinned :: PinnedStatus toPinnedStatus# :: Pinned# -> PinnedStatus -- | A version friendly of andI# compatAndI# :: Int# -> Int# -> Int# -- | A version friendly of quotRemInt# compatQuotRemInt# :: Int# -> Int# -> (# Int#, Int# #) -- | A version friendly fo copyAddrToByteArray# -- -- only available from GHC 7.8 compatCopyAddrToByteArray# :: Addr# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s -- | A version friendly fo copyByteArrayToAddr# -- -- only available from GHC 7.8 compatCopyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# s -> State# s -- | A mkWeak# version that keep working on 8.0 -- -- signature change in ghc-prim: * 0.4: mkWeak RealWorld -> ( -- RealWorld, Weak) * 0.5 :mkWeak RealWorld -> ( RealWorld, c -- RealWorld -> ( RealWorld, Weak) compatMkWeak# :: o -> b -> IO () -> State# RealWorld -> (# State# RealWorld, Weak# b #) compatGetSizeofMutableByteArray# :: MutableByteArray# s -> State# s -> (# State# s, Int# #) compatShrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) compatResizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, MutableByteArray# s #) compatIsByteArrayPinned# :: ByteArray# -> Pinned# compatIsMutableByteArrayPinned# :: MutableByteArray# s -> Pinned# -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * W# :: Word# -> Word instance GHC.Classes.Eq Basement.Compat.Primitive.PinnedStatus module Basement.Compat.Natural -- | Type representing arbitrary-precision non-negative integers. -- -- Operations whose result would be negative throw -- (Underflow :: ArithException). data Natural :: * integerToNatural :: Integer -> Natural naturalToInteger :: Natural -> Integer -- | Literal support for Integral and Fractional module Basement.Compat.NumLiteral -- | 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 instance Basement.Compat.NumLiteral.Integral GHC.Integer.Type.Integer instance Basement.Compat.NumLiteral.Integral GHC.Natural.Natural instance Basement.Compat.NumLiteral.Integral GHC.Types.Int instance Basement.Compat.NumLiteral.Integral GHC.Types.Word instance Basement.Compat.NumLiteral.Integral GHC.Word.Word8 instance Basement.Compat.NumLiteral.Integral GHC.Word.Word16 instance Basement.Compat.NumLiteral.Integral GHC.Word.Word32 instance Basement.Compat.NumLiteral.Integral GHC.Word.Word64 instance Basement.Compat.NumLiteral.Integral GHC.Int.Int8 instance Basement.Compat.NumLiteral.Integral GHC.Int.Int16 instance Basement.Compat.NumLiteral.Integral GHC.Int.Int32 instance Basement.Compat.NumLiteral.Integral GHC.Int.Int64 instance Basement.Compat.NumLiteral.Integral Foreign.C.Types.CSize instance Basement.Compat.NumLiteral.Integral Foreign.C.Types.CInt instance Basement.Compat.NumLiteral.Integral System.Posix.Types.COff instance Basement.Compat.NumLiteral.Integral Foreign.C.Types.CUIntPtr instance Basement.Compat.NumLiteral.Integral GHC.Types.Float instance Basement.Compat.NumLiteral.Integral GHC.Types.Double instance Basement.Compat.NumLiteral.Integral Foreign.C.Types.CFloat instance Basement.Compat.NumLiteral.Integral Foreign.C.Types.CDouble instance Basement.Compat.NumLiteral.HasNegation GHC.Integer.Type.Integer instance Basement.Compat.NumLiteral.HasNegation GHC.Types.Int instance Basement.Compat.NumLiteral.HasNegation GHC.Int.Int8 instance Basement.Compat.NumLiteral.HasNegation GHC.Int.Int16 instance Basement.Compat.NumLiteral.HasNegation GHC.Int.Int32 instance Basement.Compat.NumLiteral.HasNegation GHC.Int.Int64 instance Basement.Compat.NumLiteral.HasNegation GHC.Types.Word instance Basement.Compat.NumLiteral.HasNegation GHC.Word.Word8 instance Basement.Compat.NumLiteral.HasNegation GHC.Word.Word16 instance Basement.Compat.NumLiteral.HasNegation GHC.Word.Word32 instance Basement.Compat.NumLiteral.HasNegation GHC.Word.Word64 instance Basement.Compat.NumLiteral.HasNegation Foreign.C.Types.CInt instance Basement.Compat.NumLiteral.HasNegation GHC.Types.Float instance Basement.Compat.NumLiteral.HasNegation GHC.Types.Double instance Basement.Compat.NumLiteral.HasNegation Foreign.C.Types.CFloat instance Basement.Compat.NumLiteral.HasNegation Foreign.C.Types.CDouble instance Basement.Compat.NumLiteral.Fractional GHC.Real.Rational instance Basement.Compat.NumLiteral.Fractional GHC.Types.Float instance Basement.Compat.NumLiteral.Fractional GHC.Types.Double instance Basement.Compat.NumLiteral.Fractional Foreign.C.Types.CFloat instance Basement.Compat.NumLiteral.Fractional Foreign.C.Types.CDouble -- | compat friendly version of IsList module Basement.Compat.IsList -- | 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] -- | Identity re-export, with a compat wrapper for older version of base -- that do not have Data.Functor.Identity module Basement.Compat.Identity -- | Identity functor and monad. (a non-strict monad) newtype Identity a :: * -> * Identity :: a -> Identity a [runIdentity] :: Identity a -> a module Basement.Compat.CallStack -- | Request a CallStack. -- -- NOTE: The implicit parameter ?callStack :: CallStack is an -- implementation detail and should not be considered part of the -- CallStack API, we may decide to change the implementation in -- the future. type HasCallStack = ?callStack :: CallStack -- | 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 Basement.Compat.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 -- | internal re-export of all the good base bits module Basement.Compat.Base -- | 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 -- | 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 <$> -- | 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 -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | the identity morphism id :: Category k cat => forall (a :: k). cat a a -- | The maybe function takes a default value, a function, and a -- Maybe value. If the Maybe value is Nothing, the -- function returns the default value. Otherwise, it applies the function -- to the value inside the Just and returns the result. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybe False odd (Just 3)
--   True
--   
-- --
--   >>> maybe False odd Nothing
--   False
--   
-- -- Read an integer from a string using readMaybe. If we succeed, -- return twice the integer; that is, apply (*2) to it. If -- instead we fail to parse an integer, return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> maybe 0 (*2) (readMaybe "5")
--   10
--   
--   >>> maybe 0 (*2) (readMaybe "")
--   0
--   
-- -- Apply show to a Maybe Int. If we have Just -- n, we want to show the underlying Int n. But if -- we have Nothing, we return the empty string instead of (for -- example) "Nothing": -- --
--   >>> maybe "" show (Just 5)
--   "5"
--   
--   >>> maybe "" show Nothing
--   ""
--   
maybe :: b -> (a -> b) -> Maybe a -> b -- | Case analysis for the Either type. If the value is -- Left a, apply the first function to a; if it -- is Right b, apply the second function to b. -- --

Examples

-- -- We create two values of type Either String -- Int, one using the Left constructor and another -- using the Right constructor. Then we apply "either" the -- length function (if we have a String) or the -- "times-two" function (if we have an Int): -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> either length (*2) s
--   3
--   
--   >>> either length (*2) n
--   6
--   
either :: (a -> c) -> (b -> c) -> Either a b -> c -- | flip f takes its (first) two arguments in the reverse -- order of f. flip :: (a -> b -> c) -> b -> a -> c -- | const x is a unary function which evaluates to x for -- all inputs. -- -- For instance, -- --
--   >>> map (const 42) [0..3]
--   [42,42,42,42]
--   
const :: a -> b -> a -- | error stops execution and displays an error message. error :: HasCallStack => [Char] -> a -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: HasCallStack => a -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. seq is usually introduced to -- improve performance by avoiding unneeded laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: a -> b -> b -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a -- | Convert a value to a readable String. -- -- showsPrec should satisfy the law -- --
--   showsPrec d x r ++ s  ==  showsPrec d x (r ++ s)
--   
-- -- Derived instances of Read and Show satisfy the -- following: -- -- -- -- That is, readsPrec parses the string produced by -- showsPrec, and delivers the value that showsPrec started -- with. showsPrec :: Show a => Int -> a -> ShowS -- | A specialised variant of showsPrec, using precedence context -- zero, and returning an ordinary String. show :: Show a => a -> String -- | The method showList is provided to allow the programmer to give -- a specialised way of showing lists of values. For example, this is -- used by the predefined Show instance of the Char type, -- where values of type String should be shown in double quotes, -- rather than between square brackets. showList :: Show a => [a] -> ShowS -- | The Ord class is used for totally ordered datatypes. -- -- Instances of Ord can be derived for any user-defined datatype -- whose constituent types are in Ord. The declared order of the -- constructors in the data declaration determines the ordering in -- derived Ord instances. The Ordering datatype allows a -- single comparison to determine the precise ordering of two objects. -- -- Minimal complete definition: either compare or <=. -- Using compare can be more efficient for complex types. class Eq a => Ord a compare :: 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 -- | 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 -- | 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 -- | 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 :: * -- | 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 :: * -- | 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 -- | 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 :: * -- | 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 :: * -- | 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 :: * -- | 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 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] -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a -- | Representable types of kind *. This class is derivable in GHC with the -- DeriveGeneric flag on. class Generic 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 -- | The Data class comprehends a fundamental primitive -- gfoldl for folding over constructor applications, say terms. -- This primitive can be instantiated in several ways to map over the -- immediate subterms of a term; see the gmap combinators later -- in this class. Indeed, a generic programmer does not necessarily need -- to use the ingenious gfoldl primitive but rather the intuitive -- gmap combinators. The gfoldl primitive is completed by -- means to query top-level constructors, to turn constructor -- representations into proper terms, and to list all possible datatype -- constructors. This completion allows us to serve generic programming -- scenarios like read, show, equality, term generation. -- -- The combinators gmapT, gmapQ, gmapM, etc are all -- provided with default definitions in terms of gfoldl, leaving -- open the opportunity to provide datatype-specific definitions. (The -- inclusion of the gmap combinators as members of class -- Data allows the programmer or the compiler to derive -- specialised, and maybe more efficient code per datatype. Note: -- gfoldl is more higher-order than the gmap combinators. -- This is subject to ongoing benchmarking experiments. It might turn out -- that the gmap combinators will be moved out of the class -- Data.) -- -- Conceptually, the definition of the gmap combinators in terms -- of the primitive gfoldl requires the identification of the -- gfoldl function arguments. Technically, we also need to -- identify the type constructor c for the construction of the -- result type from the folded term type. -- -- In the definition of gmapQx combinators, we use -- phantom type constructors for the c in the type of -- gfoldl because the result type of a query does not involve the -- (polymorphic) type of the term argument. In the definition of -- gmapQl we simply use the plain constant type constructor -- because gfoldl is left-associative anyway and so it is readily -- suited to fold a left-associative binary operation over the immediate -- subterms. In the definition of gmapQr, extra effort is needed. We use -- a higher-order accumulation trick to mediate between left-associative -- constructor application vs. right-associative binary operation (e.g., -- (:)). When the query is meant to compute a value of type -- r, then the result type withing generic folding is r -- -> r. So the result of folding is a function to which we -- finally pass the right unit. -- -- With the -XDeriveDataTypeable option, GHC can generate -- instances of the Data class automatically. For example, given -- the declaration -- --
--   data T a b = C1 a b | C2 deriving (Typeable, Data)
--   
-- -- GHC will generate an instance that is equivalent to -- --
--   instance (Data a, Data b) => Data (T a b) where
--       gfoldl k z (C1 a b) = z C1 `k` a `k` b
--       gfoldl k z C2       = z C2
--   
--       gunfold k z c = case constrIndex c of
--                           1 -> k (k (z C1))
--                           2 -> z C2
--   
--       toConstr (C1 _ _) = con_C1
--       toConstr C2       = con_C2
--   
--       dataTypeOf _ = ty_T
--   
--   con_C1 = mkConstr ty_T "C1" [] Prefix
--   con_C2 = mkConstr ty_T "C2" [] Prefix
--   ty_T   = mkDataType "Module.T" [con_C1, con_C2]
--   
-- -- This is suitable for datatypes that are exported transparently. class Typeable * a => Data a -- | Left-associative fold operation for constructor applications. -- -- The type of gfoldl is a headache, but operationally it is a -- simple generalisation of a list fold. -- -- The default definition for gfoldl is const -- id, which is suitable for abstract datatypes with no -- substructures. gfoldl :: Data a => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a -- | Unfolding constructor applications gunfold :: Data a => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a -- | Obtaining the constructor from a given datum. For proper terms, this -- is meant to be the top-level constructor. Primitive datatypes are here -- viewed as potentially infinite sets of values (i.e., constructors). toConstr :: Data a => a -> Constr -- | The outer type constructor of the type dataTypeOf :: Data a => a -> DataType -- | Mediate types and unary type constructors. In Data instances of -- the form T a, dataCast1 should be defined as -- gcast1. -- -- The default definition is const Nothing, which -- is appropriate for non-unary type constructors. dataCast1 :: (Data a, Typeable (* -> *) t) => (forall d. Data d => c (t d)) -> Maybe (c a) -- | Mediate types and binary type constructors. In Data instances -- of the form T a b, dataCast2 should be defined as -- gcast2. -- -- The default definition is const Nothing, which -- is appropriate for non-binary type constructors. dataCast2 :: (Data a, Typeable (* -> * -> *) t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) -- | A generic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to an identity datatype constructor, using -- the isomorphism pair as injection and projection. gmapT :: Data a => (forall b. Data b => b -> b) -> a -> a -- | A generic query with a left-associative binary operator gmapQl :: Data a => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query with a right-associative binary operator gmapQr :: Data a => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query that processes the immediate subterms and returns a -- list of results. The list is given in the same order as originally -- specified in the declaration of the data constructors. gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] -- | A generic query that processes one child by index (zero-based) gmapQi :: Data a => Int -> (forall d. Data d => d -> u) -> a -> u -- | A generic monadic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to the monad datatype constructor, defining -- injection and projection using return and >>=. gmapM :: (Data a, Monad m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of at least one immediate subterm does not fail gmapMp :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of one immediate subterm with success gmapMo :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Constructs a non-representation for a non-representable type mkNoRepType :: String -> DataType -- | Representation of datatypes. A package of constructor representations -- with names of type and module. data DataType :: * -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable k (a :: k) -- | 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 <> -- | 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 -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | A variant of throw that can only be used within the IO -- monad. -- -- Although throwIO has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
--   throw e   `seq` x  ===> throw e
--   throwIO e `seq` x  ===> x
--   
-- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | 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 :: * -> * Ptr :: Addr# -> Ptr a -- | for support of if .. then .. else ifThenElse :: Bool -> a -> a -> a -- | Only to use internally for internal error cases internalError :: [Char] -> a -- | An internal and really simple monad transformers, without any bells -- and whistse. module Basement.Compat.MonadTrans -- | Simple State monad newtype State s m a State :: (s -> m (a, s)) -> State s m a [runState] :: State s m a -> s -> m (a, s) -- | Simple Reader monad newtype Reader r m a Reader :: (r -> m a) -> Reader r m a [runReader] :: Reader r m a -> r -> m a instance GHC.Base.Monad m => GHC.Base.Functor (Basement.Compat.MonadTrans.State s m) instance GHC.Base.Monad m => GHC.Base.Applicative (Basement.Compat.MonadTrans.State s m) instance GHC.Base.Monad m => GHC.Base.Monad (Basement.Compat.MonadTrans.State r m) instance GHC.Base.Monad m => GHC.Base.Functor (Basement.Compat.MonadTrans.Reader r m) instance GHC.Base.Monad m => GHC.Base.Applicative (Basement.Compat.MonadTrans.Reader r m) instance GHC.Base.Monad m => GHC.Base.Monad (Basement.Compat.MonadTrans.Reader r m) -- | Set endianness tag to a given primitive. This will help for -- serialising data for protocols (such as the network protocols). module Basement.Endianness -- | Class of types that can be byte-swapped. -- -- e.g. Word16, Word32, Word64 class ByteSwap 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 -- | 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 data Endianness LittleEndian :: Endianness BigEndian :: Endianness -- | endianness of the current architecture endianness :: Endianness instance Data.Bits.Bits a => Data.Bits.Bits (Basement.Endianness.BE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Basement.Endianness.BE a) instance GHC.Show.Show a => GHC.Show.Show (Basement.Endianness.BE a) instance Data.Bits.Bits a => Data.Bits.Bits (Basement.Endianness.LE a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Basement.Endianness.LE a) instance GHC.Show.Show a => GHC.Show.Show (Basement.Endianness.LE a) instance GHC.Show.Show Basement.Endianness.Endianness instance GHC.Classes.Eq Basement.Endianness.Endianness instance (Basement.Endianness.ByteSwap a, GHC.Classes.Ord a) => GHC.Classes.Ord (Basement.Endianness.LE a) instance (Basement.Endianness.ByteSwap a, GHC.Classes.Ord a) => GHC.Classes.Ord (Basement.Endianness.BE a) instance Basement.Endianness.ByteSwap GHC.Word.Word16 instance Basement.Endianness.ByteSwap GHC.Word.Word32 instance Basement.Endianness.ByteSwap GHC.Word.Word64 module Basement.Floating integerToDouble :: Integer -> Double naturalToDouble :: Natural -> Double doubleExponant :: Double -> Int -> Double integerToFloat :: Integer -> Float naturalToFloat :: Natural -> Float -- | Allow to run operation in ST and IO, without having to distinguinsh -- between the two. Most operations exposes the bare nuts and bolts of -- how IO and ST actually works, and relatively easy to shoot yourself in -- the foot -- -- this is highly similar to the Control.Monad.Primitive in the primitive -- package module Basement.Monad -- | 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 () -- | 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 () -- | just like unwrapPrimMonad but throw away the result and -- return just the new State# unPrimMonad_ :: PrimMonad m => m () -> State# (PrimState m) -> State# (PrimState m) -- | Convert a prim monad to another prim monad. -- -- The net effect is that it coerce the state repr to another, so the -- runtime representation should be the same, otherwise hilary ensues. unsafePrimCast :: (PrimMonad m1, PrimMonad m2) => m1 a -> m2 a -- | Convert any prim monad to an ST monad unsafePrimToST :: PrimMonad prim => prim a -> ST s a -- | Convert any prim monad to an IO monad unsafePrimToIO :: PrimMonad prim => prim a -> IO a -- | Convert any IO monad to a prim monad unsafePrimFromIO :: PrimMonad prim => IO a -> prim a -- | Touch primitive lifted to any prim monad primTouch :: PrimMonad m => a -> m () instance Basement.Monad.PrimMonad GHC.Types.IO instance Basement.Monad.PrimMonad (GHC.ST.ST s) instance Basement.Monad.MonadFailure GHC.Base.Maybe instance Basement.Monad.MonadFailure (Data.Either.Either a) -- | A smaller ForeignPtr reimplementation that work in any prim monad. -- -- Here be dragon. module Basement.FinalPtr -- | 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 touchFinalPtr :: PrimMonad prim => FinalPtr p -> prim () -- | 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 instance GHC.Show.Show (Basement.FinalPtr.FinalPtr a) instance GHC.Classes.Eq (Basement.FinalPtr.FinalPtr a) instance GHC.Classes.Ord (Basement.FinalPtr.FinalPtr a) module Basement.Numerical.Number -- | 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 instance Basement.Numerical.Number.IsIntegral GHC.Integer.Type.Integer instance Basement.Numerical.Number.IsIntegral GHC.Types.Int instance Basement.Numerical.Number.IsIntegral GHC.Int.Int8 instance Basement.Numerical.Number.IsIntegral GHC.Int.Int16 instance Basement.Numerical.Number.IsIntegral GHC.Int.Int32 instance Basement.Numerical.Number.IsIntegral GHC.Int.Int64 instance Basement.Numerical.Number.IsIntegral GHC.Natural.Natural instance Basement.Numerical.Number.IsIntegral GHC.Types.Word instance Basement.Numerical.Number.IsIntegral GHC.Word.Word8 instance Basement.Numerical.Number.IsIntegral GHC.Word.Word16 instance Basement.Numerical.Number.IsIntegral GHC.Word.Word32 instance Basement.Numerical.Number.IsIntegral GHC.Word.Word64 instance Basement.Numerical.Number.IsIntegral Foreign.C.Types.CSize instance Basement.Numerical.Number.IsNatural GHC.Natural.Natural instance Basement.Numerical.Number.IsNatural GHC.Types.Word instance Basement.Numerical.Number.IsNatural GHC.Word.Word8 instance Basement.Numerical.Number.IsNatural GHC.Word.Word16 instance Basement.Numerical.Number.IsNatural GHC.Word.Word32 instance Basement.Numerical.Number.IsNatural GHC.Word.Word64 instance Basement.Numerical.Number.IsNatural Foreign.C.Types.CSize module Basement.IntegralConv -- | 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 -- | 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 -- | 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 intToInt64 :: Int -> Int64 int64ToInt :: Int64 -> Int wordToWord64 :: Word -> Word64 word64ToWord32s :: Word64 -> Word32x2 -- | 2 Word32s data Word32x2 Word32x2 :: {-# UNPACK #-} !Word32 -> {-# UNPACK #-} !Word32 -> Word32x2 word64ToWord :: Word64 -> Word wordToChar :: Word -> Char wordToInt :: Word -> Int charToInt :: Char -> Int instance Basement.Numerical.Number.IsIntegral a => Basement.IntegralConv.IntegralUpsize a GHC.Integer.Type.Integer instance Basement.Numerical.Number.IsNatural a => Basement.IntegralConv.IntegralUpsize a GHC.Natural.Natural instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int8 GHC.Int.Int16 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int8 GHC.Int.Int32 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int8 GHC.Int.Int64 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int8 GHC.Types.Int instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int16 GHC.Int.Int32 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int16 GHC.Int.Int64 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int16 GHC.Types.Int instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int32 GHC.Int.Int64 instance Basement.IntegralConv.IntegralUpsize GHC.Int.Int32 GHC.Types.Int instance Basement.IntegralConv.IntegralUpsize GHC.Types.Int GHC.Int.Int64 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Word.Word16 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Word.Word32 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Word.Word64 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Types.Word instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Int.Int16 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Int.Int32 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Int.Int64 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word8 GHC.Types.Int instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word16 GHC.Word.Word32 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word16 GHC.Word.Word64 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word16 GHC.Types.Word instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word32 GHC.Word.Word64 instance Basement.IntegralConv.IntegralUpsize GHC.Word.Word32 GHC.Types.Word instance Basement.IntegralConv.IntegralUpsize GHC.Types.Word GHC.Word.Word64 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Int GHC.Int.Int8 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Int GHC.Int.Int16 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Int GHC.Int.Int32 instance Basement.IntegralConv.IntegralDownsize GHC.Int.Int64 GHC.Int.Int8 instance Basement.IntegralConv.IntegralDownsize GHC.Int.Int64 GHC.Int.Int16 instance Basement.IntegralConv.IntegralDownsize GHC.Int.Int64 GHC.Int.Int32 instance Basement.IntegralConv.IntegralDownsize GHC.Int.Int64 GHC.Types.Int instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word64 GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word64 GHC.Word.Word16 instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word64 GHC.Word.Word32 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Word GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Word GHC.Word.Word16 instance Basement.IntegralConv.IntegralDownsize GHC.Types.Word GHC.Word.Word32 instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word32 GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word32 GHC.Word.Word16 instance Basement.IntegralConv.IntegralDownsize GHC.Word.Word16 GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Int.Int8 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Int.Int16 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Int.Int32 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Int.Int64 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Word.Word16 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Word.Word32 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Word.Word64 instance Basement.IntegralConv.IntegralDownsize GHC.Integer.Type.Integer GHC.Natural.Natural instance Basement.IntegralConv.IntegralDownsize GHC.Natural.Natural GHC.Word.Word8 instance Basement.IntegralConv.IntegralDownsize GHC.Natural.Natural GHC.Word.Word16 instance Basement.IntegralConv.IntegralDownsize GHC.Natural.Natural GHC.Word.Word32 instance Basement.IntegralConv.IntegralDownsize GHC.Natural.Natural GHC.Word.Word64 instance Basement.IntegralConv.IntegralCast GHC.Types.Word GHC.Types.Int instance Basement.IntegralConv.IntegralCast GHC.Types.Int GHC.Types.Word instance Basement.IntegralConv.IntegralCast GHC.Word.Word64 GHC.Int.Int64 instance Basement.IntegralConv.IntegralCast GHC.Int.Int64 GHC.Word.Word64 instance Basement.IntegralConv.IntegralCast GHC.Int.Int8 GHC.Word.Word8 instance Basement.IntegralConv.IntegralCast GHC.Int.Int16 GHC.Word.Word16 instance Basement.IntegralConv.IntegralCast GHC.Int.Int32 GHC.Word.Word32 instance Basement.IntegralConv.IntegralCast GHC.Word.Word8 GHC.Int.Int8 instance Basement.IntegralConv.IntegralCast GHC.Word.Word16 GHC.Int.Int16 instance Basement.IntegralConv.IntegralCast GHC.Word.Word32 GHC.Int.Int32 module Basement.Types.Char7 -- | ASCII value between 0x0 and 0x7f newtype Char7 Char7 :: Word8 -> Char7 [toByte] :: Char7 -> Word8 -- | Convert a Char7 to a unicode code point Char toChar :: Char7 -> Char -- | Convert a Char to a Char7 ignoring all higher bits fromCharMask :: Char -> Char7 -- | Try to convert a Char to a Char7 -- -- If the code point is non ascii, then Nothing is returned. fromChar :: Char -> Maybe Char7 -- | Convert a Byte to a Char7 ignoring the higher bit fromByteMask :: Word8 -> Char7 -- | Try to convert Word8 to a Char7 -- -- If the byte got higher bit set, then Nothing is returned. fromByte :: Word8 -> Maybe Char7 c7_LF :: Char7 c7_CR :: Char7 c7_minus :: Char7 c7_a :: Char7 c7_A :: Char7 c7_z :: Char7 c7_Z :: Char7 c7_0 :: Char7 c7_1 :: Char7 c7_2 :: Char7 c7_3 :: Char7 c7_4 :: Char7 c7_5 :: Char7 c7_6 :: Char7 c7_7 :: Char7 c7_8 :: Char7 c7_9 :: Char7 instance GHC.Classes.Ord Basement.Types.Char7.Char7 instance GHC.Classes.Eq Basement.Types.Char7.Char7 instance GHC.Show.Show Basement.Types.Char7.Char7 module Basement.Types.Word128 -- | 128 bits Word data Word128 Word128 :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Word128 -- | Add 2 Word128 (+) :: Word128 -> Word128 -> Word128 -- | Subtract 2 Word128 (-) :: Word128 -> Word128 -> Word128 -- | Multiplication (*) :: Word128 -> Word128 -> Word128 -- | Division quot :: Word128 -> Word128 -> Word128 -- | Modulo rem :: Word128 -> Word128 -> Word128 -- | Bitwise and bitwiseAnd :: Word128 -> Word128 -> Word128 -- | Bitwise or bitwiseOr :: Word128 -> Word128 -> Word128 -- | Bitwise xor bitwiseXor :: Word128 -> Word128 -> Word128 fromNatural :: Natural -> Word128 instance GHC.Classes.Eq Basement.Types.Word128.Word128 instance GHC.Show.Show Basement.Types.Word128.Word128 instance GHC.Enum.Enum Basement.Types.Word128.Word128 instance GHC.Enum.Bounded Basement.Types.Word128.Word128 instance GHC.Classes.Ord Basement.Types.Word128.Word128 instance Foreign.Storable.Storable Basement.Types.Word128.Word128 instance Basement.Compat.NumLiteral.Integral Basement.Types.Word128.Word128 instance Basement.Compat.NumLiteral.HasNegation Basement.Types.Word128.Word128 instance Basement.Numerical.Number.IsIntegral Basement.Types.Word128.Word128 instance Basement.Numerical.Number.IsNatural Basement.Types.Word128.Word128 instance GHC.Num.Num Basement.Types.Word128.Word128 instance Data.Bits.Bits Basement.Types.Word128.Word128 module Basement.Types.Word256 -- | 256 bits Word data Word256 Word256 :: {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> {-# UNPACK #-} !Word64 -> Word256 -- | Add 2 Word256 (+) :: Word256 -> Word256 -> Word256 -- | Subtract 2 Word256 (-) :: Word256 -> Word256 -> Word256 -- | Multiplication (*) :: Word256 -> Word256 -> Word256 -- | Division quot :: Word256 -> Word256 -> Word256 -- | Modulo rem :: Word256 -> Word256 -> Word256 -- | Bitwise and bitwiseAnd :: Word256 -> Word256 -> Word256 -- | Bitwise or bitwiseOr :: Word256 -> Word256 -> Word256 -- | Bitwise xor bitwiseXor :: Word256 -> Word256 -> Word256 fromNatural :: Natural -> Word256 instance GHC.Classes.Eq Basement.Types.Word256.Word256 instance GHC.Show.Show Basement.Types.Word256.Word256 instance GHC.Enum.Enum Basement.Types.Word256.Word256 instance GHC.Enum.Bounded Basement.Types.Word256.Word256 instance GHC.Classes.Ord Basement.Types.Word256.Word256 instance Foreign.Storable.Storable Basement.Types.Word256.Word256 instance Basement.Compat.NumLiteral.Integral Basement.Types.Word256.Word256 instance Basement.Compat.NumLiteral.HasNegation Basement.Types.Word256.Word256 instance Basement.Numerical.Number.IsIntegral Basement.Types.Word256.Word256 instance Basement.Numerical.Number.IsNatural Basement.Types.Word256.Word256 instance GHC.Num.Num Basement.Types.Word256.Word256 instance Data.Bits.Bits Basement.Types.Word256.Word256 module Basement.Numerical.Additive -- | 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 instance Basement.Numerical.Additive.Additive GHC.Integer.Type.Integer instance Basement.Numerical.Additive.Additive GHC.Types.Int instance Basement.Numerical.Additive.Additive GHC.Int.Int8 instance Basement.Numerical.Additive.Additive GHC.Int.Int16 instance Basement.Numerical.Additive.Additive GHC.Int.Int32 instance Basement.Numerical.Additive.Additive GHC.Int.Int64 instance Basement.Numerical.Additive.Additive GHC.Types.Word instance Basement.Numerical.Additive.Additive GHC.Natural.Natural instance Basement.Numerical.Additive.Additive GHC.Word.Word8 instance Basement.Numerical.Additive.Additive GHC.Word.Word16 instance Basement.Numerical.Additive.Additive GHC.Word.Word32 instance Basement.Numerical.Additive.Additive GHC.Word.Word64 instance Basement.Numerical.Additive.Additive Basement.Types.Word128.Word128 instance Basement.Numerical.Additive.Additive Basement.Types.Word256.Word256 instance Basement.Numerical.Additive.Additive GHC.Types.Float instance Basement.Numerical.Additive.Additive GHC.Types.Double instance Basement.Numerical.Additive.Additive Foreign.C.Types.CSize module Basement.Compat.ExtList -- | Compute the size of the list length :: [a] -> Int null :: [a] -> Bool -- | Sum the element in a list sum :: Additive n => [n] -> n reverse :: [a] -> [a] module Basement.Numerical.Multiplicative -- | 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 recip :: Divisible a => a -> a instance Basement.Numerical.Multiplicative.Multiplicative GHC.Integer.Type.Integer instance Basement.Numerical.Multiplicative.Multiplicative GHC.Types.Int instance Basement.Numerical.Multiplicative.Multiplicative GHC.Int.Int8 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Int.Int16 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Int.Int32 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Int.Int64 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Natural.Natural instance Basement.Numerical.Multiplicative.Multiplicative GHC.Types.Word instance Basement.Numerical.Multiplicative.Multiplicative GHC.Word.Word8 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Word.Word16 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Word.Word32 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Word.Word64 instance Basement.Numerical.Multiplicative.Multiplicative Basement.Types.Word128.Word128 instance Basement.Numerical.Multiplicative.Multiplicative Basement.Types.Word256.Word256 instance Basement.Numerical.Multiplicative.Multiplicative GHC.Types.Float instance Basement.Numerical.Multiplicative.Multiplicative GHC.Types.Double instance Basement.Numerical.Multiplicative.Multiplicative GHC.Real.Rational instance Basement.Numerical.Multiplicative.IDivisible GHC.Integer.Type.Integer instance Basement.Numerical.Multiplicative.IDivisible GHC.Types.Int instance Basement.Numerical.Multiplicative.IDivisible GHC.Int.Int8 instance Basement.Numerical.Multiplicative.IDivisible GHC.Int.Int16 instance Basement.Numerical.Multiplicative.IDivisible GHC.Int.Int32 instance Basement.Numerical.Multiplicative.IDivisible GHC.Int.Int64 instance Basement.Numerical.Multiplicative.IDivisible GHC.Natural.Natural instance Basement.Numerical.Multiplicative.IDivisible GHC.Types.Word instance Basement.Numerical.Multiplicative.IDivisible GHC.Word.Word8 instance Basement.Numerical.Multiplicative.IDivisible GHC.Word.Word16 instance Basement.Numerical.Multiplicative.IDivisible GHC.Word.Word32 instance Basement.Numerical.Multiplicative.IDivisible GHC.Word.Word64 instance Basement.Numerical.Multiplicative.IDivisible Basement.Types.Word128.Word128 instance Basement.Numerical.Multiplicative.IDivisible Basement.Types.Word256.Word256 instance Basement.Numerical.Multiplicative.Divisible GHC.Real.Rational instance Basement.Numerical.Multiplicative.Divisible GHC.Types.Float instance Basement.Numerical.Multiplicative.Divisible GHC.Types.Double module Basement.Numerical.Subtractive -- | 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 instance Basement.Numerical.Subtractive.Subtractive GHC.Integer.Type.Integer instance Basement.Numerical.Subtractive.Subtractive GHC.Types.Int instance Basement.Numerical.Subtractive.Subtractive GHC.Int.Int8 instance Basement.Numerical.Subtractive.Subtractive GHC.Int.Int16 instance Basement.Numerical.Subtractive.Subtractive GHC.Int.Int32 instance Basement.Numerical.Subtractive.Subtractive GHC.Int.Int64 instance Basement.Numerical.Subtractive.Subtractive GHC.Natural.Natural instance Basement.Numerical.Subtractive.Subtractive GHC.Types.Word instance Basement.Numerical.Subtractive.Subtractive GHC.Word.Word8 instance Basement.Numerical.Subtractive.Subtractive GHC.Word.Word16 instance Basement.Numerical.Subtractive.Subtractive GHC.Word.Word32 instance Basement.Numerical.Subtractive.Subtractive GHC.Word.Word64 instance Basement.Numerical.Subtractive.Subtractive Basement.Types.Word128.Word128 instance Basement.Numerical.Subtractive.Subtractive Basement.Types.Word256.Word256 instance Basement.Numerical.Subtractive.Subtractive GHC.Types.Float instance Basement.Numerical.Subtractive.Subtractive GHC.Types.Double instance Basement.Numerical.Subtractive.Subtractive GHC.Types.Char module Basement.Types.OffsetSize -- | File size in bytes newtype FileSize FileSize :: Word64 -> FileSize -- | 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 -- | Offset in bytes used for memory addressing (e.g. in a vector, string, -- ..) type Offset8 = Offset Word8 offsetOfE :: CountOf Word8 -> Offset ty -> Offset8 offsetPlusE :: Offset ty -> CountOf ty -> Offset ty offsetMinusE :: Offset ty -> CountOf ty -> Offset ty offsetRecast :: CountOf Word8 -> CountOf Word8 -> Offset ty -> Offset ty2 offsetCast :: Proxy (a -> b) -> Offset a -> Offset b -- | subtract 2 CountOf values of the same type. -- -- m need to be greater than n, otherwise negative count error ensue use -- the safer (-) version if unsure. offsetSub :: Offset a -> Offset a -> Offset a offsetShiftL :: Int -> Offset ty -> Offset ty2 offsetShiftR :: Int -> Offset ty -> Offset ty2 sizeCast :: Proxy (a -> b) -> CountOf a -> CountOf b sizeLastOffset :: CountOf a -> Offset a sizeAsOffset :: CountOf a -> Offset a -- | subtract 2 CountOf values of the same type. -- -- m need to be greater than n, otherwise negative count error ensue use -- the safer (-) version if unsure. sizeSub :: CountOf a -> CountOf a -> CountOf a -- | alignment need to be a power of 2 countOfRoundUp :: Int -> CountOf ty -> CountOf ty offsetAsSize :: Offset a -> CountOf a (+.) :: Offset ty -> Int -> Offset ty (.==#) :: Offset ty -> CountOf ty -> Bool -- | CountOf of a data structure. -- -- More specifically, it represents the number of elements of type -- ty that fit into the data structure. -- --
--   >>> length (fromList ['a', 'b', 'c', '🌟']) :: CountOf Char
--   CountOf 4
--   
-- -- Same caveats as Offset apply here. newtype CountOf ty CountOf :: Int -> CountOf ty sizeOfE :: CountOf Word8 -> CountOf ty -> CountOf Word8 csizeOfOffset :: Offset8 -> CSize csizeOfSize :: CountOf Word8 -> CSize sizeOfCSSize :: CSsize -> CountOf Word8 sizeOfCSize :: CSize -> CountOf Word8 instance Basement.Compat.NumLiteral.Integral (Basement.Types.OffsetSize.CountOf ty) instance GHC.Enum.Enum (Basement.Types.OffsetSize.CountOf ty) instance GHC.Classes.Ord (Basement.Types.OffsetSize.CountOf ty) instance GHC.Classes.Eq (Basement.Types.OffsetSize.CountOf ty) instance GHC.Show.Show (Basement.Types.OffsetSize.CountOf ty) instance GHC.Num.Num (Basement.Types.OffsetSize.Offset ty) instance Basement.Compat.NumLiteral.Integral (Basement.Types.OffsetSize.Offset ty) instance Basement.Numerical.Additive.Additive (Basement.Types.OffsetSize.Offset ty) instance GHC.Enum.Enum (Basement.Types.OffsetSize.Offset ty) instance GHC.Classes.Ord (Basement.Types.OffsetSize.Offset ty) instance GHC.Classes.Eq (Basement.Types.OffsetSize.Offset ty) instance GHC.Show.Show (Basement.Types.OffsetSize.Offset ty) instance GHC.Classes.Ord Basement.Types.OffsetSize.FileSize instance GHC.Classes.Eq Basement.Types.OffsetSize.FileSize instance GHC.Show.Show Basement.Types.OffsetSize.FileSize instance Basement.Numerical.Number.IsIntegral (Basement.Types.OffsetSize.Offset ty) instance Basement.Numerical.Number.IsNatural (Basement.Types.OffsetSize.Offset ty) instance Basement.Numerical.Subtractive.Subtractive (Basement.Types.OffsetSize.Offset ty) instance Basement.IntegralConv.IntegralCast GHC.Types.Int (Basement.Types.OffsetSize.Offset ty) instance Basement.IntegralConv.IntegralCast GHC.Types.Word (Basement.Types.OffsetSize.Offset ty) instance GHC.Num.Num (Basement.Types.OffsetSize.CountOf ty) instance Basement.Numerical.Number.IsIntegral (Basement.Types.OffsetSize.CountOf ty) instance Basement.Numerical.Number.IsNatural (Basement.Types.OffsetSize.CountOf ty) instance Basement.Numerical.Additive.Additive (Basement.Types.OffsetSize.CountOf ty) instance Basement.Numerical.Subtractive.Subtractive (Basement.Types.OffsetSize.CountOf ty) instance GHC.Base.Monoid (Basement.Types.OffsetSize.CountOf ty) instance Basement.IntegralConv.IntegralCast GHC.Types.Int (Basement.Types.OffsetSize.CountOf ty) instance Basement.IntegralConv.IntegralCast GHC.Types.Word (Basement.Types.OffsetSize.CountOf ty) -- | Common part for vectors module Basement.Exception -- | 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 OutOfBound :: OutOfBoundOperation -> Int -> Int -> OutOfBound -- | The type of operation that triggers an OutOfBound exception. -- -- data OutOfBoundOperation OOB_Read :: OutOfBoundOperation OOB_Write :: OutOfBoundOperation OOB_MemSet :: OutOfBoundOperation OOB_MemCopy :: OutOfBoundOperation OOB_Index :: OutOfBoundOperation isOutOfBound :: Offset ty -> CountOf ty -> Bool outOfBound :: OutOfBoundOperation -> Offset ty -> CountOf ty -> a primOutOfBound :: PrimMonad prim => OutOfBoundOperation -> Offset ty -> CountOf ty -> prim a data InvalidRecast InvalidRecast :: RecastSourceSize -> RecastDestinationSize -> InvalidRecast newtype RecastSourceSize RecastSourceSize :: Int -> RecastSourceSize newtype RecastDestinationSize RecastDestinationSize :: Int -> RecastDestinationSize -- | Exception for using NonEmpty assertion with an empty collection data NonEmptyCollectionIsEmpty NonEmptyCollectionIsEmpty :: NonEmptyCollectionIsEmpty instance GHC.Show.Show Basement.Exception.NonEmptyCollectionIsEmpty instance GHC.Show.Show Basement.Exception.InvalidRecast instance GHC.Classes.Eq Basement.Exception.RecastDestinationSize instance GHC.Show.Show Basement.Exception.RecastDestinationSize instance GHC.Classes.Eq Basement.Exception.RecastSourceSize instance GHC.Show.Show Basement.Exception.RecastSourceSize instance GHC.Show.Show Basement.Exception.OutOfBound instance GHC.Classes.Eq Basement.Exception.OutOfBoundOperation instance GHC.Show.Show Basement.Exception.OutOfBoundOperation instance GHC.Exception.Exception Basement.Exception.OutOfBound instance GHC.Exception.Exception Basement.Exception.InvalidRecast instance GHC.Exception.Exception Basement.Exception.NonEmptyCollectionIsEmpty -- | A newtype wrapper around a non-empty Collection. module Basement.NonEmpty -- | NonEmpty property for any Collection newtype NonEmpty a NonEmpty :: a -> NonEmpty a [getNonEmpty] :: NonEmpty a -> a instance GHC.Classes.Eq a => GHC.Classes.Eq (Basement.NonEmpty.NonEmpty a) instance GHC.Show.Show a => GHC.Show.Show (Basement.NonEmpty.NonEmpty a) instance GHC.Exts.IsList c => GHC.Exts.IsList (Basement.NonEmpty.NonEmpty c) module Basement.MutableBuilder newtype Builder collection mutCollection step state err a Builder :: State (Offset step, BuildingState collection mutCollection step (PrimState state), Maybe err) state a -> Builder collection mutCollection step state err a [runBuilder] :: Builder collection mutCollection step state err a -> State (Offset step, BuildingState collection mutCollection step (PrimState state), Maybe err) state a -- | The in-progress state of a building operation. -- -- The previous buffers are in reverse order, and this contains the -- current buffer and the state of progress packing the elements inside. data BuildingState collection mutCollection step state BuildingState :: [collection] -> !(CountOf step) -> mutCollection state -> !(CountOf step) -> BuildingState collection mutCollection step state [prevChunks] :: BuildingState collection mutCollection step state -> [collection] [prevChunksSize] :: BuildingState collection mutCollection step state -> !(CountOf step) [curChunk] :: BuildingState collection mutCollection step state -> mutCollection state [chunkSize] :: BuildingState collection mutCollection step state -> !(CountOf step) instance GHC.Base.Monad state => GHC.Base.Monad (Basement.MutableBuilder.Builder collection mutCollection step state err) instance GHC.Base.Monad state => GHC.Base.Applicative (Basement.MutableBuilder.Builder collection mutCollection step state err) instance GHC.Base.Monad state => GHC.Base.Functor (Basement.MutableBuilder.Builder collection mutCollection step state err) instance GHC.Base.Monad state => Basement.Monad.MonadFailure (Basement.MutableBuilder.Builder collection mutCollection step state err) module Basement.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. natValNatural :: forall n proxy. KnownNat n => proxy n -> Natural natValCountOf :: forall n ty proxy. (KnownNat n, NatWithinBound (CountOf ty) n) => proxy n -> CountOf ty natValOffset :: forall n ty proxy. (KnownNat n, NatWithinBound (Offset ty) n) => proxy n -> Offset ty 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 module Basement.NormalForm -- | Data that can be fully evaluated in Normal Form class NormalForm a toNormalForm :: NormalForm a => a -> () deepseq :: NormalForm a => a -> b -> b force :: NormalForm a => a -> a instance Basement.NormalForm.NormalForm GHC.Int.Int8 instance Basement.NormalForm.NormalForm GHC.Int.Int16 instance Basement.NormalForm.NormalForm GHC.Int.Int32 instance Basement.NormalForm.NormalForm GHC.Int.Int64 instance Basement.NormalForm.NormalForm GHC.Types.Int instance Basement.NormalForm.NormalForm GHC.Integer.Type.Integer instance Basement.NormalForm.NormalForm GHC.Word.Word8 instance Basement.NormalForm.NormalForm GHC.Word.Word16 instance Basement.NormalForm.NormalForm GHC.Word.Word32 instance Basement.NormalForm.NormalForm GHC.Word.Word64 instance Basement.NormalForm.NormalForm GHC.Types.Word instance Basement.NormalForm.NormalForm GHC.Natural.Natural instance Basement.NormalForm.NormalForm GHC.Types.Float instance Basement.NormalForm.NormalForm GHC.Types.Double instance Basement.NormalForm.NormalForm GHC.Types.Char instance Basement.NormalForm.NormalForm GHC.Types.Bool instance Basement.NormalForm.NormalForm () instance Basement.NormalForm.NormalForm Foreign.C.Types.CChar instance Basement.NormalForm.NormalForm Foreign.C.Types.CUChar instance Basement.NormalForm.NormalForm Foreign.C.Types.CSChar instance Basement.NormalForm.NormalForm Foreign.C.Types.CShort instance Basement.NormalForm.NormalForm Foreign.C.Types.CUShort instance Basement.NormalForm.NormalForm Foreign.C.Types.CInt instance Basement.NormalForm.NormalForm Foreign.C.Types.CUInt instance Basement.NormalForm.NormalForm Foreign.C.Types.CLong instance Basement.NormalForm.NormalForm Foreign.C.Types.CULong instance Basement.NormalForm.NormalForm Foreign.C.Types.CLLong instance Basement.NormalForm.NormalForm Foreign.C.Types.CULLong instance Basement.NormalForm.NormalForm Foreign.C.Types.CFloat instance Basement.NormalForm.NormalForm Foreign.C.Types.CDouble instance Basement.NormalForm.NormalForm (GHC.Ptr.Ptr a) instance Basement.NormalForm.NormalForm (Basement.Types.OffsetSize.Offset a) instance Basement.NormalForm.NormalForm (Basement.Types.OffsetSize.CountOf a) instance Basement.NormalForm.NormalForm Basement.Types.Char7.Char7 instance Basement.NormalForm.NormalForm Basement.Types.Word128.Word128 instance Basement.NormalForm.NormalForm Basement.Types.Word256.Word256 instance Basement.NormalForm.NormalForm a => Basement.NormalForm.NormalForm (GHC.Base.Maybe a) instance (Basement.NormalForm.NormalForm l, Basement.NormalForm.NormalForm r) => Basement.NormalForm.NormalForm (Data.Either.Either l r) instance Basement.NormalForm.NormalForm a => Basement.NormalForm.NormalForm (Basement.Endianness.LE a) instance Basement.NormalForm.NormalForm a => Basement.NormalForm.NormalForm (Basement.Endianness.BE a) instance Basement.NormalForm.NormalForm a => Basement.NormalForm.NormalForm [a] instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b) => Basement.NormalForm.NormalForm (a, b) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c) => Basement.NormalForm.NormalForm (a, b, c) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c, Basement.NormalForm.NormalForm d) => Basement.NormalForm.NormalForm (a, b, c, d) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c, Basement.NormalForm.NormalForm d, Basement.NormalForm.NormalForm e) => Basement.NormalForm.NormalForm (a, b, c, d, e) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c, Basement.NormalForm.NormalForm d, Basement.NormalForm.NormalForm e, Basement.NormalForm.NormalForm f) => Basement.NormalForm.NormalForm (a, b, c, d, e, f) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c, Basement.NormalForm.NormalForm d, Basement.NormalForm.NormalForm e, Basement.NormalForm.NormalForm f, Basement.NormalForm.NormalForm g) => Basement.NormalForm.NormalForm (a, b, c, d, e, f, g) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b, Basement.NormalForm.NormalForm c, Basement.NormalForm.NormalForm d, Basement.NormalForm.NormalForm e, Basement.NormalForm.NormalForm f, Basement.NormalForm.NormalForm g, Basement.NormalForm.NormalForm h) => Basement.NormalForm.NormalForm (a, b, c, d, e, f, g, h) -- | These a b, sum type to represent either a or -- b or both. module Basement.These -- | Either a or b or both. data These a b This :: a -> These a b That :: b -> These a b These :: a -> b -> These a b instance (GHC.Show.Show b, GHC.Show.Show a) => GHC.Show.Show (Basement.These.These a b) instance (GHC.Classes.Ord b, GHC.Classes.Ord a) => GHC.Classes.Ord (Basement.These.These a b) instance (GHC.Classes.Eq b, GHC.Classes.Eq a) => GHC.Classes.Eq (Basement.These.These a b) instance (Basement.NormalForm.NormalForm a, Basement.NormalForm.NormalForm b) => Basement.NormalForm.NormalForm (Basement.These.These a b) instance Data.Bifunctor.Bifunctor Basement.These.These instance GHC.Base.Functor (Basement.These.These a) module Basement.Types.Ptr data Addr Addr :: Addr# -> Addr addrPlus :: Addr -> Offset Word8 -> Addr addrPlusSz :: Addr -> CountOf Word8 -> Addr addrPlusCSz :: Addr -> CSize -> Addr -- | 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 :: * -> * Ptr :: Addr# -> Ptr a ptrPlus :: Ptr a -> Offset Word8 -> Ptr a ptrPlusSz :: Ptr a -> CountOf Word8 -> Ptr a ptrPlusCSz :: Ptr a -> CSize -> Ptr a -- | The castPtr function casts a pointer from one type to another. castPtr :: Ptr a -> Ptr b instance GHC.Classes.Ord Basement.Types.Ptr.Addr instance GHC.Classes.Eq Basement.Types.Ptr.Addr module Basement.PrimType -- | 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 -> CountOf Word8 -- | get the shift size primShiftToBytes :: PrimType ty => Proxy ty -> Int -- | 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 () -- | A constraint class for serializable type that have an unique memory -- compare representation -- -- e.g. Float and Double have -0.0 and 0.0 which are Eq individual, yet -- have a different memory representation which doesn't allow for memcmp -- operation class PrimMemoryComparable ty primBaIndex :: PrimType ty => ByteArray# -> Offset ty -> ty primMbaRead :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty primMbaWrite :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () primArrayIndex :: Array# ty -> Offset ty -> ty primMutableArrayRead :: PrimMonad prim => MutableArray# (PrimState prim) ty -> Offset ty -> prim ty primMutableArrayWrite :: PrimMonad prim => MutableArray# (PrimState prim) ty -> Offset ty -> ty -> prim () -- | Deprecated: use offsetInBytes primOffsetOfE :: forall a. PrimType a => Offset a -> Offset Word8 primOffsetRecast :: forall a b. (PrimType a, PrimType b) => Offset a -> Offset b -- | Cast a CountOf linked to type A (CountOf A) to a CountOf linked to -- type B (CountOf B) sizeRecast :: forall a b. (PrimType a, PrimType b) => CountOf a -> CountOf b offsetAsSize :: Offset a -> CountOf a sizeAsOffset :: CountOf a -> Offset a sizeInBytes :: forall a. PrimType a => CountOf a -> CountOf Word8 offsetInBytes :: forall a. PrimType a => Offset a -> Offset Word8 offsetInElements :: forall a. PrimType a => Offset Word8 -> Offset a offsetIsAligned :: forall a. PrimType a => Proxy a -> Offset Word8 -> Bool primWordGetByteAndShift :: Word# -> (# Word#, Word# #) primWord64GetByteAndShift :: Word# -> (# Word#, Word# #) primWord64GetHiLo :: Word# -> (# Word#, Word# #) instance Basement.PrimType.PrimType GHC.Types.Int instance Basement.PrimType.PrimType GHC.Types.Word instance Basement.PrimType.PrimType GHC.Word.Word8 instance Basement.PrimType.PrimType GHC.Word.Word16 instance Basement.PrimType.PrimType GHC.Word.Word32 instance Basement.PrimType.PrimType GHC.Word.Word64 instance Basement.PrimType.PrimType Basement.Types.Word128.Word128 instance Basement.PrimType.PrimType Basement.Types.Word256.Word256 instance Basement.PrimType.PrimType GHC.Int.Int8 instance Basement.PrimType.PrimType GHC.Int.Int16 instance Basement.PrimType.PrimType GHC.Int.Int32 instance Basement.PrimType.PrimType GHC.Int.Int64 instance Basement.PrimType.PrimType GHC.Types.Float instance Basement.PrimType.PrimType GHC.Types.Double instance Basement.PrimType.PrimType GHC.Types.Char instance Basement.PrimType.PrimType Foreign.C.Types.CChar instance Basement.PrimType.PrimType Foreign.C.Types.CUChar instance Basement.PrimType.PrimType Basement.Types.Char7.Char7 instance Basement.PrimType.PrimType a => Basement.PrimType.PrimType (Basement.Endianness.LE a) instance Basement.PrimType.PrimType a => Basement.PrimType.PrimType (Basement.Endianness.BE a) instance Basement.PrimType.PrimMemoryComparable GHC.Types.Int instance Basement.PrimType.PrimMemoryComparable GHC.Types.Word instance Basement.PrimType.PrimMemoryComparable GHC.Word.Word8 instance Basement.PrimType.PrimMemoryComparable GHC.Word.Word16 instance Basement.PrimType.PrimMemoryComparable GHC.Word.Word32 instance Basement.PrimType.PrimMemoryComparable GHC.Word.Word64 instance Basement.PrimType.PrimMemoryComparable Basement.Types.Word128.Word128 instance Basement.PrimType.PrimMemoryComparable Basement.Types.Word256.Word256 instance Basement.PrimType.PrimMemoryComparable GHC.Int.Int8 instance Basement.PrimType.PrimMemoryComparable GHC.Int.Int16 instance Basement.PrimType.PrimMemoryComparable GHC.Int.Int32 instance Basement.PrimType.PrimMemoryComparable GHC.Int.Int64 instance Basement.PrimType.PrimMemoryComparable GHC.Types.Char instance Basement.PrimType.PrimMemoryComparable Foreign.C.Types.CChar instance Basement.PrimType.PrimMemoryComparable Foreign.C.Types.CUChar instance Basement.PrimType.PrimMemoryComparable a => Basement.PrimType.PrimMemoryComparable (Basement.Endianness.LE a) instance Basement.PrimType.PrimMemoryComparable a => Basement.PrimType.PrimMemoryComparable (Basement.Endianness.BE a) -- | Types to represent ℤ/nℤ. -- -- ℤ/nℤ is a finite field and is defined as the set of natural number: -- {0, 1, ..., n − 1}. module Basement.Bounded -- | A type level bounded natural backed by a Word64 data Zn64 (n :: Nat) unZn64 :: Zn64 n -> Word64 -- | A type level bounded natural data Zn (n :: Nat) unZn :: Zn n -> Natural -- | Create an element of ℤ/nℤ from a Word64 -- -- If the value is greater than n, then the value is normalized by using -- the integer modulus n zn64 :: forall n. (KnownNat n, NatWithinBound Word64 n) => Word64 -> Zn64 n -- | Create an element of ℤ/nℤ from a Natural. -- -- If the value is greater than n, then the value is normalized by using -- the integer modulus n zn :: forall n. KnownNat n => Natural -> Zn n -- | Create an element of ℤ/nℤ from a type level Nat zn64Nat :: forall m n. (KnownNat m, KnownNat n, NatWithinBound Word64 m, NatWithinBound Word64 n, CmpNat m n ~ LT) => Proxy m -> Zn64 n -- | Create an element of ℤ/nℤ from a type level Nat znNat :: forall m n. (KnownNat m, KnownNat n, CmpNat m n ~ LT) => Proxy m -> Zn n instance GHC.Classes.Ord (Basement.Bounded.Zn n) instance GHC.Classes.Eq (Basement.Bounded.Zn n) instance GHC.Show.Show (Basement.Bounded.Zn n) instance GHC.Classes.Ord (Basement.Bounded.Zn64 n) instance GHC.Classes.Eq (Basement.Bounded.Zn64 n) instance GHC.Show.Show (Basement.Bounded.Zn64 n) -- | A block of memory that contains elements of a type, very similar to an -- unboxed array but with the key difference: -- -- -- -- It should be rarely needed in high level API, but in lowlevel API or -- some data structure containing lots of unboxed array that will benefit -- from optimisation. -- -- Because it's unpinned, the blocks are compactable / movable, at the -- expense of making them less friendly to interop with the C layer as -- address. -- -- Note that sadly the bytearray primitive type automatically create a -- pinned bytearray if the size is bigger than a certain threshold -- -- GHC Documentation associated: -- -- includesrtsstorage/Block.h * LARGE_OBJECT_THRESHOLD -- ((uint32_t)(BLOCK_SIZE * 8 / 10)) * BLOCK_SIZE (1<<BLOCK_SHIFT) -- -- includesrtsConstant.h * BLOCK_SHIFT 12 module Basement.Block.Mutable -- | A block of memory containing unpacked bytes representing values of -- type ty data Block ty Block :: ByteArray# -> Block ty -- | A Mutable block of memory containing unpacked bytes representing -- values of type ty data MutableBlock ty st MutableBlock :: (MutableByteArray# st) -> MutableBlock ty st -- | Return the length of a Mutable Block -- -- note: we don't allow resizing yet, so this can remain a pure function mutableLengthSize :: forall ty st. PrimType ty => MutableBlock ty st -> CountOf ty mutableLengthBytes :: MutableBlock ty st -> CountOf Word8 -- | Get the address of the context of the mutable block. -- -- if the block is not pinned, this is a _dangerous_ operation -- -- Note that if nothing is holding the block, the GC can garbage collect -- the block and thus the address is dangling on the memory. use -- mutableWithAddr to prevent this problem by construction mutableGetAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Ptr ty) -- | Get the address of the mutable block in a safer construct -- -- if the block is not pinned, this is a _dangerous_ operation mutableWithAddr :: PrimMonad prim => MutableBlock ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a mutableTouch :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim () -- | Create a new mutable block of a specific N size of ty -- elements new :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim)) newPinned :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MutableBlock ty (PrimState prim)) mutableEmpty :: PrimMonad prim => prim (MutableBlock ty (PrimState prim)) -- | Set all mutable block element to a value iterSet :: (PrimType ty, PrimMonad prim) => (Offset ty -> ty) -> MutableBlock ty (PrimState prim) -> prim () -- | read a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. read :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty -- | Write to a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. write :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> ty -> prim () -- | Create a new mutable block of a specific size in bytes. -- -- Note that no checks are made to see if the size in bytes is compatible -- with the size of the underlaying element ty in the block. -- -- use new if unsure unsafeNew :: PrimMonad prim => PinnedStatus -> CountOf Word8 -> prim (MutableBlock ty (PrimState prim)) -- | write to a cell in a mutable block without bounds checking. -- -- Writing with invalid bounds will corrupt memory and your program will -- become unreliable. use write if unsure. unsafeWrite :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> ty -> prim () -- | read from a cell in a mutable block without bounds checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use read if unsure. unsafeRead :: (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> prim ty -- | Freeze a mutable block into a block. -- -- If the mutable block is still use after freeze, then the modification -- will be reflected in an unexpected way in the Block. unsafeFreeze :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Block ty) -- | Thaw an immutable block. -- -- If the immutable block is modified, then the original immutable block -- will be modified too, but lead to unexpected results when querying unsafeThaw :: (PrimType ty, PrimMonad prim) => Block ty -> prim (MutableBlock ty (PrimState prim)) -- | Copy a number of elements from an array to another array with offsets unsafeCopyElements :: forall prim ty. (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> MutableBlock ty (PrimState prim) -> Offset ty -> CountOf ty -> prim () unsafeCopyElementsRO :: forall prim ty. (PrimMonad prim, PrimType ty) => MutableBlock ty (PrimState prim) -> Offset ty -> Block ty -> Offset ty -> CountOf ty -> prim () -- | Copy a number of bytes from a MutableBlock to another MutableBlock -- with specific byte offsets unsafeCopyBytes :: forall prim ty. PrimMonad prim => MutableBlock ty (PrimState prim) -> Offset Word8 -> MutableBlock ty (PrimState prim) -> Offset Word8 -> CountOf Word8 -> prim () -- | Copy a number of bytes from a Block to a MutableBlock with specific -- byte offsets unsafeCopyBytesRO :: forall prim ty. PrimMonad prim => MutableBlock ty (PrimState prim) -> Offset Word8 -> Block ty -> Offset Word8 -> CountOf Word8 -> prim () module Basement.Base16 -- | Convert a byte value in Words containing the hexadecimal -- representation of the Word# -- -- The output words# are guaranteed to be included in the 0 to 2^7-1 -- range -- -- Note that calling convertByte with a value greater than 256 will cause -- segfault or other horrible effect. unsafeConvertByte :: Word# -> (# Word#, Word# #) -- | hex word16 hexWord16 :: Word16 -> (Char, Char, Char, Char) -- | hex word32 hexWord32 :: Word32 -> (Char, Char, Char, Char, Char, Char, Char, Char) -- | A block of memory that contains elements of a type, very similar to an -- unboxed array but with the key difference: -- -- module Basement.Block -- | A block of memory containing unpacked bytes representing values of -- type ty data Block ty Block :: ByteArray# -> Block ty -- | A Mutable block of memory containing unpacked bytes representing -- values of type ty data MutableBlock ty st MutableBlock :: (MutableByteArray# st) -> MutableBlock ty st length :: forall ty. PrimType ty => Block ty -> CountOf ty -- | Thaw an immutable block. -- -- If the immutable block is modified, then the original immutable block -- will be modified too, but lead to unexpected results when querying unsafeThaw :: (PrimType ty, PrimMonad prim) => Block ty -> prim (MutableBlock ty (PrimState prim)) -- | Freeze a mutable block into a block. -- -- If the mutable block is still use after freeze, then the modification -- will be reflected in an unexpected way in the Block. unsafeFreeze :: PrimMonad prim => MutableBlock ty (PrimState prim) -> prim (Block ty) -- | Return the element at a specific index from an array without bounds -- checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use index if unsure. unsafeIndex :: forall ty. PrimType ty => Block ty -> Offset ty -> ty -- | Thaw a Block into a MutableBlock -- -- the Block is not modified, instead a new Mutable Block is created and -- its content is copied to the mutable block thaw :: (PrimMonad prim, PrimType ty) => Block ty -> prim (MutableBlock ty (PrimState prim)) freeze :: (PrimType ty, PrimMonad prim) => MutableBlock ty (PrimState prim) -> prim (Block ty) -- | Copy every cells of an existing Block to a new Block copy :: PrimType ty => Block ty -> Block ty -- | Create a new array of size n by settings each cells through the -- function f. create :: forall ty. PrimType ty => CountOf ty -> (Offset ty -> ty) -> Block ty isPinned :: Block ty -> PinnedStatus isMutablePinned :: MutableBlock s ty -> PinnedStatus singleton :: PrimType ty => ty -> Block ty replicate :: PrimType ty => CountOf ty -> ty -> Block ty -- | Return the element at a specific index from an array. -- -- If the index @n is out of bounds, an error is raised. index :: PrimType ty => Block ty -> Offset ty -> ty -- | Map all element a from a block to a new block of b map :: (PrimType a, PrimType b) => (a -> b) -> Block a -> Block b foldl' :: PrimType ty => (a -> ty -> a) -> a -> Block ty -> a foldr :: PrimType ty => (ty -> a -> a) -> a -> Block ty -> a foldl1' :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (Block ty) -> ty foldr1 :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (Block ty) -> ty cons :: PrimType ty => ty -> Block ty -> Block ty snoc :: PrimType ty => Block ty -> ty -> Block ty uncons :: PrimType ty => Block ty -> Maybe (ty, Block ty) unsnoc :: PrimType ty => Block ty -> Maybe (Block ty, ty) sub :: PrimType ty => Block ty -> Offset ty -> Offset ty -> Block ty splitAt :: PrimType ty => CountOf ty -> Block ty -> (Block ty, Block ty) revSplitAt :: PrimType ty => CountOf ty -> Block ty -> (Block ty, Block ty) splitOn :: PrimType ty => (ty -> Bool) -> Block ty -> [Block ty] break :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) breakEnd :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) span :: PrimType ty => (ty -> Bool) -> Block ty -> (Block ty, Block ty) elem :: PrimType ty => ty -> Block ty -> Bool all :: PrimType ty => (ty -> Bool) -> Block ty -> Bool any :: PrimType ty => (ty -> Bool) -> Block ty -> Bool find :: PrimType ty => (ty -> Bool) -> Block ty -> Maybe ty filter :: PrimType ty => (ty -> Bool) -> Block ty -> Block ty reverse :: forall ty. PrimType ty => Block ty -> Block ty sortBy :: PrimType ty => (ty -> ty -> Ordering) -> Block ty -> Block ty intersperse :: forall ty. PrimType ty => ty -> Block ty -> Block ty -- | Copy all the block content to the memory starting at the destination -- address unsafeCopyToPtr :: forall ty prim. PrimMonad prim => Block ty -> Ptr ty -> prim () -- | A Nat-sized version of Block module Basement.BlockN data BlockN (n :: Nat) a data MutableBlockN (n :: Nat) ty st toBlockN :: forall n ty. (PrimType ty, KnownNat n, Countable ty n) => Block ty -> Maybe (BlockN n ty) toBlock :: BlockN n ty -> Block ty singleton :: PrimType ty => ty -> BlockN 1 ty replicate :: forall n ty. (KnownNat n, Countable ty n, PrimType ty) => ty -> BlockN n ty thaw :: (KnownNat n, PrimMonad prim, PrimType ty) => BlockN n ty -> prim (MutableBlockN n ty (PrimState prim)) freeze :: (PrimMonad prim, PrimType ty, Countable ty n) => MutableBlockN n ty (PrimState prim) -> prim (BlockN n ty) index :: forall i n ty. (KnownNat i, CmpNat i n ~ LT, PrimType ty, Offsetable ty i) => BlockN n ty -> ty map :: (PrimType a, PrimType b) => (a -> b) -> BlockN n a -> BlockN n b foldl' :: PrimType ty => (a -> ty -> a) -> a -> BlockN n ty -> a foldr :: PrimType ty => (ty -> a -> a) -> a -> BlockN n ty -> a cons :: PrimType ty => ty -> BlockN n ty -> BlockN (n + 1) ty snoc :: PrimType ty => BlockN n ty -> ty -> BlockN (n + 1) ty elem :: PrimType ty => ty -> BlockN n ty -> Bool sub :: forall i j n ty. ((i <=? n) ~ True, (j <=? n) ~ True, (i <=? j) ~ True, PrimType ty, KnownNat i, KnownNat j, Offsetable ty i, Offsetable ty j) => BlockN n ty -> BlockN (j - i) ty uncons :: forall n ty. (CmpNat 0 n ~ LT, PrimType ty, KnownNat n, Offsetable ty n) => BlockN n ty -> (ty, BlockN (n - 1) ty) unsnoc :: forall n ty. (CmpNat 0 n ~ LT, KnownNat n, PrimType ty, Offsetable ty n) => BlockN n ty -> (BlockN (n - 1) ty, ty) splitAt :: forall i n ty. (CmpNat i n ~ LT, PrimType ty, KnownNat i, Countable ty i) => BlockN n ty -> (BlockN i ty, BlockN (n - i) ty) all :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool any :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Bool find :: PrimType ty => (ty -> Bool) -> BlockN n ty -> Maybe ty reverse :: PrimType ty => BlockN n ty -> BlockN n ty sortBy :: PrimType ty => (ty -> ty -> Ordering) -> BlockN n ty -> BlockN n ty intersperse :: (CmpNat n 1 ~ GT, PrimType ty) => ty -> BlockN n ty -> BlockN ((n + n) - 1) ty instance (GHC.Show.Show a, Basement.PrimType.PrimType a) => GHC.Show.Show (Basement.BlockN.BlockN n a) instance Basement.PrimType.PrimType a => GHC.Classes.Eq (Basement.BlockN.BlockN n a) instance Basement.NormalForm.NormalForm (Basement.BlockN.BlockN n a) -- | Simple boxed array abstraction module Basement.BoxedArray -- | Array of a data Array a -- | Mutable Array of a data MArray a st empty :: Array a length :: Array a -> CountOf a -- | return the numbers of elements in a mutable array mutableLength :: MArray ty st -> Int -- | Copy the element to a new element array copy :: Array ty -> Array ty -- | Copy n sequential elements from the specified offset in a -- source array to the specified position in a destination array. -- -- This function does not check bounds. Accessing invalid memory can -- return unpredictable and invalid values. unsafeCopyAtRO :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> Array ty -> Offset ty -> CountOf ty -> prim () -- | Thaw an array to a mutable array. -- -- the array is not modified, instead a new mutable array is created and -- every values is copied, before returning the mutable array. thaw :: PrimMonad prim => Array ty -> prim (MArray ty (PrimState prim)) -- | Create a new 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 and -- always contains a number of bytes multiples of 64 bits. new :: PrimMonad prim => CountOf ty -> prim (MArray ty (PrimState prim)) -- | Freeze a mutable array into an array. -- -- the MArray must not be changed after freezing. unsafeFreeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (Array ty) -- | Thaw an immutable array. -- -- The Array must not be used after thawing. unsafeThaw :: PrimMonad prim => Array ty -> prim (MArray ty (PrimState prim)) freeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (Array ty) -- | write to a cell in a mutable array without bounds checking. -- -- Writing with invalid bounds will corrupt memory and your program will -- become unreliable. use write if unsure. unsafeWrite :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> ty -> prim () -- | read from a cell in a mutable array without bounds checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use read if unsure. unsafeRead :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> prim ty -- | Return the element at a specific index from an array without bounds -- checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use index if unsure. unsafeIndex :: Array ty -> Offset ty -> ty -- | Write to a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. write :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> ty -> prim () -- | read a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. read :: PrimMonad prim => MArray ty (PrimState prim) -> Offset ty -> prim ty -- | Return the element at a specific index from an array. -- -- If the index @n is out of bounds, an error is raised. index :: Array ty -> Offset ty -> ty singleton :: ty -> Array ty replicate :: CountOf ty -> ty -> Array ty null :: Array ty -> Bool take :: CountOf ty -> Array ty -> Array ty drop :: CountOf ty -> Array ty -> Array ty splitAt :: CountOf ty -> Array ty -> (Array ty, Array ty) revTake :: CountOf ty -> Array ty -> Array ty revDrop :: CountOf ty -> Array ty -> Array ty revSplitAt :: CountOf ty -> Array ty -> (Array ty, Array ty) splitOn :: (ty -> Bool) -> Array ty -> [Array ty] sub :: Array ty -> Offset ty -> Offset ty -> Array ty intersperse :: ty -> Array ty -> Array ty span :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) spanEnd :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) break :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) breakEnd :: (ty -> Bool) -> Array ty -> (Array ty, Array ty) mapFromUnboxed :: PrimType a => (a -> b) -> UArray a -> Array b mapToUnboxed :: PrimType b => (a -> b) -> Array a -> UArray b cons :: ty -> Array ty -> Array ty snoc :: Array ty -> ty -> Array ty uncons :: Array ty -> Maybe (ty, Array ty) unsnoc :: Array ty -> Maybe (Array ty, ty) sortBy :: forall ty. (ty -> ty -> Ordering) -> Array ty -> Array ty filter :: forall ty. (ty -> Bool) -> Array ty -> Array ty reverse :: Array ty -> Array ty elem :: Eq ty => ty -> Array ty -> Bool find :: (ty -> Bool) -> Array ty -> Maybe ty foldl' :: (a -> ty -> a) -> a -> Array ty -> a foldr :: (ty -> a -> a) -> a -> Array ty -> a foldl1' :: (ty -> ty -> ty) -> NonEmpty (Array ty) -> ty foldr1 :: (ty -> ty -> ty) -> NonEmpty (Array ty) -> ty all :: (ty -> Bool) -> Array ty -> Bool any :: (ty -> Bool) -> Array ty -> Bool isPrefixOf :: Eq ty => Array ty -> Array ty -> Bool isSuffixOf :: Eq ty => Array ty -> Array ty -> Bool builderAppend :: PrimMonad state => ty -> Builder (Array ty) (MArray ty) ty state err () builderBuild :: PrimMonad m => Int -> Builder (Array ty) (MArray ty) ty m err () -> m (Either err (Array ty)) builderBuild_ :: PrimMonad m => Int -> Builder (Array ty) (MArray ty) ty m () () -> m (Array ty) instance Data.Data.Data ty => Data.Data.Data (Basement.BoxedArray.Array ty) instance Basement.NormalForm.NormalForm a => Basement.NormalForm.NormalForm (Basement.BoxedArray.Array a) instance GHC.Base.Functor Basement.BoxedArray.Array instance GHC.Base.Monoid (Basement.BoxedArray.Array a) instance GHC.Show.Show a => GHC.Show.Show (Basement.BoxedArray.Array a) instance GHC.Classes.Eq a => GHC.Classes.Eq (Basement.BoxedArray.Array a) instance GHC.Classes.Ord a => GHC.Classes.Ord (Basement.BoxedArray.Array a) instance GHC.Exts.IsList (Basement.BoxedArray.Array ty) -- | A simple array abstraction that allow to use typed array of bytes -- where the array is pinned in memory to allow easy use with Foreign -- interfaces, ByteString and always aligned to 64 bytes. module Basement.UArray.Mutable -- | A Mutable array of types built on top of GHC primitive. -- -- Element in this array can be modified in place. data MUArray ty st MUArray :: {-# UNPACK #-} !(Offset ty) -> {-# UNPACK #-} !(CountOf ty) -> !(MUArrayBackend ty st) -> MUArray ty st sizeInMutableBytesOfContent :: forall ty s. PrimType ty => MUArray ty s -> CountOf Word8 -- | return the numbers of elements in a mutable array mutableLength :: PrimType ty => MUArray ty st -> CountOf ty mutableOffset :: MUArray ty st -> Offset ty mutableSame :: MUArray ty st -> MUArray ty st -> Bool onMutableBackend :: PrimMonad prim => (MutableByteArray# (PrimState prim) -> prim a) -> (FinalPtr ty -> prim a) -> MUArray ty (PrimState prim) -> prim a -- | 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) => CountOf 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 :: forall prim ty. (PrimMonad prim, PrimType ty) => CountOf ty -> prim (MUArray ty (PrimState prim)) newNative :: (PrimMonad prim, PrimType ty) => CountOf ty -> (MutableBlock ty (PrimState prim) -> prim a) -> prim (a, MUArray ty (PrimState prim)) mutableForeignMem :: (PrimMonad prim, PrimType ty) => FinalPtr ty -> Int -> prim (MUArray ty (PrimState prim)) -- | Copy a number of elements from an array to another array with offsets copyAt :: forall prim ty. (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> MUArray ty (PrimState prim) -> Offset ty -> CountOf ty -> prim () -- | Copy from a pointer, count elements, into the mutable array copyFromPtr :: forall prim ty. (PrimMonad prim, PrimType ty) => Ptr ty -> CountOf ty -> MUArray ty (PrimState prim) -> prim () -- | Copy all the block content to the memory starting at the destination -- address copyToPtr :: forall ty prim. (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> Ptr ty -> prim () sub :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Int -> Int -> prim (MUArray ty (PrimState prim)) -- | write to a cell in a mutable array without bounds checking. -- -- Writing with invalid bounds will corrupt memory and your program will -- become unreliable. use write if unsure. unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () -- | read from a cell in a mutable array without bounds checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use read if unsure. unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty -- | Write to a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. write :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () -- | read a cell in a mutable array. -- -- If the index is out of bounds, an error is raised. read :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty -- | 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 copied when f return. withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a -- | An unboxed array of primitive types -- -- All the cells in the array are in one chunk of contiguous memory. module Basement.UArray -- | 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 UArray :: {-# UNPACK #-} !(Offset ty) -> {-# UNPACK #-} !(CountOf ty) -> !(UArrayBackend ty) -> 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 -- | get the size in bytes of a ty element primSizeInBytes :: PrimType ty => Proxy ty -> CountOf Word8 -- | get the shift size primShiftToBytes :: PrimType ty => Proxy ty -> Int -- | 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 () -- | Copy every cells of an existing array to a new array copy :: PrimType ty => UArray ty -> UArray ty -- | Copy n sequential elements from the specified offset in a -- source array to the specified position in a destination array. -- -- This function does not check bounds. Accessing invalid memory can -- return unpredictable and invalid values. unsafeCopyAtRO :: forall prim ty. (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> UArray ty -> Offset ty -> CountOf ty -> prim () -- | Recast an array of type a to an array of b -- -- a and b need to have the same size otherwise this raise an async -- exception recast :: forall a b. (PrimType a, PrimType b) => UArray a -> UArray b unsafeRecast :: (PrimType a, PrimType b) => UArray a -> UArray b length :: UArray ty -> CountOf ty freeze :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> prim (UArray ty) -- | Freeze a mutable array into an array. -- -- the MUArray must not be changed after freezing. unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (UArray ty) -- | Thaw an array to a mutable array. -- -- the array is not modified, instead a new mutable array is created and -- every values is copied, before returning the mutable array. thaw :: (PrimMonad prim, PrimType ty) => UArray ty -> prim (MUArray ty (PrimState prim)) -- | Thaw an immutable array. -- -- The UArray must not be used after thawing. unsafeThaw :: (PrimType ty, PrimMonad prim) => UArray ty -> prim (MUArray ty (PrimState prim)) -- | Make an array from a list of elements with a size hint. -- -- The list should be of the same size as the hint, as otherwise: -- -- vFromListN :: forall ty. PrimType ty => CountOf ty -> [ty] -> UArray ty -- | 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) => CountOf ty -> prim (MUArray ty (PrimState prim)) -- | Create a new array of size n by settings each cells through the -- function f. create :: forall ty. PrimType ty => CountOf ty -> (Offset ty -> ty) -> UArray ty -- | Create a pinned array that is filled by a filler function -- (typically an IO call like hGetBuf) createFromIO :: PrimType ty => CountOf ty -> (Ptr ty -> IO (CountOf ty)) -> IO (UArray ty) -- | Freeze a chunk of memory pointed, of specific size into a new unboxed -- array createFromPtr :: PrimType ty => Ptr ty -> CountOf ty -> IO (UArray ty) sub :: PrimType ty => UArray ty -> Offset ty -> Offset ty -> UArray ty -- | Copy all the block content to the memory starting at the destination -- address copyToPtr :: forall ty prim. (PrimType ty, PrimMonad prim) => UArray ty -> Ptr ty -> prim () withPtr :: forall ty prim a. (PrimMonad prim, PrimType ty) => UArray ty -> (Ptr ty -> prim a) -> prim a -- | 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 copied when f return. withMutablePtr :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> (Ptr ty -> prim a) -> prim a unsafeFreezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) freezeShrink :: (PrimType ty, PrimMonad prim) => MUArray ty (PrimState prim) -> CountOf ty -> prim (UArray ty) -- | Create a UArray from a Block -- -- The block is still used by the uarray fromBlock :: PrimType ty => Block ty -> UArray ty -- | Create a Block from a UArray. -- -- Note that because of the slice, the destination block is re-allocated -- and copied, unless the slice point at the whole array toBlock :: PrimType ty => UArray ty -> Block ty -- | update an array by creating a new array with the updates. -- -- the operation copy the previous array, modify it in place, then freeze -- it. update :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty unsafeUpdate :: PrimType ty => UArray ty -> [(Offset ty, ty)] -> UArray ty -- | Return the element at a specific index from an array without bounds -- checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use index if unsure. unsafeIndex :: forall ty. PrimType ty => UArray ty -> Offset ty -> ty unsafeIndexer :: (PrimMonad prim, PrimType ty) => UArray ty -> ((Offset ty -> ty) -> prim a) -> prim a unsafeDewrap :: (ByteArray# -> Offset ty -> a) -> (Ptr ty -> Offset ty -> ST s a) -> UArray ty -> a -- | read from a cell in a mutable array without bounds checking. -- -- Reading from invalid memory can return unpredictable and invalid -- values. use read if unsure. unsafeRead :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> prim ty -- | write to a cell in a mutable array without bounds checking. -- -- Writing with invalid bounds will corrupt memory and your program will -- become unreliable. use write if unsure. unsafeWrite :: (PrimMonad prim, PrimType ty) => MUArray ty (PrimState prim) -> Offset ty -> ty -> prim () equalMemcmp :: PrimType ty => UArray ty -> UArray ty -> Bool singleton :: PrimType ty => ty -> UArray ty replicate :: PrimType ty => CountOf ty -> ty -> UArray ty map :: (PrimType a, PrimType b) => (a -> b) -> UArray a -> UArray b mapIndex :: (PrimType a, PrimType b) => (Offset b -> a -> b) -> UArray a -> UArray b findIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty) revFindIndex :: PrimType ty => ty -> UArray ty -> Maybe (Offset ty) -- | Return the element at a specific index from an array. -- -- If the index @n is out of bounds, an error is raised. index :: PrimType ty => UArray ty -> Offset ty -> ty null :: UArray ty -> Bool -- | Take a count of elements from the array and create an array with just -- those elements take :: CountOf ty -> UArray ty -> UArray ty unsafeTake :: CountOf ty -> UArray ty -> UArray ty -- | Drop a count of elements from the array and return the new array minus -- those dropped elements drop :: CountOf ty -> UArray ty -> UArray ty unsafeDrop :: CountOf ty -> UArray ty -> UArray ty -- | Split an array into two, with a count of at most N elements in the -- first one and the remaining in the other. splitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) -- | Drop the N elements from the end of the array revDrop :: CountOf ty -> UArray ty -> UArray ty -- | Take the N elements from the end of the array revTake :: CountOf ty -> UArray ty -> UArray ty -- | Split an array at the N element from the end, and return the last N -- elements in the first part of the tuple, and whatever first elements -- remaining in the second revSplitAt :: CountOf ty -> UArray ty -> (UArray ty, UArray ty) splitOn :: PrimType ty => (ty -> Bool) -> UArray ty -> [UArray ty] break :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) -- | Similar to break but start the search of the breakpoint from the end -- --
--   breakEnd (> 0) [1,2,3,0,0,0]
--   
-- -- ([1,2,3], [0,0,0]) breakEnd :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) breakElem :: PrimType ty => ty -> UArray ty -> (UArray ty, UArray ty) -- | Similar to breakElem specialized to split on linefeed -- -- it either returns: * Left. no line has been found, and whether the -- last character is a CR * Right, a line has been found with an optional -- CR, and it returns the array of bytes on the left of the CR/LF, and -- the the array of bytes on the right of the LF. breakLine :: UArray Word8 -> Either Bool (UArray Word8, UArray Word8) elem :: PrimType ty => ty -> UArray ty -> Bool indices :: PrimType ty => UArray ty -> UArray ty -> [Offset ty] intersperse :: forall ty. PrimType ty => ty -> UArray ty -> UArray ty span :: PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) spanEnd :: PrimType ty => (ty -> Bool) -> UArray ty -> (UArray ty, UArray ty) cons :: PrimType ty => ty -> UArray ty -> UArray ty snoc :: PrimType ty => UArray ty -> ty -> UArray ty uncons :: PrimType ty => UArray ty -> Maybe (ty, UArray ty) unsnoc :: PrimType ty => UArray ty -> Maybe (UArray ty, ty) find :: PrimType ty => (ty -> Bool) -> UArray ty -> Maybe ty sortBy :: forall ty. PrimType ty => (ty -> ty -> Ordering) -> UArray ty -> UArray ty filter :: forall ty. PrimType ty => (ty -> Bool) -> UArray ty -> UArray ty reverse :: forall ty. PrimType ty => UArray ty -> UArray ty -- | Replace all the occurrencies of needle with -- replacement in the haystack string. replace :: PrimType ty => UArray ty -> UArray ty -> UArray ty -> UArray ty foldr :: PrimType ty => (ty -> a -> a) -> a -> UArray ty -> a foldl' :: PrimType ty => (a -> ty -> a) -> a -> UArray ty -> a foldr1 :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (UArray ty) -> ty foldl1' :: PrimType ty => (ty -> ty -> ty) -> NonEmpty (UArray ty) -> ty all :: PrimType ty => (ty -> Bool) -> UArray ty -> Bool any :: PrimType ty => (ty -> Bool) -> UArray ty -> Bool isPrefixOf :: PrimType ty => UArray ty -> UArray ty -> Bool isSuffixOf :: PrimType ty => UArray ty -> UArray ty -> Bool foreignMem :: PrimType ty => FinalPtr ty -> CountOf ty -> UArray ty fromForeignPtr :: PrimType ty => (ForeignPtr ty, Int, Int) -> UArray ty builderAppend :: (PrimType ty, PrimMonad state) => ty -> Builder (UArray ty) (MUArray ty) ty state err () builderBuild :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m err () -> m (Either err (UArray ty)) builderBuild_ :: (PrimType ty, PrimMonad m) => Int -> Builder (UArray ty) (MUArray ty) ty m () () -> m (UArray ty) toHexadecimal :: PrimType ty => UArray ty -> UArray Word8 toBase64Internal :: PrimType ty => Addr# -> UArray ty -> Bool -> UArray Word8 -- | A AsciiString type backed by a ASCII encoded byte array and -- all the necessary functions to manipulate the string. module Basement.Types.AsciiString -- | Opaque packed array of characters in the ASCII encoding newtype AsciiString AsciiString :: UArray Char7 -> AsciiString [toBytes] :: AsciiString -> UArray Char7 newtype MutableAsciiString st MutableAsciiString :: (MUArray Char7 st) -> MutableAsciiString st -- | Convert a Byte Array representing ASCII data directly to an -- AsciiString without checking for ASCII validity -- -- If the input contains invalid Char7 value (anything above 0x7f), it -- will trigger runtime async errors when processing data. -- -- In doubt, use fromBytes fromBytesUnsafe :: UArray Word8 -> AsciiString -- | Convert a Byte Array representing ASCII checking validity. -- -- If the byte array is not valid, then Nothing is returned fromBytes :: UArray Word8 -> Maybe AsciiString instance GHC.Classes.Ord Basement.Types.AsciiString.AsciiString instance GHC.Classes.Eq Basement.Types.AsciiString.AsciiString instance GHC.Base.Monoid Basement.Types.AsciiString.AsciiString instance GHC.Show.Show Basement.Types.AsciiString.AsciiString instance Data.String.IsString Basement.Types.AsciiString.AsciiString instance GHC.Exts.IsList Basement.Types.AsciiString.AsciiString module Basement.Environment -- | Returns a list of the program's command line arguments (not including -- the program name). getArgs :: IO [String] -- | Lookup variable in the environment lookupEnv :: String -> IO (Maybe String) -- | re-export of all the base prelude and basic primitive stuffs module Basement.Imports -- | 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 -- | 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 <$> -- | 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 -- | Extract the first component of a pair. fst :: (a, b) -> a -- | Extract the second component of a pair. snd :: (a, b) -> b -- | 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 -- | and returns the conjunction of a container of Bools. For the -- result to be True, the container must be finite; False, -- however, results from a False value finitely far from the left -- end. and :: Foldable t => t Bool -> Bool -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: HasCallStack => a -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. seq is usually introduced to -- improve performance by avoiding unneeded laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: a -> b -> b -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a -- | 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 -- | 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 -- | 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 -- | 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 :: * -- | 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. data Offset ty -- | CountOf of a data structure. -- -- More specifically, it represents the number of elements of type -- ty that fit into the data structure. -- --
--   >>> length (fromList ['a', 'b', 'c', '🌟']) :: CountOf Char
--   CountOf 4
--   
-- -- Same caveats as Offset apply here. data CountOf ty -- | 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 :: * -- | 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 -- | ASCII value between 0x0 and 0x7f data Char7 -- | Opaque packed array of characters in the ASCII encoding data AsciiString -- | Opaque packed array of characters in the UTF8 encoding data String -- | 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 -- | Array of a data Array 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 -- | 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 :: * -- | 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 :: * -- | 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 :: * -- | 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 :: * -> * -- | IEEE754 Floating point Binary32, simple precision (Also known as -- Float) type FP32 = Float -- | IEEE754 Floating point Binary64, double precision (Also known as -- Double) type FP64 = Double -- | 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] -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a -- | Representable types of kind *. This class is derivable in GHC with the -- DeriveGeneric flag on. class Generic a where type Rep a :: * -> * where { type family Rep a :: * -> *; } -- | Convert from the datatype to its representation from :: Generic a => a -> Rep a x -- | Convert from the representation to the datatype to :: Generic a => Rep a x -> 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 -- | The Data class comprehends a fundamental primitive -- gfoldl for folding over constructor applications, say terms. -- This primitive can be instantiated in several ways to map over the -- immediate subterms of a term; see the gmap combinators later -- in this class. Indeed, a generic programmer does not necessarily need -- to use the ingenious gfoldl primitive but rather the intuitive -- gmap combinators. The gfoldl primitive is completed by -- means to query top-level constructors, to turn constructor -- representations into proper terms, and to list all possible datatype -- constructors. This completion allows us to serve generic programming -- scenarios like read, show, equality, term generation. -- -- The combinators gmapT, gmapQ, gmapM, etc are all -- provided with default definitions in terms of gfoldl, leaving -- open the opportunity to provide datatype-specific definitions. (The -- inclusion of the gmap combinators as members of class -- Data allows the programmer or the compiler to derive -- specialised, and maybe more efficient code per datatype. Note: -- gfoldl is more higher-order than the gmap combinators. -- This is subject to ongoing benchmarking experiments. It might turn out -- that the gmap combinators will be moved out of the class -- Data.) -- -- Conceptually, the definition of the gmap combinators in terms -- of the primitive gfoldl requires the identification of the -- gfoldl function arguments. Technically, we also need to -- identify the type constructor c for the construction of the -- result type from the folded term type. -- -- In the definition of gmapQx combinators, we use -- phantom type constructors for the c in the type of -- gfoldl because the result type of a query does not involve the -- (polymorphic) type of the term argument. In the definition of -- gmapQl we simply use the plain constant type constructor -- because gfoldl is left-associative anyway and so it is readily -- suited to fold a left-associative binary operation over the immediate -- subterms. In the definition of gmapQr, extra effort is needed. We use -- a higher-order accumulation trick to mediate between left-associative -- constructor application vs. right-associative binary operation (e.g., -- (:)). When the query is meant to compute a value of type -- r, then the result type withing generic folding is r -- -> r. So the result of folding is a function to which we -- finally pass the right unit. -- -- With the -XDeriveDataTypeable option, GHC can generate -- instances of the Data class automatically. For example, given -- the declaration -- --
--   data T a b = C1 a b | C2 deriving (Typeable, Data)
--   
-- -- GHC will generate an instance that is equivalent to -- --
--   instance (Data a, Data b) => Data (T a b) where
--       gfoldl k z (C1 a b) = z C1 `k` a `k` b
--       gfoldl k z C2       = z C2
--   
--       gunfold k z c = case constrIndex c of
--                           1 -> k (k (z C1))
--                           2 -> z C2
--   
--       toConstr (C1 _ _) = con_C1
--       toConstr C2       = con_C2
--   
--       dataTypeOf _ = ty_T
--   
--   con_C1 = mkConstr ty_T "C1" [] Prefix
--   con_C2 = mkConstr ty_T "C2" [] Prefix
--   ty_T   = mkDataType "Module.T" [con_C1, con_C2]
--   
-- -- This is suitable for datatypes that are exported transparently. class Typeable * a => Data a -- | Left-associative fold operation for constructor applications. -- -- The type of gfoldl is a headache, but operationally it is a -- simple generalisation of a list fold. -- -- The default definition for gfoldl is const -- id, which is suitable for abstract datatypes with no -- substructures. gfoldl :: Data a => (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> a -> c a -- | Unfolding constructor applications gunfold :: Data a => (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c a -- | Obtaining the constructor from a given datum. For proper terms, this -- is meant to be the top-level constructor. Primitive datatypes are here -- viewed as potentially infinite sets of values (i.e., constructors). toConstr :: Data a => a -> Constr -- | The outer type constructor of the type dataTypeOf :: Data a => a -> DataType -- | Mediate types and unary type constructors. In Data instances of -- the form T a, dataCast1 should be defined as -- gcast1. -- -- The default definition is const Nothing, which -- is appropriate for non-unary type constructors. dataCast1 :: (Data a, Typeable (* -> *) t) => (forall d. Data d => c (t d)) -> Maybe (c a) -- | Mediate types and binary type constructors. In Data instances -- of the form T a b, dataCast2 should be defined as -- gcast2. -- -- The default definition is const Nothing, which -- is appropriate for non-binary type constructors. dataCast2 :: (Data a, Typeable (* -> * -> *) t) => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a) -- | A generic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to an identity datatype constructor, using -- the isomorphism pair as injection and projection. gmapT :: Data a => (forall b. Data b => b -> b) -> a -> a -- | A generic query with a left-associative binary operator gmapQl :: Data a => (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query with a right-associative binary operator gmapQr :: Data a => (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r -- | A generic query that processes the immediate subterms and returns a -- list of results. The list is given in the same order as originally -- specified in the declaration of the data constructors. gmapQ :: Data a => (forall d. Data d => d -> u) -> a -> [u] -- | A generic query that processes one child by index (zero-based) gmapQi :: Data a => Int -> (forall d. Data d => d -> u) -> a -> u -- | A generic monadic transformation that maps over the immediate subterms -- -- The default definition instantiates the type constructor c in -- the type of gfoldl to the monad datatype constructor, defining -- injection and projection using return and >>=. gmapM :: (Data a, Monad m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of at least one immediate subterm does not fail gmapMp :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Transformation of one immediate subterm with success gmapMo :: (Data a, MonadPlus m) => (forall d. Data d => d -> m d) -> a -> m a -- | Constructs a non-representation for a non-representable type mkNoRepType :: String -> DataType -- | Representation of datatypes. A package of constructor representations -- with names of type and module. data DataType :: * -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable k (a :: k) -- | 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 <> -- | 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 -- | Throw an exception. Exceptions may be thrown from purely functional -- code, but may only be caught within the IO monad. throw :: Exception e => e -> a -- | A variant of throw that can only be used within the IO -- monad. -- -- Although throwIO has a type that is an instance of the type of -- throw, the two functions are subtly different: -- --
--   throw e   `seq` x  ===> throw e
--   throwIO e `seq` x  ===> x
--   
-- -- The first example will cause the exception e to be raised, -- whereas the second one won't. In fact, throwIO will only cause -- an exception to be raised when it is used within the IO monad. -- The throwIO variant should be used in preference to -- throw to raise an exception within the IO monad because -- it guarantees ordering with respect to other IO operations, -- whereas throw does not. throwIO :: Exception e => e -> IO a -- | 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 :: * -> * Ptr :: Addr# -> Ptr a -- | for support of if .. then .. else ifThenElse :: Bool -> a -> a -> a -- | A String type backed by a UTF8 encoded byte array and all the -- necessary functions to manipulate the string. -- -- You can think of String as a specialization of a byte array that have -- element of type Char. -- -- The String data must contain UTF8 valid data. module Basement.String -- | Opaque packed array of characters in the UTF8 encoding newtype String String :: (UArray Word8) -> String -- | Mutable String Buffer. -- -- Use as an *append* buffer, as UTF8 variable encoding doesn't really -- allow to change previously written character without potentially -- shifting bytes. newtype MutableString st MutableString :: (MUArray Word8 st) -> MutableString st -- | Unsafely create a string of up to sz bytes. -- -- The callback f needs to return the number of bytes filled in -- the underlaying bytes buffer. No check is made on the callback return -- values, and if it's not contained without the bounds, bad things will -- happen. create :: PrimMonad prim => CountOf Word8 -> (MutableString (PrimState prim) -> prim (Offset Word8)) -> prim String -- | Replicate a character c n times to create a string -- of length n replicate :: CountOf Char -> Char -> String -- | Length of a String using CountOf -- -- this size is available in o(n) length :: String -> CountOf Char -- | 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) -- | Decode a stream of binary chunks containing UTF8 encoding in a list of -- valid String -- -- Chunk not necessarily contains a valid string, as a UTF8 sequence -- could be split over 2 chunks. fromChunkBytes :: [UArray Word8] -> [String] -- | 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 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 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 -- | Similar to validate but works on a MutableByteArray mutableValidate :: PrimMonad prim => MUArray Word8 (PrimState prim) -> Offset Word8 -> CountOf Word8 -> prim (Offset Word8, Maybe ValidationFailure) -- | Copy the String -- -- The slice of memory is copied to a new slice, making the new string -- independent from the original string.. copy :: String -> String -- | Possible failure related to validating bytes of UTF8 sequences. data ValidationFailure InvalidHeader :: ValidationFailure InvalidContinuation :: ValidationFailure MissingByte :: ValidationFailure BuildingFailure :: ValidationFailure -- | Return the nth character in a String -- -- Compared to an array, the string need to be scanned from the beginning -- since the UTF8 encoding is variable. index :: String -> Offset Char -> Maybe Char -- | Check if a String is null null :: String -> Bool -- | Create a string with the remaining Chars after dropping @n Chars from -- the beginning drop :: CountOf Char -> String -> String -- | Create a string composed of a number @n of Chars (Unicode code -- points). -- -- if the input @s contains less characters than required, then the input -- string is returned. take :: CountOf Char -> String -> String -- | Split a string at the Offset specified (in Char) returning both the -- leading part and the remaining part. splitAt :: CountOf Char -> String -> (String, String) -- | Similar to drop but from the end revDrop :: CountOf Char -> String -> String -- | Similar to take but from the end revTake :: CountOf Char -> String -> String -- | Similar to splitAt but from the end revSplitAt :: CountOf Char -> String -> (String, String) -- | Split on the input string using the predicate as separator -- -- e.g. -- --
--   splitOn (== ',') ","          == ["",""]
--   splitOn (== ',') ",abc,"      == ["","abc",""]
--   splitOn (== ':') "abc"        == ["abc"]
--   splitOn (== ':') "abc::def"   == ["abc","","def"]
--   splitOn (== ':') "::abc::def" == ["","","abc","","def"]
--   
splitOn :: (Char -> Bool) -> String -> [String] -- | Internal call to make a substring given offset in bytes. -- -- This is unsafe considering that one can create a substring starting -- and/or ending on the middle of a UTF8 sequence. sub :: String -> Offset8 -> Offset8 -> String -- | Return whereas the string contains a specific character or not elem :: Char -> String -> Bool indices :: String -> String -> [Offset8] -- | Intersperse the character sep between each character in the -- string -- --
--   intersperse ' ' "Hello Foundation"
--   
-- -- "H e l l o F o u n d a t i o n" intersperse :: Char -> String -> String -- | Apply a predicate to the string to return the longest prefix -- that satisfy the predicate and the remaining span :: (Char -> Bool) -> String -> (String, String) -- | Apply a predicate to the string to return the longest suffix -- that satisfy the predicate and the remaining spanEnd :: (Char -> Bool) -> String -> (String, String) -- | Break a string into 2 strings at the location where the predicate -- return True break :: (Char -> Bool) -> String -> (String, String) breakEnd :: (Char -> Bool) -> String -> (String, String) -- | Break a string into 2 strings at the first occurence of the character breakElem :: Char -> String -> (String, String) -- | Same as break but cut on a line feed with an optional carriage return. -- -- This is the same operation as 'breakElem LF' dropping the last -- character of the string if it's a CR. -- -- Also for efficiency reason (streaming), it returns if the last -- character was a CR character. breakLine :: String -> Either Bool (String, String) -- | Drop character from the beginning while the predicate is true dropWhile :: (Char -> Bool) -> String -> String -- | Create a single element String singleton :: Char -> String -- | Monomorphically map the character in a string and return the -- transformed one charMap :: (Char -> Char) -> String -> String -- | Append a Char to the end of the String and return this new String snoc :: String -> Char -> String -- | Prepend a Char to the beginning of the String and return this new -- String cons :: Char -> String -> String -- | Extract the String stripped of the last character and the last -- character if not empty -- -- If empty, Nothing is returned unsnoc :: String -> Maybe (String, Char) -- | Extract the First character of a string, and the String stripped of -- the first character. -- -- If empty, Nothing is returned uncons :: String -> Maybe (Char, String) -- | Look for a predicate in the String and return the matched character, -- if any. find :: (Char -> Bool) -> String -> Maybe Char -- | Return the index in unit of Char of the first occurence of the -- predicate returning True -- -- If not found, Nothing is returned findIndex :: (Char -> Bool) -> String -> Maybe (Offset Char) -- | Sort the character in a String using a specific sort function -- -- TODO: optimise not going through a list sortBy :: (Char -> Char -> Ordering) -> String -> String -- | Filter characters of a string using the predicate filter :: (Char -> Bool) -> String -> String -- | Reverse a string reverse :: String -> String -- | Replace all the occurrencies of needle with -- replacement in the haystack string. replace :: String -> String -> String -> String -- | Append a character to a String builder builderAppend :: PrimMonad state => Char -> Builder String MutableString Word8 state err () -- | Create a new String builder using chunks of sizeChunksI builderBuild :: PrimMonad m => Int -> Builder String MutableString Word8 m err () -> m (Either err String) builderBuild_ :: PrimMonad m => Int -> Builder String MutableString Word8 m () () -> m String 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 -- | Convert a String to the upper-case equivalent. Does not -- properly support multicharacter Unicode conversions. upper :: String -> String -- | Convert a String to the upper-case equivalent. Does not -- properly support multicharacter Unicode conversions. lower :: String -> String -- | Check whether the first string is a prefix of the second string. isPrefixOf :: String -> String -> Bool -- | Check whether the first string is a suffix of the second string. isSuffixOf :: String -> String -> Bool -- | Check whether the first string is contains within the second string. -- -- TODO: implemented the naive way and thus terribly inefficient, -- reimplement properly isInfixOf :: String -> String -> Bool -- | Try to strip a prefix from the start of a String. -- -- If the prefix is not starting the string, then Nothing is returned, -- otherwise the striped string is returned stripPrefix :: String -> String -> Maybe String -- | Try to strip a suffix from the end of a String. -- -- If the suffix is not ending the string, then Nothing is returned, -- otherwise the striped string is returned stripSuffix :: String -> String -> Maybe String all :: (Char -> Bool) -> String -> Bool any :: (Char -> Bool) -> String -> Bool -- | Split lines in a string using newline as separation. -- -- Note that carriage return preceding a newline are also strip for -- maximum compatibility between Windows and Unix system. lines :: String -> [String] -- | Split words in a string using spaces as separation -- --
--   words "Hello Foundation"
--   
-- -- words :: String -> [String] -- | Transform string src to base64 binary representation. toBase64 :: String -> String -- | Transform string src to URL-safe base64 binary -- representation. The result will be either padded or unpadded, -- depending on the boolean padded argument. toBase64URL :: Bool -> String -> String -- | Transform string src to OpenBSD base64 binary representation. toBase64OpenBSD :: String -> String instance GHC.Enum.Bounded Basement.String.Encoding instance GHC.Enum.Enum Basement.String.Encoding instance GHC.Show.Show Basement.String.Encoding instance GHC.Classes.Ord Basement.String.Encoding instance GHC.Classes.Eq Basement.String.Encoding instance Data.Data.Data Basement.String.Encoding instance Basement.String.Encoding.Encoding.Encoding Basement.String.EncoderUTF8 -- | Flexible Type convertion -- -- From is multi parameter type class that allow converting from a to b. -- -- Only type that are valid to convert to another type should be From -- instance; otherwise TryFrom should be used. -- -- Into (resp TryInto) allows the contrary instances to be able to -- specify the destination type before the source. This is practical with -- TypeApplication module Basement.From -- | Class of things that can be converted from a to b. -- -- In a valid instance, the source should be always representable by the -- destination, otherwise the instance should be using TryFrom class From a b from :: From a b => a -> b type Into b a = From a b -- | Class of things that can mostly be converted from a to b, but with -- possible error cases. class TryFrom a b tryFrom :: TryFrom a b => a -> Maybe b type TryInto b a = TryFrom a b -- | Same as from but reverse the type variable so that the destination -- type can be specified first -- -- e.g. converting: -- -- from _ Word (10 :: Int) -- -- into @Word (10 :: Int) into :: Into b a => a -> b -- | same as tryFrom but reversed tryInto :: TryInto b a => a -> Maybe b instance Basement.From.From a a instance Basement.From.From GHC.Types.Int GHC.Types.Word instance Basement.From.From GHC.Types.Word GHC.Types.Int instance Basement.Numerical.Number.IsNatural n => Basement.From.From n GHC.Natural.Natural instance Basement.Numerical.Number.IsIntegral n => Basement.From.From n GHC.Integer.Type.Integer instance Basement.From.From GHC.Int.Int8 GHC.Int.Int16 instance Basement.From.From GHC.Int.Int8 GHC.Int.Int32 instance Basement.From.From GHC.Int.Int8 GHC.Int.Int64 instance Basement.From.From GHC.Int.Int8 GHC.Types.Int instance Basement.From.From GHC.Int.Int16 GHC.Int.Int32 instance Basement.From.From GHC.Int.Int16 GHC.Int.Int64 instance Basement.From.From GHC.Int.Int16 GHC.Types.Int instance Basement.From.From GHC.Int.Int32 GHC.Int.Int64 instance Basement.From.From GHC.Int.Int32 GHC.Types.Int instance Basement.From.From GHC.Types.Int GHC.Int.Int64 instance Basement.From.From GHC.Word.Word8 GHC.Word.Word16 instance Basement.From.From GHC.Word.Word8 GHC.Word.Word32 instance Basement.From.From GHC.Word.Word8 GHC.Word.Word64 instance Basement.From.From GHC.Word.Word8 Basement.Types.Word128.Word128 instance Basement.From.From GHC.Word.Word8 Basement.Types.Word256.Word256 instance Basement.From.From GHC.Word.Word8 GHC.Types.Word instance Basement.From.From GHC.Word.Word8 GHC.Int.Int16 instance Basement.From.From GHC.Word.Word8 GHC.Int.Int32 instance Basement.From.From GHC.Word.Word8 GHC.Int.Int64 instance Basement.From.From GHC.Word.Word8 GHC.Types.Int instance Basement.From.From GHC.Word.Word16 GHC.Word.Word32 instance Basement.From.From GHC.Word.Word16 GHC.Word.Word64 instance Basement.From.From GHC.Word.Word16 Basement.Types.Word128.Word128 instance Basement.From.From GHC.Word.Word16 Basement.Types.Word256.Word256 instance Basement.From.From GHC.Word.Word16 GHC.Types.Word instance Basement.From.From GHC.Word.Word32 GHC.Word.Word64 instance Basement.From.From GHC.Word.Word32 Basement.Types.Word128.Word128 instance Basement.From.From GHC.Word.Word32 Basement.Types.Word256.Word256 instance Basement.From.From GHC.Word.Word32 GHC.Types.Word instance Basement.From.From GHC.Word.Word64 Basement.Types.Word128.Word128 instance Basement.From.From GHC.Word.Word64 Basement.Types.Word256.Word256 instance Basement.From.From GHC.Types.Word GHC.Word.Word64 instance Basement.From.From (GHC.Base.Maybe a) (Data.Either.Either () a) instance Basement.From.From (Basement.Types.OffsetSize.CountOf ty) GHC.Types.Int instance Basement.From.From (Basement.Types.OffsetSize.CountOf ty) GHC.Types.Word instance Basement.From.From (Data.Either.Either a b) (Basement.These.These a b) instance Basement.PrimType.PrimType ty => Basement.From.From (Basement.Block.Base.Block ty) (Basement.UArray.Base.UArray ty) instance Basement.PrimType.PrimType ty => Basement.From.From (Basement.BoxedArray.Array ty) (Basement.UArray.Base.UArray ty) instance Basement.PrimType.PrimType ty => Basement.From.From (Basement.UArray.Base.UArray ty) (Basement.Block.Base.Block ty) instance Basement.PrimType.PrimType ty => Basement.From.From (Basement.BoxedArray.Array ty) (Basement.Block.Base.Block ty) instance Basement.PrimType.PrimType ty => Basement.From.From (Basement.UArray.Base.UArray ty) (Basement.BoxedArray.Array ty) instance Basement.From.From Basement.UTF8.Base.String (Basement.UArray.Base.UArray GHC.Word.Word8) instance Basement.From.From Basement.Types.AsciiString.AsciiString Basement.UTF8.Base.String instance Basement.From.From Basement.Types.AsciiString.AsciiString (Basement.UArray.Base.UArray GHC.Word.Word8) instance Basement.From.TryFrom (Basement.UArray.Base.UArray GHC.Word.Word8) Basement.UTF8.Base.String instance Basement.From.From (Basement.BlockN.BlockN n ty) (Basement.Block.Base.Block ty) instance (Basement.Nat.NatWithinBound GHC.Types.Int n, Basement.PrimType.PrimType ty) => Basement.From.From (Basement.BlockN.BlockN n ty) (Basement.UArray.Base.UArray ty) instance (Basement.Nat.NatWithinBound GHC.Types.Int n, Basement.PrimType.PrimType ty) => Basement.From.From (Basement.BlockN.BlockN n ty) (Basement.BoxedArray.Array ty) instance (Basement.Nat.NatWithinBound (Basement.Types.OffsetSize.CountOf ty) n, GHC.TypeLits.KnownNat n, Basement.PrimType.PrimType ty) => Basement.From.TryFrom (Basement.Block.Base.Block ty) (Basement.BlockN.BlockN n ty) instance (Basement.Nat.NatWithinBound (Basement.Types.OffsetSize.CountOf ty) n, GHC.TypeLits.KnownNat n, Basement.PrimType.PrimType ty) => Basement.From.TryFrom (Basement.UArray.Base.UArray ty) (Basement.BlockN.BlockN n ty) instance (Basement.Nat.NatWithinBound (Basement.Types.OffsetSize.CountOf ty) n, GHC.TypeLits.KnownNat n, Basement.PrimType.PrimType ty) => Basement.From.TryFrom (Basement.BoxedArray.Array ty) (Basement.BlockN.BlockN n ty) instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word8 n) => Basement.From.From (Basement.Bounded.Zn64 n) GHC.Word.Word8 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word16 n) => Basement.From.From (Basement.Bounded.Zn64 n) GHC.Word.Word16 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word32 n) => Basement.From.From (Basement.Bounded.Zn64 n) GHC.Word.Word32 instance Basement.From.From (Basement.Bounded.Zn64 n) GHC.Word.Word64 instance Basement.From.From (Basement.Bounded.Zn64 n) Basement.Types.Word128.Word128 instance Basement.From.From (Basement.Bounded.Zn64 n) Basement.Types.Word256.Word256 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word8 n) => Basement.From.From (Basement.Bounded.Zn n) GHC.Word.Word8 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word16 n) => Basement.From.From (Basement.Bounded.Zn n) GHC.Word.Word16 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word32 n) => Basement.From.From (Basement.Bounded.Zn n) GHC.Word.Word32 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word64 n) => Basement.From.From (Basement.Bounded.Zn n) GHC.Word.Word64 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound Basement.Types.Word128.Word128 n) => Basement.From.From (Basement.Bounded.Zn n) Basement.Types.Word128.Word128 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound Basement.Types.Word256.Word256 n) => Basement.From.From (Basement.Bounded.Zn n) Basement.Types.Word256.Word256 instance (GHC.TypeLits.KnownNat n, Basement.Nat.NatWithinBound GHC.Word.Word64 n) => Basement.From.From (Basement.Bounded.Zn n) (Basement.Bounded.Zn64 n) instance GHC.TypeLits.KnownNat n => Basement.From.From (Basement.Bounded.Zn64 n) (Basement.Bounded.Zn n)