-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | An enhanced core prelude; a common foundation for alternate preludes. -- -- Please see the README on Github at -- https://github.com/snoyberg/basic-prelude#readme @package basic-prelude @version 0.7.0 module CorePrelude -- | Application operator. This operator is redundant, since ordinary -- application (f x) means the same as (f $ x). -- However, $ has low, right-associative binding precedence, so it -- sometimes allows parentheses to be omitted; for example: -- --
--   f $ g $ h x  =  f (g (h x))
--   
-- -- It is also useful in higher-order situations, such as map -- ($ 0) xs, or zipWith ($) fs xs. ($) :: (a -> b) -> a -> b infixr 0 $ -- | Strict (call-by-value) application operator. It takes a function and -- an argument, evaluates the argument to weak head normal form (WHNF), -- then calls the function with that value. ($!) :: (a -> b) -> a -> b infixr 0 $! -- | Boolean "and" (&&) :: Bool -> Bool -> Bool infixr 3 && -- | Boolean "or" (||) :: Bool -> Bool -> Bool infixr 2 || -- | morphism composition (.) :: Category k cat => forall (b :: k) (c :: k) (a :: k). cat b c -> cat a b -> cat a c -- | Boolean "not" not :: Bool -> Bool -- | otherwise is defined as the value True. It helps to make -- guards more readable. eg. -- --
--   f x | x < 0     = ...
--       | otherwise = ...
--   
otherwise :: Bool -- | 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 putStr :: MonadIO m => Text -> m () putStrLn :: MonadIO m => Text -> m () print :: (MonadIO m, Show a) => a -> m () getArgs :: MonadIO m => m [Text] -- | error applied to Text -- -- Since 0.4.1 terror :: HasCallStack => Text -> a odd :: Integral a => a -> Bool even :: Integral a => a -> Bool -- | uncurry converts a curried function to a function on pairs. uncurry :: (a -> b -> c) -> (a, b) -> c -- | curry converts an uncurried function to a curried function. curry :: ((a, b) -> c) -> a -> b -> c -- | Swap the components of a pair. swap :: (a, b) -> (b, a) -- | until p f yields the result of applying f -- until p holds. until :: (a -> Bool) -> (a -> a) -> a -> a -- | asTypeOf is a type-restricted version of const. It is -- usually used as an infix operator, and its typing forces its first -- argument (which is usually overloaded) to have the same type as the -- second. asTypeOf :: a -> a -> a -- | A special case of error. It is expected that compilers will -- recognize this and insert error messages which are more appropriate to -- the context in which undefined appears. undefined :: HasCallStack => a -- | The value of seq a b is bottom if a is bottom, and -- otherwise equal to b. seq is usually introduced to -- improve performance by avoiding unneeded laziness. -- -- A note on evaluation order: the expression seq a b does -- not guarantee that a will be evaluated before -- b. The only guarantee given by seq is that the both -- a and b will be evaluated before seq -- returns a value. In particular, this means that b may be -- evaluated before a. If you need to guarantee a specific order -- of evaluation, you must use the function pseq from the -- "parallel" package. seq :: a -> b -> b -- | 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] -- | 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 -- | Parsing of Strings, producing values. -- -- Derived instances of Read make the following assumptions, which -- derived instances of Show obey: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Read in Haskell 2010 is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readsPrec d r =  readParen (d > app_prec)
--                            (\r -> [(Leaf m,t) |
--                                    ("Leaf",s) <- lex r,
--                                    (m,t) <- readsPrec (app_prec+1) s]) r
--   
--                         ++ readParen (d > up_prec)
--                            (\r -> [(u:^:v,w) |
--                                    (u,s) <- readsPrec (up_prec+1) r,
--                                    (":^:",t) <- lex s,
--                                    (v,w) <- readsPrec (up_prec+1) t]) r
--   
--             where app_prec = 10
--                   up_prec = 5
--   
-- -- Note that right-associativity of :^: is unused. -- -- The derived instance in GHC is equivalent to -- --
--   instance (Read a) => Read (Tree a) where
--   
--           readPrec = parens $ (prec app_prec $ do
--                                    Ident "Leaf" <- lexP
--                                    m <- step readPrec
--                                    return (Leaf m))
--   
--                        +++ (prec up_prec $ do
--                                    u <- step readPrec
--                                    Symbol ":^:" <- lexP
--                                    v <- step readPrec
--                                    return (u :^: v))
--   
--             where app_prec = 10
--                   up_prec = 5
--   
--           readListPrec = readListPrecDefault
--   
class Read 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 -- | The Monad class defines the basic operations over a -- monad, a concept from a branch of mathematics known as -- category theory. From the perspective of a Haskell programmer, -- however, it is best to think of a monad as an abstract datatype -- of actions. Haskell's do expressions provide a convenient -- syntax for writing monadic expressions. -- -- Instances of Monad should satisfy the following laws: -- -- -- -- Furthermore, the Monad and Applicative operations should -- relate as follows: -- -- -- -- The above laws imply: -- -- -- -- and that pure and (<*>) satisfy the applicative -- functor laws. -- -- The instances of Monad for lists, Maybe and IO -- defined in the Prelude satisfy these laws. class Applicative m => Monad (m :: * -> *) -- | Sequentially compose two actions, passing any value produced by the -- first as an argument to the second. (>>=) :: Monad m => m a -> (a -> m b) -> m b -- | Sequentially compose two actions, discarding any value produced by the -- first, like sequencing operators (such as the semicolon) in imperative -- languages. (>>) :: Monad m => m a -> m b -> m b -- | Inject a value into the monadic type. return :: Monad m => a -> m a -- | Fail with a message. This operation is not part of the mathematical -- definition of a monad, but is invoked on pattern-match failure in a -- do expression. -- -- As part of the MonadFail proposal (MFP), this function is moved to its -- own class MonadFail (see Control.Monad.Fail for more -- details). The definition here will be removed in a future release. fail :: Monad m => String -> m a -- | Same as >>=, but with the arguments interchanged. (=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 =<< -- | Class for string-like datastructures; used by the overloaded string -- extension (-XOverloadedStrings in GHC). class IsString a fromString :: IsString a => String -> a -- | Basic numeric class. class Num a (+) :: Num a => a -> a -> a (-) :: Num a => a -> a -> a (*) :: Num a => a -> a -> a -- | Unary negation. negate :: Num a => a -> a -- | Absolute value. abs :: Num a => a -> a -- | Sign of a number. The functions abs and signum should -- satisfy the law: -- --
--   abs x * signum x == x
--   
-- -- For real numbers, the signum is either -1 (negative), -- 0 (zero) or 1 (positive). signum :: Num a => a -> a -- | Conversion from an Integer. An integer literal represents the -- application of the function fromInteger to the appropriate -- value of type Integer, so such literals have type -- (Num a) => a. fromInteger :: Num a => Integer -> a class (Num a, Ord a) => Real a -- | the rational equivalent of its real argument with full precision toRational :: Real a => a -> Rational -- | Integral numbers, supporting integer division. class (Real a, Enum a) => Integral a -- | integer division truncated toward zero quot :: Integral a => a -> a -> a -- | integer remainder, satisfying -- --
--   (x `quot` y)*y + (x `rem` y) == x
--   
rem :: Integral a => a -> a -> a -- | integer division truncated toward negative infinity div :: Integral a => a -> a -> a -- | integer modulus, satisfying -- --
--   (x `div` y)*y + (x `mod` y) == x
--   
mod :: Integral a => a -> a -> a -- | simultaneous quot and rem quotRem :: Integral a => a -> a -> (a, a) -- | simultaneous div and mod divMod :: Integral a => a -> a -> (a, a) -- | conversion to Integer toInteger :: Integral a => a -> Integer -- | Fractional numbers, supporting real division. class Num a => Fractional a -- | fractional division (/) :: Fractional a => a -> a -> a -- | reciprocal fraction recip :: Fractional a => a -> a -- | Conversion from a Rational (that is Ratio -- Integer). A floating literal stands for an application of -- fromRational to a value of type Rational, so such -- literals have type (Fractional a) => a. fromRational :: Fractional a => Rational -> a -- | Trigonometric and hyperbolic functions and related functions. class Fractional a => Floating a pi :: Floating a => a exp :: Floating a => a -> a log :: Floating a => a -> a sqrt :: Floating a => a -> a (**) :: Floating a => a -> a -> a logBase :: Floating a => a -> a -> a sin :: Floating a => a -> a cos :: Floating a => a -> a tan :: Floating a => a -> a asin :: Floating a => a -> a acos :: Floating a => a -> a atan :: Floating a => a -> a sinh :: Floating a => a -> a cosh :: Floating a => a -> a tanh :: Floating a => a -> a asinh :: Floating a => a -> a acosh :: Floating a => a -> a atanh :: Floating a => a -> a -- | Extracting components of fractions. class (Real a, Fractional a) => RealFrac a -- | The function properFraction takes a real fractional number -- x and returns a pair (n,f) such that x = -- n+f, and: -- -- -- -- The default definitions of the ceiling, floor, -- truncate and round functions are in terms of -- properFraction. properFraction :: (RealFrac a, Integral b) => a -> (b, a) -- | truncate x returns the integer nearest x -- between zero and x truncate :: (RealFrac a, Integral b) => a -> b -- | round x returns the nearest integer to x; the -- even integer if x is equidistant between two integers round :: (RealFrac a, Integral b) => a -> b -- | ceiling x returns the least integer not less than -- x ceiling :: (RealFrac a, Integral b) => a -> b -- | floor x returns the greatest integer not greater than -- x floor :: (RealFrac a, Integral b) => a -> b -- | Efficient, machine-independent access to the components of a -- floating-point number. class (RealFrac a, Floating a) => RealFloat a -- | a constant function, returning the radix of the representation (often -- 2) floatRadix :: RealFloat a => a -> Integer -- | a constant function, returning the number of digits of -- floatRadix in the significand floatDigits :: RealFloat a => a -> Int -- | a constant function, returning the lowest and highest values the -- exponent may assume floatRange :: RealFloat a => a -> (Int, Int) -- | The function decodeFloat applied to a real floating-point -- number returns the significand expressed as an Integer and an -- appropriately scaled exponent (an Int). If -- decodeFloat x yields (m,n), then x -- is equal in value to m*b^^n, where b is the -- floating-point radix, and furthermore, either m and -- n are both zero or else b^(d-1) <= abs m < -- b^d, where d is the value of floatDigits -- x. In particular, decodeFloat 0 = (0,0). If the -- type contains a negative zero, also decodeFloat (-0.0) = -- (0,0). The result of decodeFloat x is -- unspecified if either of isNaN x or -- isInfinite x is True. decodeFloat :: RealFloat a => a -> (Integer, Int) -- | encodeFloat performs the inverse of decodeFloat in the -- sense that for finite x with the exception of -0.0, -- uncurry encodeFloat (decodeFloat x) = -- x. encodeFloat m n is one of the two closest -- representable floating-point numbers to m*b^^n (or -- ±Infinity if overflow occurs); usually the closer, but if -- m contains too many bits, the result may be rounded in the -- wrong direction. encodeFloat :: RealFloat a => Integer -> Int -> a -- | exponent corresponds to the second component of -- decodeFloat. exponent 0 = 0 and for finite -- nonzero x, exponent x = snd (decodeFloat x) -- + floatDigits x. If x is a finite floating-point -- number, it is equal in value to significand x * b ^^ -- exponent x, where b is the floating-point radix. -- The behaviour is unspecified on infinite or NaN values. exponent :: RealFloat a => a -> Int -- | The first component of decodeFloat, scaled to lie in the open -- interval (-1,1), either 0.0 or of absolute -- value >= 1/b, where b is the floating-point -- radix. The behaviour is unspecified on infinite or NaN -- values. significand :: RealFloat a => a -> a -- | multiplies a floating-point number by an integer power of the radix scaleFloat :: RealFloat a => Int -> a -> a -- | True if the argument is an IEEE "not-a-number" (NaN) value isNaN :: RealFloat a => a -> Bool -- | True if the argument is an IEEE infinity or negative infinity isInfinite :: RealFloat a => a -> Bool -- | True if the argument is too small to be represented in -- normalized format isDenormalized :: RealFloat a => a -> Bool -- | True if the argument is an IEEE negative zero isNegativeZero :: RealFloat a => a -> Bool -- | True if the argument is an IEEE floating point number isIEEE :: RealFloat a => a -> Bool -- | a version of arctangent taking two real floating-point arguments. For -- real floating x and y, atan2 y x -- computes the angle (from the positive x-axis) of the vector from the -- origin to the point (x,y). atan2 y x returns -- a value in the range [-pi, pi]. It follows the -- Common Lisp semantics for the origin when signed zeroes are supported. -- atan2 y 1, with y in a type that is -- RealFloat, should return the same value as atan -- y. A default definition of atan2 is provided, but -- implementors can provide a more accurate implementation. atan2 :: RealFloat a => a -> a -> a -- | The Maybe type encapsulates an optional value. A value of type -- Maybe a either contains a value of type a -- (represented as Just a), or it is empty (represented -- as Nothing). Using Maybe is a good way to deal with -- errors or exceptional cases without resorting to drastic measures such -- as error. -- -- The Maybe type is also a monad. It is a simple kind of error -- monad, where all errors are represented by Nothing. A richer -- error monad can be built using the Either type. data Maybe a :: * -> * Nothing :: Maybe a Just :: a -> Maybe a data Ordering :: * LT :: Ordering EQ :: Ordering GT :: Ordering data Bool :: * False :: Bool True :: Bool -- | The character type Char is an enumeration whose values -- represent Unicode (or equivalently ISO/IEC 10646) characters (see -- http://www.unicode.org/ for details). This set extends the ISO -- 8859-1 (Latin-1) character set (the first 256 characters), which is -- itself an extension of the ASCII character set (the first 128 -- characters). A character literal in Haskell has type Char. -- -- To convert a Char to or from the corresponding Int value -- defined by Unicode, use toEnum and fromEnum from the -- Enum class respectively (or equivalently ord and -- chr). data Char :: * -- | A value of type IO a is a computation which, when -- performed, does some I/O before returning a value of type a. -- -- There is really only one way to "perform" an I/O action: bind it to -- Main.main in your program. When your program is run, the I/O -- will be performed. It isn't possible to perform I/O from an arbitrary -- function, unless that function is itself in the IO monad and -- called at some point, directly or indirectly, from Main.main. -- -- IO is a monad, so IO actions can be combined using -- either the do-notation or the >> and >>= -- operations from the Monad class. data IO a :: * -> * -- | The Either type represents values with two possibilities: a -- value of type Either a b is either Left -- a or Right b. -- -- The Either type is sometimes used to represent a value which is -- either correct or an error; by convention, the Left constructor -- is used to hold an error value and the Right constructor is -- used to hold a correct value (mnemonic: "right" also means "correct"). -- --

Examples

-- -- The type Either String Int is the type -- of values which can be either a String or an Int. The -- Left constructor can be used only on Strings, and the -- Right constructor can be used only on Ints: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> s
--   Left "foo"
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> n
--   Right 3
--   
--   >>> :type s
--   s :: Either String Int
--   
--   >>> :type n
--   n :: Either String Int
--   
-- -- The fmap from our Functor instance will ignore -- Left values, but will apply the supplied function to values -- contained in a Right: -- --
--   >>> let s = Left "foo" :: Either String Int
--   
--   >>> let n = Right 3 :: Either String Int
--   
--   >>> fmap (*2) s
--   Left "foo"
--   
--   >>> fmap (*2) n
--   Right 6
--   
-- -- The Monad instance for Either allows us to chain -- together multiple actions which may fail, and fail overall if any of -- the individual steps failed. First we'll write a function that can -- either parse an Int from a Char, or fail. -- --
--   >>> import Data.Char ( digitToInt, isDigit )
--   
--   >>> :{
--       let parseEither :: Char -> Either String Int
--           parseEither c
--             | isDigit c = Right (digitToInt c)
--             | otherwise = Left "parse error"
--   
--   >>> :}
--   
-- -- The following should work, since both '1' and '2' -- can be parsed as Ints. -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither '1'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Right 3
--   
-- -- But the following should fail overall, since the first operation where -- we attempt to parse 'm' as an Int will fail: -- --
--   >>> :{
--       let parseMultiple :: Either String Int
--           parseMultiple = do
--             x <- parseEither 'm'
--             y <- parseEither '2'
--             return (x + y)
--   
--   >>> :}
--   
-- --
--   >>> parseMultiple
--   Left "parse error"
--   
data Either a b :: * -> * -> * Left :: a -> Either a b Right :: b -> Either a b -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A ByteString contains 8-bit bytes, or by using the operations -- from Data.ByteString.Char8 it can be interpreted as containing -- 8-bit characters. data ByteString :: * type LByteString = ByteString -- | A space efficient, packed, unboxed Unicode text type. data Text :: * type LText = Text -- | A Map from keys k to values a. data Map k a :: * -> * -> * -- | A map from keys to values. A map cannot contain duplicate keys; each -- key can map to at most one value. data HashMap k v :: * -> * -> * -- | A map of integers to values a. data IntMap a :: * -> * -- | A set of values a. data Set a :: * -> * -- | A set of values. A set cannot contain duplicate values. data HashSet a :: * -> * -- | A set of integers. data IntSet :: * -- | General-purpose finite sequences. data Seq a :: * -> * -- | Boxed vectors, supporting efficient slicing. data Vector a :: * -> * type UVector = Vector class (Vector Vector a, MVector MVector a) => Unbox a type SVector = Vector -- | The member functions of this class facilitate writing values of -- primitive types to raw memory (which may have been allocated with the -- above mentioned routines) and reading values from blocks of raw -- memory. The class, furthermore, includes support for computing the -- storage requirements and alignment restrictions of storable types. -- -- Memory addresses are represented as values of type Ptr -- a, for some a which is an instance of class -- Storable. The type argument to Ptr helps provide some -- valuable type safety in FFI code (you can't mix pointers of different -- types without an explicit cast), while helping the Haskell type system -- figure out which marshalling method is needed for a given pointer. -- -- All marshalling between Haskell and a foreign language ultimately -- boils down to translating Haskell data structures into the binary -- representation of a corresponding data structure of the foreign -- language and vice versa. To code this marshalling in Haskell, it is -- necessary to manipulate primitive data types stored in unstructured -- memory blocks. The class Storable facilitates this manipulation -- on all types for which it is instantiated, which are the standard -- basic types of Haskell, the fixed size Int types -- (Int8, Int16, Int32, Int64), the fixed -- size Word types (Word8, Word16, Word32, -- Word64), StablePtr, all types from -- Foreign.C.Types, as well as Ptr. class Storable a -- | The class of types that can be converted to a hash value. -- -- Minimal implementation: hashWithSalt. class Hashable a -- | Return a hash value for the argument, using the given salt. -- -- The general contract of hashWithSalt is: -- -- hashWithSalt :: Hashable a => Int -> a -> Int -- | Like hashWithSalt, but no salt is used. The default -- implementation uses hashWithSalt with some default salt. -- Instances might want to implement this method to provide a more -- efficient implementation than the default implementation. hash :: Hashable a => a -> Int -- | A Word is an unsigned integral type, with the same size as -- Int. data Word :: * -- | 8-bit unsigned integer type data Word8 :: * -- | 32-bit unsigned integer type data Word32 :: * -- | 64-bit unsigned integer type data Word64 :: * -- | 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 :: * -- | 32-bit signed integer type data Int32 :: * -- | 64-bit signed integer type data Int64 :: * -- | Invariant: Jn# and Jp# are used iff value doesn't fit in -- S# -- -- Useful properties resulting from the invariants: -- -- data Integer :: * -- | Arbitrary-precision rational numbers, represented as a ratio of two -- Integer values. A rational number may be constructed using the -- % operator. type Rational = Ratio Integer -- | Single-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- single-precision type. data Float :: * -- | Double-precision floating point numbers. It is desirable that this -- type be at least equal in range and precision to the IEEE -- double-precision type. data Double :: * -- | raise a number to a non-negative integral power (^) :: (Num a, Integral b) => a -> b -> a infixr 8 ^ -- | raise a number to an integral power (^^) :: (Fractional a, Integral b) => a -> b -> a infixr 8 ^^ -- | the same as flip (-). -- -- Because - is treated specially in the Haskell grammar, -- (- e) is not a section, but an application of -- prefix negation. However, (subtract -- exp) is equivalent to the disallowed section. subtract :: Num a => a -> a -> a -- | general coercion from integral types fromIntegral :: (Integral a, Num b) => a -> b -- | general coercion to fractional types realToFrac :: (Real a, Fractional b) => a -> b -- | The class of monoids (types with an associative binary operation that -- has an identity). Instances should satisfy the following laws: -- -- -- -- The method names refer to the monoid of lists under concatenation, but -- there are many other instances. -- -- Some types can be viewed as a monoid in more than one way, e.g. both -- addition and multiplication on numbers. In such cases we often define -- newtypes and make those instances of Monoid, e.g. -- Sum and Product. class Monoid a -- | Identity of mappend mempty :: Monoid a => a -- | An associative operation mappend :: Monoid a => a -> a -> a -- | Fold a list using the monoid. For most types, the default definition -- for mconcat will be used, but the function is included in the -- class definition so that an optimized version can be provided for -- specific types. mconcat :: Monoid a => [a] -> a -- | An infix synonym for mappend. (<>) :: Monoid m => m -> m -> m infixr 6 <> -- | Data structures that can be folded. -- -- For example, given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Foldable Tree where
--      foldMap f Empty = mempty
--      foldMap f (Leaf x) = f x
--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
--   
-- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
--   instance Foldable Tree where
--      foldr f z Empty = z
--      foldr f z (Leaf x) = f x z
--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable (t :: * -> *) -- | The sum of a collection of actions, generalizing concat. asum :: (Foldable t, Alternative f) => t (f a) -> f a -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Traversable Tree where
--      traverse f Empty = pure Empty
--      traverse f (Leaf x) = Leaf <$> f x
--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
--   
-- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- -- class (Functor t, Foldable t) => Traversable (t :: * -> *) -- | Send the first component of the input through the argument arrow, and -- copy the rest unchanged to the output. first :: Arrow a => forall b c d. a b c -> a (b, d) (c, d) -- | A mirror image of first. -- -- The default definition may be overridden with a more efficient version -- if desired. second :: Arrow a => forall b c d. a b c -> a (d, b) (d, c) -- | Split the input between the two argument arrows and combine their -- output. Note that this is in general not a functor. -- -- The default definition may be overridden with a more efficient version -- if desired. (***) :: Arrow a => forall b c b' c'. a b c -> a b' c' -> a (b, b') (c, c') -- | Fanout: send the input to both argument arrows and combine their -- output. -- -- The default definition may be overridden with a more efficient version -- if desired. (&&&) :: Arrow a => forall b c c'. a b c -> a b c' -> a b (c, c') -- | Case analysis for the Bool type. bool x y p -- evaluates to x when p is False, and evaluates -- to y when p is True. -- -- This is equivalent to if p then y else x; that is, one can -- think of it as an if-then-else construct with its arguments reordered. -- --

Examples

-- -- Basic usage: -- --
--   >>> bool "foo" "bar" True
--   "bar"
--   
--   >>> bool "foo" "bar" False
--   "foo"
--   
-- -- Confirm that bool x y p and if p then y else -- x are equivalent: -- --
--   >>> let p = True; x = "bar"; y = "foo"
--   
--   >>> bool x y p == if p then y else x
--   True
--   
--   >>> let p = False
--   
--   >>> bool x y p == if p then y else x
--   True
--   
bool :: a -> a -> Bool -> a -- | The mapMaybe function is a version of map which can -- throw out elements. In particular, the functional argument returns -- something of type Maybe b. If this is Nothing, -- no element is added on to the result list. If it is Just -- b, then b is included in the result list. -- --

Examples

-- -- Using mapMaybe f x is a shortcut for -- catMaybes $ map f x in most cases: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> let readMaybeInt = readMaybe :: String -> Maybe Int
--   
--   >>> mapMaybe readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
--   >>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
--   [1,3]
--   
-- -- If we map the Just constructor, the entire list should be -- returned: -- --
--   >>> mapMaybe Just [1,2,3]
--   [1,2,3]
--   
mapMaybe :: (a -> Maybe b) -> [a] -> [b] -- | The catMaybes function takes a list of Maybes and -- returns a list of all the Just values. -- --

Examples

-- -- Basic usage: -- --
--   >>> catMaybes [Just 1, Nothing, Just 3]
--   [1,3]
--   
-- -- When constructing a list of Maybe values, catMaybes can -- be used to return all of the "success" results (if the list is the -- result of a map, then mapMaybe would be more -- appropriate): -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [Just 1,Nothing,Just 3]
--   
--   >>> catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ]
--   [1,3]
--   
catMaybes :: [Maybe a] -> [a] -- | The fromMaybe function takes a default value and and -- Maybe value. If the Maybe is Nothing, it returns -- the default values; otherwise, it returns the value contained in the -- Maybe. -- --

Examples

-- -- Basic usage: -- --
--   >>> fromMaybe "" (Just "Hello, World!")
--   "Hello, World!"
--   
-- --
--   >>> fromMaybe "" Nothing
--   ""
--   
-- -- Read an integer from a string using readMaybe. If we fail to -- parse an integer, we want to return 0 by default: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> fromMaybe 0 (readMaybe "5")
--   5
--   
--   >>> fromMaybe 0 (readMaybe "")
--   0
--   
fromMaybe :: a -> Maybe a -> a -- | The isJust function returns True iff its argument is of -- the form Just _. -- --

Examples

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

Examples

-- -- Basic usage: -- --
--   >>> isNothing (Just 3)
--   False
--   
-- --
--   >>> isNothing (Just ())
--   False
--   
-- --
--   >>> isNothing Nothing
--   True
--   
-- -- Only the outer constructor is taken into consideration: -- --
--   >>> isNothing (Just Nothing)
--   False
--   
isNothing :: Maybe a -> Bool -- | The listToMaybe function returns Nothing on an empty -- list or Just a where a is the first element -- of the list. -- --

Examples

-- -- Basic usage: -- --
--   >>> listToMaybe []
--   Nothing
--   
-- --
--   >>> listToMaybe [9]
--   Just 9
--   
-- --
--   >>> listToMaybe [1,2,3]
--   Just 1
--   
-- -- Composing maybeToList with listToMaybe should be the -- identity on singleton/empty lists: -- --
--   >>> maybeToList $ listToMaybe [5]
--   [5]
--   
--   >>> maybeToList $ listToMaybe []
--   []
--   
-- -- But not on lists with more than one element: -- --
--   >>> maybeToList $ listToMaybe [1,2,3]
--   [1]
--   
listToMaybe :: [a] -> Maybe a -- | The maybeToList function returns an empty list when given -- Nothing or a singleton list when not given Nothing. -- --

Examples

-- -- Basic usage: -- --
--   >>> maybeToList (Just 7)
--   [7]
--   
-- --
--   >>> maybeToList Nothing
--   []
--   
-- -- One can use maybeToList to avoid pattern matching when combined -- with a function that (safely) works on lists: -- --
--   >>> import Text.Read ( readMaybe )
--   
--   >>> sum $ maybeToList (readMaybe "3")
--   3
--   
--   >>> sum $ maybeToList (readMaybe "")
--   0
--   
maybeToList :: Maybe a -> [a] -- | Partitions a list of Either into two lists. All the Left -- elements are extracted, in order, to the first component of the -- output. Similarly the Right elements are extracted to the -- second component of the output. -- --

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list
--   (["foo","bar","baz"],[3,7])
--   
-- -- The pair returned by partitionEithers x should be the -- same pair as (lefts x, rights x): -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> partitionEithers list == (lefts list, rights list)
--   True
--   
partitionEithers :: [Either a b] -> ([a], [b]) -- | Extracts from a list of Either all the Left elements. -- All the Left elements are extracted in order. -- --

Examples

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

Examples

-- -- Basic usage: -- --
--   >>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
--   
--   >>> rights list
--   [3,7]
--   
rights :: [Either a b] -> [b] -- | (*) `on` f = \x y -> f x * f y. -- -- Typical usage: sortBy (compare `on` -- fst). -- -- Algebraic properties: -- -- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 `on` -- |
--   comparing p x y = compare (p x) (p y)
--   
-- -- Useful combinator for use in conjunction with the xxxBy -- family of functions from Data.List, for example: -- --
--   ... sortBy (comparing fst) ...
--   
comparing :: Ord a => (b -> a) -> b -> b -> Ordering equating :: Eq a => (b -> a) -> b -> b -> Bool -- | The Down type allows you to reverse sort order conveniently. A -- value of type Down a contains a value of type -- a (represented as Down a). If a has -- an Ord instance associated with it then comparing two -- values thus wrapped will give you the opposite of their normal sort -- order. This is particularly useful when sorting in generalised list -- comprehensions, as in: then sortWith by Down x -- -- Provides Show and Read instances (since: -- 4.7.0.0). newtype Down a :: * -> * Down :: a -> Down 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 -- | An infix synonym for fmap. -- -- The name of this operator is an allusion to $. Note the -- similarities between their types: -- --
--    ($)  ::              (a -> b) ->   a ->   b
--   (<$>) :: Functor f => (a -> b) -> f a -> f b
--   
-- -- Whereas $ is function application, <$> is -- function application lifted over a Functor. -- --

Examples

-- -- Convert from a Maybe Int to a -- Maybe String using show: -- --
--   >>> show <$> Nothing
--   Nothing
--   
--   >>> show <$> Just 3
--   Just "3"
--   
-- -- Convert from an Either Int Int to -- an Either Int String using -- show: -- --
--   >>> show <$> Left 17
--   Left 17
--   
--   >>> show <$> Right 17
--   Right "17"
--   
-- -- Double each element of a list: -- --
--   >>> (*2) <$> [1,2,3]
--   [2,4,6]
--   
-- -- Apply even to the second element of a pair: -- --
--   >>> even <$> (2,2)
--   (2,True)
--   
(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 <$> -- | An associative binary operation (<|>) :: Alternative f => forall a. f a -> f a -> f a -- | Left-to-right Kleisli composition of monads. (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 >=> -- | Lift a computation from the argument monad to the constructed monad. lift :: MonadTrans t => forall (m :: * -> *) a. Monad m => m a -> t m a -- | Monads in which IO computations may be embedded. Any monad -- built by applying a sequence of monad transformers to the IO -- monad will be an instance of this class. -- -- Instances should satisfy the following laws, which state that -- liftIO is a transformer of monads: -- -- class Monad m => MonadIO (m :: * -> *) -- | Lift a computation from the IO monad. liftIO :: MonadIO m => IO a -> m a -- | Lift a computation from the IO monad. liftIO :: MonadIO m => forall a. IO a -> m a -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
--   data MyException = ThisException | ThatException
--       deriving (Show, Typeable)
--   
--   instance Exception MyException
--   
-- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
--   *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException))
--   Caught ThisException
--   
-- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
--   ---------------------------------------------------------------------
--   -- Make the root exception type for all the exceptions in a compiler
--   
--   data SomeCompilerException = forall e . Exception e => SomeCompilerException e
--       deriving Typeable
--   
--   instance Show SomeCompilerException where
--       show (SomeCompilerException e) = show e
--   
--   instance Exception SomeCompilerException
--   
--   compilerExceptionToException :: Exception e => e -> SomeException
--   compilerExceptionToException = toException . SomeCompilerException
--   
--   compilerExceptionFromException :: Exception e => SomeException -> Maybe e
--   compilerExceptionFromException x = do
--       SomeCompilerException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make a subhierarchy for exceptions in the frontend of the compiler
--   
--   data SomeFrontendException = forall e . Exception e => SomeFrontendException e
--       deriving Typeable
--   
--   instance Show SomeFrontendException where
--       show (SomeFrontendException e) = show e
--   
--   instance Exception SomeFrontendException where
--       toException = compilerExceptionToException
--       fromException = compilerExceptionFromException
--   
--   frontendExceptionToException :: Exception e => e -> SomeException
--   frontendExceptionToException = toException . SomeFrontendException
--   
--   frontendExceptionFromException :: Exception e => SomeException -> Maybe e
--   frontendExceptionFromException x = do
--       SomeFrontendException a <- fromException x
--       cast a
--   
--   ---------------------------------------------------------------------
--   -- Make an exception type for a particular frontend compiler exception
--   
--   data MismatchedParentheses = MismatchedParentheses
--       deriving (Typeable, Show)
--   
--   instance Exception MismatchedParentheses where
--       toException   = frontendExceptionToException
--       fromException = frontendExceptionFromException
--   
-- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException))
--   Caught MismatchedParentheses
--   *Main> throw MismatchedParentheses catch e -> putStrLn ("Caught " ++ show (e :: IOException))
--   *** Exception: MismatchedParentheses
--   
class (Typeable * e, Show e) => Exception e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | The class Typeable allows a concrete representation of a type -- to be calculated. class Typeable k (a :: k) -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException :: * -- | Exceptions that occur in the IO monad. An -- IOException records a more specific error type, a descriptive -- string and maybe the handle that was used when the error was flagged. data IOException :: * -- | File and directory names are values of type String, whose -- precise meaning is operating system dependent. Files can be opened, -- yielding a handle which can then be used to operate on the contents of -- that file. type FilePath = String -- | Combine two paths with a path separator. If the second path starts -- with a path separator or a drive letter, then it returns the second. -- The intention is that readFile (dir </> file) -- will access the same file as setCurrentDirectory dir; readFile -- file. -- --
--   Posix:   "/directory" </> "file.ext" == "/directory/file.ext"
--   Windows: "/directory" </> "file.ext" == "/directory\\file.ext"
--            "directory" </> "/file.ext" == "/file.ext"
--   Valid x => (takeDirectory x </> takeFileName x) `equalFilePath` x
--   
-- -- Combined: -- --
--   Posix:   "/" </> "test" == "/test"
--   Posix:   "home" </> "bob" == "home/bob"
--   Posix:   "x:" </> "foo" == "x:/foo"
--   Windows: "C:\\foo" </> "bar" == "C:\\foo\\bar"
--   Windows: "home" </> "bob" == "home\\bob"
--   
-- -- Not combined: -- --
--   Posix:   "home" </> "/bob" == "/bob"
--   Windows: "home" </> "C:\\bob" == "C:\\bob"
--   
-- -- Not combined (tricky): -- -- On Windows, if a filepath starts with a single slash, it is relative -- to the root of the current drive. In [1], this is (confusingly) -- referred to as an absolute path. The current behavior of -- </> is to never combine these forms. -- --
--   Windows: "home" </> "/bob" == "/bob"
--   Windows: "home" </> "\\bob" == "\\bob"
--   Windows: "C:\\home" </> "\\bob" == "\\bob"
--   
-- -- On Windows, from [1]: "If a file name begins with only a disk -- designator but not the backslash after the colon, it is interpreted as -- a relative path to the current directory on the drive with the -- specified letter." The current behavior of </> is to -- never combine these forms. -- --
--   Windows: "D:\\foo" </> "C:bar" == "C:bar"
--   Windows: "C:\\foo" </> "C:bar" == "C:bar"
--   
() :: FilePath -> FilePath -> FilePath infixr 5 -- | Add an extension, even if there is already one there, equivalent to -- addExtension. -- --
--   "/directory/path" <.> "ext" == "/directory/path.ext"
--   "/directory/path" <.> ".ext" == "/directory/path.ext"
--   
(<.>) :: FilePath -> String -> FilePath infixr 7 <.> -- | A String is a list of characters. String constants in Haskell -- are values of type String. type String = [Char] -- | Like hashWithSalt, but no salt is used. The default -- implementation uses hashWithSalt with some default salt. -- Instances might want to implement this method to provide a more -- efficient implementation than the default implementation. hash :: Hashable a => a -> Int -- | Return a hash value for the argument, using the given salt. -- -- The general contract of hashWithSalt is: -- -- hashWithSalt :: Hashable a => Int -> a -> Int -- | BasicPrelude mostly re-exports several key libraries in their -- entirety. The exception is Data.List, where various functions are -- replaced by similar versions that are either generalized, operate on -- Text, or are implemented strictly. module BasicPrelude -- | Data structures that can be folded. -- -- For example, given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Foldable Tree where
--      foldMap f Empty = mempty
--      foldMap f (Leaf x) = f x
--      foldMap f (Node l k r) = foldMap f l `mappend` f k `mappend` foldMap f r
--   
-- -- This is suitable even for abstract types, as the monoid is assumed to -- satisfy the monoid laws. Alternatively, one could define -- foldr: -- --
--   instance Foldable Tree where
--      foldr f z Empty = z
--      foldr f z (Leaf x) = f x z
--      foldr f z (Node l k r) = foldr f (f k (foldr f z r)) l
--   
-- -- Foldable instances are expected to satisfy the following -- laws: -- --
--   foldr f z t = appEndo (foldMap (Endo . f) t ) z
--   
-- --
--   foldl f z t = appEndo (getDual (foldMap (Dual . Endo . flip f) t)) z
--   
-- --
--   fold = foldMap id
--   
-- -- sum, product, maximum, and minimum -- should all be essentially equivalent to foldMap forms, such -- as -- --
--   sum = getSum . foldMap Sum
--   
-- -- but may be less defined. -- -- If the type is also a Functor instance, it should satisfy -- --
--   foldMap f = fold . fmap f
--   
-- -- which implies that -- --
--   foldMap f . fmap g = foldMap (f . g)
--   
class Foldable (t :: * -> *) -- | Map each element of the structure to a monoid, and combine the -- results. foldMap :: (Foldable t, Monoid m) => (a -> m) -> t a -> m -- | Right-associative fold of a structure. -- -- In the case of lists, foldr, when applied to a binary operator, -- a starting value (typically the right-identity of the operator), and a -- list, reduces the list using the binary operator, from right to left: -- --
--   foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
--   
-- -- Note that, since the head of the resulting expression is produced by -- an application of the operator to the first element of the list, -- foldr can produce a terminating expression from an infinite -- list. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldr f z = foldr f z . toList
--   
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Right-associative fold of a structure, but with strict application of -- the operator. foldr' :: Foldable t => (a -> b -> b) -> b -> t a -> b -- | Left-associative fold of a structure. -- -- In the case of lists, foldl, when applied to a binary operator, -- a starting value (typically the left-identity of the operator), and a -- list, reduces the list using the binary operator, from left to right: -- --
--   foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
--   
-- -- Note that to produce the outermost application of the operator the -- entire input list must be traversed. This means that foldl' -- will diverge if given an infinite list. -- -- Also note that if you want an efficient left-fold, you probably want -- to use foldl' instead of foldl. The reason for this is -- that latter does not force the "inner" results (e.g. z f -- x1 in the above example) before applying them to the operator -- (e.g. to (f x2)). This results in a thunk chain -- O(n) elements long, which then must be evaluated from the -- outside-in. -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl f z . toList
--   
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | Left-associative fold of a structure but with strict application of -- the operator. -- -- This ensures that each step of the fold is forced to weak head normal -- form before being applied, avoiding the collection of thunks that -- would otherwise occur. This is often what you want to strictly reduce -- a finite list to a single, monolithic result (e.g. length). -- -- For a general Foldable structure this should be semantically -- identical to, -- --
--   foldl f z = foldl' f z . toList
--   
foldl' :: Foldable t => (b -> a -> b) -> b -> t a -> b -- | A variant of foldr that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldr1 f = foldr1 f . toList
--   
foldr1 :: Foldable t => (a -> a -> a) -> t a -> a -- | A variant of foldl that has no base case, and thus may only be -- applied to non-empty structures. -- --
--   foldl1 f = foldl1 f . toList
--   
foldl1 :: Foldable t => (a -> a -> a) -> t a -> a -- | Test whether the structure is empty. The default implementation is -- optimized for structures that are similar to cons-lists, because there -- is no general way to do better. null :: Foldable t => t a -> Bool -- | Returns the size/length of a finite structure as an Int. The -- default implementation is optimized for structures that are similar to -- cons-lists, because there is no general way to do better. length :: Foldable t => t a -> Int -- | Does the element occur in the structure? elem :: (Foldable t, Eq a) => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: (Foldable t, Ord a) => t a -> a -- | The least element of a non-empty structure. minimum :: (Foldable t, Ord a) => t a -> a -- | Does the element occur in the structure? elem :: Foldable t => forall a. Eq a => a -> t a -> Bool -- | The largest element of a non-empty structure. maximum :: Foldable t => forall a. Ord a => t a -> a -- | The least element of a non-empty structure. minimum :: Foldable t => forall a. Ord a => t a -> a -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and ignore the results. For a version that doesn't -- ignore the results see traverse. traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f () -- | Evaluate each action in the structure from left to right, and ignore -- the results. For a version that doesn't ignore the results see -- sequenceA. sequenceA_ :: (Foldable t, Applicative f) => t (f a) -> f () -- | for_ is traverse_ with its arguments flipped. For a -- version that doesn't ignore the results see for. -- --
--   >>> for_ [1..4] print
--   1
--   2
--   3
--   4
--   
for_ :: (Foldable t, Applicative f) => t a -> (a -> f b) -> f () maximumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a minimumBy :: Foldable t => (a -> a -> Ordering) -> t a -> a -- | Functors representing data structures that can be traversed from left -- to right. -- -- A definition of traverse must satisfy the following laws: -- -- -- -- A definition of sequenceA must satisfy the following laws: -- -- -- -- where an applicative transformation is a function -- --
--   t :: (Applicative f, Applicative g) => f a -> g a
--   
-- -- preserving the Applicative operations, i.e. -- -- -- -- and the identity functor Identity and composition of functors -- Compose are defined as -- --
--   newtype Identity a = Identity a
--   
--   instance Functor Identity where
--     fmap f (Identity x) = Identity (f x)
--   
--   instance Applicative Identity where
--     pure x = Identity x
--     Identity f <*> Identity x = Identity (f x)
--   
--   newtype Compose f g a = Compose (f (g a))
--   
--   instance (Functor f, Functor g) => Functor (Compose f g) where
--     fmap f (Compose x) = Compose (fmap (fmap f) x)
--   
--   instance (Applicative f, Applicative g) => Applicative (Compose f g) where
--     pure x = Compose (pure (pure x))
--     Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
--   
-- -- (The naturality law is implied by parametricity.) -- -- Instances are similar to Functor, e.g. given a data type -- --
--   data Tree a = Empty | Leaf a | Node (Tree a) a (Tree a)
--   
-- -- a suitable instance would be -- --
--   instance Traversable Tree where
--      traverse f Empty = pure Empty
--      traverse f (Leaf x) = Leaf <$> f x
--      traverse f (Node l k r) = Node <$> traverse f l <*> f k <*> traverse f r
--   
-- -- This is suitable even for abstract types, as the laws for -- <*> imply a form of associativity. -- -- The superclass instances should satisfy the following: -- -- class (Functor t, Foldable t) => Traversable (t :: * -> *) -- | Map each element of a structure to an action, evaluate these actions -- from left to right, and collect the results. For a version that -- ignores the results see traverse_. traverse :: (Traversable t, Applicative f) => (a -> f b) -> t a -> f (t b) -- | Evaluate each action in the structure from left to right, and and -- collect the results. For a version that ignores the results see -- sequenceA_. sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a) -- | Map each element of a structure to a monadic action, evaluate these -- actions from left to right, and collect the results. For a version -- that ignores the results see mapM_. mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) -- | Evaluate each monadic action in the structure from left to right, and -- collect the results. For a version that ignores the results see -- sequence_. sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) -- | for is traverse with its arguments flipped. For a -- version that ignores the results see for_. for :: (Traversable t, Applicative f) => t a -> (a -> f b) -> f (t b) -- |
--   map = fmap
--   
map :: (Functor f) => (a -> b) -> f a -> f b -- |
--   empty = mempty
--   
-- | Deprecated: Use mempty empty :: Monoid w => w -- |
--   (++) = mappend
--   
(++) :: Monoid w => w -> w -> w infixr 5 ++ -- |
--   concat = mconcat
--   
concat :: Monoid w => [w] -> w -- |
--   intercalate = mconcat .: intersperse
--   
intercalate :: Monoid w => w -> [w] -> w -- | Compute the sum of a finite list of numbers. sum :: (Foldable f, Num a) => f a -> a -- | Compute the product of a finite list of numbers. product :: (Foldable f, Num a) => f a -> a -- | Convert a value to readable Text tshow :: Show a => a -> Text -- | Convert a value to readable IsString -- -- Since 0.3.12 fromShow :: (Show a, IsString b) => a -> b -- | Parse Text to a value read :: Read a => Text -> a -- | The readIO function is similar to read except that it signals parse -- failure to the IO monad instead of terminating the program. readIO :: (MonadIO m, Read a) => Text -> m a -- | Read a file and return the contents of the file as Text. The entire -- file is read strictly. readFile :: MonadIO m => FilePath -> m Text -- | Write Text to a file. The file is truncated to zero length before -- writing begins. writeFile :: MonadIO m => FilePath -> Text -> m () -- | Write Text to the end of a file. appendFile :: MonadIO m => FilePath -> Text -> m () -- | O(n) Breaks a Text up into a list of Texts at -- newline Chars. The resulting strings do not contain newlines. lines :: Text -> [Text] -- | O(n) Breaks a Text up into a list of words, delimited by -- Chars representing white space. words :: Text -> [Text] -- | O(n) Joins lines, after appending a terminating newline to -- each. unlines :: [Text] -> Text -- | O(n) Joins words using single space characters. unwords :: [Text] -> Text textToString :: Text -> String ltextToString :: LText -> String -- | This function assumes file paths are encoded in UTF8. If it cannot -- decode the FilePath, the result is just an approximation. -- -- Since 0.3.13 -- | Deprecated: Use Data.Text.pack fpToText :: FilePath -> Text -- | Since 0.3.13 -- | Deprecated: Use Data.Text.unpack fpFromText :: Text -> FilePath -- | Since 0.3.13 -- | Deprecated: Use id fpToString :: FilePath -> String -- | Encode text using UTF-8 encoding. encodeUtf8 :: Text -> ByteString -- | Note that this is not the standard -- Data.Text.Encoding.decodeUtf8. That function will throw -- impure exceptions on any decoding errors. This function instead uses -- decodeLenient. decodeUtf8 :: ByteString -> Text getLine :: MonadIO m => m Text getContents :: MonadIO m => m LText interact :: MonadIO m => (LText -> LText) -> m () -- | gcd x y is the non-negative factor of both x -- and y of which every common factor of x and -- y is also a factor; for example gcd 4 2 = 2, -- gcd (-4) 6 = 2, gcd 0 4 = 4. -- gcd 0 0 = 0. (That is, the common divisor -- that is "greatest" in the divisibility preordering.) -- -- Note: Since for signed fixed-width integer types, abs -- minBound < 0, the result may be negative if one of the -- arguments is minBound (and necessarily is if the other -- is 0 or minBound) for such types. gcd :: Integral a => a -> a -> a -- | lcm x y is the smallest positive integer that both -- x and y divide. lcm :: Integral a => a -> a -> a -- | Conversion of values to readable Strings. -- -- Derived instances of Show have the following properties, which -- are compatible with derived instances of Read: -- -- -- -- For example, given the declarations -- --
--   infixr 5 :^:
--   data Tree a =  Leaf a  |  Tree a :^: Tree a
--   
-- -- the derived instance of Show is equivalent to -- --
--   instance (Show a) => Show (Tree a) where
--   
--          showsPrec d (Leaf m) = showParen (d > app_prec) $
--               showString "Leaf " . showsPrec (app_prec+1) m
--            where app_prec = 10
--   
--          showsPrec d (u :^: v) = showParen (d > up_prec) $
--               showsPrec (up_prec+1) u .
--               showString " :^: "      .
--               showsPrec (up_prec+1) v
--            where up_prec = 5
--   
-- -- Note that right-associativity of :^: is ignored. For example, -- -- class Show a -- | 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 shows functions return a function that prepends the -- output String to an existing String. This allows -- constant-time concatenation of results using function composition. type ShowS = String -> String -- | equivalent to showsPrec with a precedence of 0. shows :: Show a => a -> ShowS -- | utility function converting a Char to a show function that -- simply prepends the character unchanged. showChar :: Char -> ShowS -- | utility function converting a String to a show function that -- simply prepends the string unchanged. showString :: String -> ShowS -- | utility function that surrounds the inner show function with -- parentheses when the Bool parameter is True. showParen :: Bool -> ShowS -> ShowS -- | A parser for a type a, represented as a function that takes a -- String and returns a list of possible parses as -- (a,String) pairs. -- -- Note that this kind of backtracking parser is very inefficient; -- reading a large structure may be quite slow (cf ReadP). type ReadS a = String -> [(a, String)] -- | attempts to parse a value from the front of the string, returning a -- list of (parsed value, remaining string) pairs. If there is no -- successful parse, the returned list is empty. -- -- 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. readsPrec :: Read a => Int -> ReadS a -- | The method readList is provided to allow the programmer to give -- a specialised way of parsing lists of values. For example, this is -- used by the predefined Read instance of the Char type, -- where values of type String should be are expected to use -- double quotes, rather than square brackets. readList :: Read a => ReadS [a] -- | equivalent to readsPrec with a precedence of 0. reads :: Read a => ReadS a -- | readParen True p parses what p parses, -- but surrounded with parentheses. -- -- readParen False p parses what p -- parses, but optionally surrounded with parentheses. readParen :: Bool -> ReadS a -> ReadS a -- | The lex function reads a single lexeme from the input, -- discarding initial white space, and returning the characters that -- constitute the lexeme. If the input string contains only white space, -- lex returns a single successful `lexeme' consisting of the -- empty string. (Thus lex "" = [("","")].) If there is -- no legal lexeme at the beginning of the input string, lex fails -- (i.e. returns []). -- -- This lexer is not completely faithful to the Haskell lexical syntax in -- the following respects: -- -- lex :: ReadS String readMay :: Read a => Text -> Maybe a getChar :: MonadIO m => m Char putChar :: MonadIO m => Char -> m () -- | The readLn function combines getLine and readIO. readLn :: (MonadIO m, Read a) => m a