foundation-0.0.29: Alternative prelude with batteries and no dependencies
License BSD-style
Maintainer Vincent Hanquez <vincent@snarc.org>
Stability experimental
Portability portable
Safe Haskell None
Language Haskell2010

Foundation

Description

I tried to picture clusters of information As they moved through the computer What do they look like?

Alternative Prelude

Synopsis

Standard

Operators

($) :: forall (r :: RuntimeRep ) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 Source #

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 .

Note that ( $ ) is levity-polymorphic in its result type, so that foo $ True where foo :: Bool -> Int# is well-typed.

($!) :: forall (r :: RuntimeRep ) a (b :: TYPE r). (a -> b) -> a -> b infixr 0 Source #

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.

(&&) :: Bool -> Bool -> Bool infixr 3 Source #

Boolean "and", lazy in the second argument

(||) :: Bool -> Bool -> Bool infixr 2 Source #

Boolean "or", lazy in the second argument

(.) :: forall (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c infixr 9 Source #

morphism composition

Functions

otherwise :: Bool Source #

otherwise is defined as the value True . It helps to make guards more readable. eg.

 f x | x < 0     = ...
     | otherwise = ...

data Tuple2 a b Source #

Strict tuple (a,b)

Constructors

Tuple2 !a !b

Instances

Instances details
Bifunctor Tuple2 Source #
Instance details

Defined in Foundation.Tuple

Methods

bimap :: (a -> b) -> (c -> d) -> Tuple2 a c -> Tuple2 b d Source #

first :: (a -> b) -> Tuple2 a c -> Tuple2 b c Source #

second :: (b -> c) -> Tuple2 a b -> Tuple2 a c Source #

Nthable 1 ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 1 ( Tuple2 a b) Source #

Methods

nth :: proxy 1 -> Tuple2 a b -> NthTy 1 ( Tuple2 a b) Source #

Nthable 2 ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 2 ( Tuple2 a b) Source #

Methods

nth :: proxy 2 -> Tuple2 a b -> NthTy 2 ( Tuple2 a b) Source #

( Eq a, Eq b) => Eq ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

( Data a, Data b) => Data ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Methods

gfoldl :: ( forall d b0. Data d => c (d -> b0) -> d -> c b0) -> ( forall g. g -> c g) -> Tuple2 a b -> c ( Tuple2 a b) Source #

gunfold :: ( forall b0 r. Data b0 => c (b0 -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Tuple2 a b) Source #

toConstr :: Tuple2 a b -> Constr Source #

dataTypeOf :: Tuple2 a b -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Tuple2 a b)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Tuple2 a b)) Source #

gmapT :: ( forall b0. Data b0 => b0 -> b0) -> Tuple2 a b -> Tuple2 a b Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Tuple2 a b -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Tuple2 a b -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Tuple2 a b -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Tuple2 a b -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Tuple2 a b -> m ( Tuple2 a b) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tuple2 a b -> m ( Tuple2 a b) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tuple2 a b -> m ( Tuple2 a b) Source #

( Ord a, Ord b) => Ord ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

( Show a, Show b) => Show ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Generic ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep ( Tuple2 a b) :: Type -> Type Source #

( NormalForm a, NormalForm b) => NormalForm ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Sndable ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple2 a b) Source #

Fstable ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple2 a b) Source #

( Hashable a, Hashable b) => Hashable ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Tuple2 a b -> st -> st Source #

type NthTy 1 ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 1 ( Tuple2 a b) = a
type NthTy 2 ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 2 ( Tuple2 a b) = b
type Rep ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

type ProductSecond ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

type ProductFirst ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

type ProductFirst ( Tuple2 a b) = a

data Tuple3 a b c Source #

Strict tuple (a,b,c)

Constructors

Tuple3 !a !b !c

Instances

Instances details
Nthable 1 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 1 ( Tuple3 a b c) Source #

Methods

nth :: proxy 1 -> Tuple3 a b c -> NthTy 1 ( Tuple3 a b c) Source #

Nthable 2 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 2 ( Tuple3 a b c) Source #

Methods

nth :: proxy 2 -> Tuple3 a b c -> NthTy 2 ( Tuple3 a b c) Source #

Nthable 3 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 3 ( Tuple3 a b c) Source #

Methods

nth :: proxy 3 -> Tuple3 a b c -> NthTy 3 ( Tuple3 a b c) Source #

( Eq a, Eq b, Eq c) => Eq ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

( Data a, Data b, Data c) => Data ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Methods

gfoldl :: ( forall d b0. Data d => c0 (d -> b0) -> d -> c0 b0) -> ( forall g. g -> c0 g) -> Tuple3 a b c -> c0 ( Tuple3 a b c) Source #

gunfold :: ( forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> ( forall r. r -> c0 r) -> Constr -> c0 ( Tuple3 a b c) Source #

toConstr :: Tuple3 a b c -> Constr Source #

dataTypeOf :: Tuple3 a b c -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c0 (t d)) -> Maybe (c0 ( Tuple3 a b c)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c0 (t d e)) -> Maybe (c0 ( Tuple3 a b c)) Source #

gmapT :: ( forall b0. Data b0 => b0 -> b0) -> Tuple3 a b c -> Tuple3 a b c Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Tuple3 a b c -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Tuple3 a b c -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Tuple3 a b c -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Tuple3 a b c -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Tuple3 a b c -> m ( Tuple3 a b c) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tuple3 a b c -> m ( Tuple3 a b c) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Tuple3 a b c -> m ( Tuple3 a b c) Source #

( Ord a, Ord b, Ord c) => Ord ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

( Show a, Show b, Show c) => Show ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Generic ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep ( Tuple3 a b c) :: Type -> Type Source #

( NormalForm a, NormalForm b, NormalForm c) => NormalForm ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Thdable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird ( Tuple3 a b c) Source #

Sndable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple3 a b c) Source #

Fstable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple3 a b c) Source #

( Hashable a, Hashable b, Hashable c) => Hashable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Tuple3 a b c -> st -> st Source #

type NthTy 1 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 1 ( Tuple3 a b c) = a
type NthTy 2 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 2 ( Tuple3 a b c) = b
type NthTy 3 ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 3 ( Tuple3 a b c) = c
type Rep ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

type ProductThird ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

type ProductThird ( Tuple3 a b c) = c
type ProductSecond ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

type ProductSecond ( Tuple3 a b c) = b
type ProductFirst ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

type ProductFirst ( Tuple3 a b c) = a

data Tuple4 a b c d Source #

Strict tuple (a,b,c,d)

Constructors

Tuple4 !a !b !c !d

Instances

Instances details
Nthable 1 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 1 ( Tuple4 a b c d) Source #

Methods

nth :: proxy 1 -> Tuple4 a b c d -> NthTy 1 ( Tuple4 a b c d) Source #

Nthable 2 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 2 ( Tuple4 a b c d) Source #

Methods

nth :: proxy 2 -> Tuple4 a b c d -> NthTy 2 ( Tuple4 a b c d) Source #

Nthable 3 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 3 ( Tuple4 a b c d) Source #

Methods

nth :: proxy 3 -> Tuple4 a b c d -> NthTy 3 ( Tuple4 a b c d) Source #

Nthable 4 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

Associated Types

type NthTy 4 ( Tuple4 a b c d) Source #

Methods

nth :: proxy 4 -> Tuple4 a b c d -> NthTy 4 ( Tuple4 a b c d) Source #

( Eq a, Eq b, Eq c, Eq d) => Eq ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

( Data a, Data b, Data c, Data d) => Data ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Methods

gfoldl :: ( forall d0 b0. Data d0 => c0 (d0 -> b0) -> d0 -> c0 b0) -> ( forall g. g -> c0 g) -> Tuple4 a b c d -> c0 ( Tuple4 a b c d) Source #

gunfold :: ( forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> ( forall r. r -> c0 r) -> Constr -> c0 ( Tuple4 a b c d) Source #

toConstr :: Tuple4 a b c d -> Constr Source #

dataTypeOf :: Tuple4 a b c d -> DataType Source #

dataCast1 :: Typeable t => ( forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 ( Tuple4 a b c d)) Source #

dataCast2 :: Typeable t => ( forall d0 e. ( Data d0, Data e) => c0 (t d0 e)) -> Maybe (c0 ( Tuple4 a b c d)) Source #

gmapT :: ( forall b0. Data b0 => b0 -> b0) -> Tuple4 a b c d -> Tuple4 a b c d Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d0. Data d0 => d0 -> r') -> Tuple4 a b c d -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d0. Data d0 => d0 -> r') -> Tuple4 a b c d -> r Source #

gmapQ :: ( forall d0. Data d0 => d0 -> u) -> Tuple4 a b c d -> [u] Source #

gmapQi :: Int -> ( forall d0. Data d0 => d0 -> u) -> Tuple4 a b c d -> u Source #

gmapM :: Monad m => ( forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m ( Tuple4 a b c d) Source #

gmapMp :: MonadPlus m => ( forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m ( Tuple4 a b c d) Source #

gmapMo :: MonadPlus m => ( forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m ( Tuple4 a b c d) Source #

( Ord a, Ord b, Ord c, Ord d) => Ord ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

( Show a, Show b, Show c, Show d) => Show ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Generic ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type Rep ( Tuple4 a b c d) :: Type -> Type Source #

Methods

from :: Tuple4 a b c d -> Rep ( Tuple4 a b c d) x Source #

to :: Rep ( Tuple4 a b c d) x -> Tuple4 a b c d Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Methods

toNormalForm :: Tuple4 a b c d -> () Source #

Thdable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird ( Tuple4 a b c d) Source #

Sndable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple4 a b c d) Source #

Fstable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple4 a b c d) Source #

( Hashable a, Hashable b, Hashable c, Hashable d) => Hashable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Tuple4 a b c d -> st -> st Source #

type NthTy 1 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 1 ( Tuple4 a b c d) = a
type NthTy 2 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 2 ( Tuple4 a b c d) = b
type NthTy 3 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 3 ( Tuple4 a b c d) = c
type NthTy 4 ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple.Nth

type NthTy 4 ( Tuple4 a b c d) = d
type Rep ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

type ProductThird ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

type ProductThird ( Tuple4 a b c d) = c
type ProductSecond ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

type ProductSecond ( Tuple4 a b c d) = b
type ProductFirst ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

type ProductFirst ( Tuple4 a b c d) = a

class Fstable a where Source #

Class of product types that have a first element

Associated Types

type ProductFirst a Source #

Instances

Instances details
Fstable (a, b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst (a, b) Source #

Methods

fst :: (a, b) -> ProductFirst (a, b) Source #

Fstable ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple2 a b) Source #

Fstable (a, b, c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst (a, b, c) Source #

Methods

fst :: (a, b, c) -> ProductFirst (a, b, c) Source #

Fstable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple3 a b c) Source #

Fstable (a, b, c, d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst (a, b, c, d) Source #

Methods

fst :: (a, b, c, d) -> ProductFirst (a, b, c, d) Source #

Fstable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductFirst ( Tuple4 a b c d) Source #

class Sndable a where Source #

Class of product types that have a second element

Associated Types

type ProductSecond a Source #

Instances

Instances details
Sndable (a, b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond (a, b) Source #

Methods

snd :: (a, b) -> ProductSecond (a, b) Source #

Sndable ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple2 a b) Source #

Sndable (a, b, c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond (a, b, c) Source #

Methods

snd :: (a, b, c) -> ProductSecond (a, b, c) Source #

Sndable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple3 a b c) Source #

Sndable (a, b, c, d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond (a, b, c, d) Source #

Methods

snd :: (a, b, c, d) -> ProductSecond (a, b, c, d) Source #

Sndable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductSecond ( Tuple4 a b c d) Source #

class Thdable a where Source #

Class of product types that have a third element

Associated Types

type ProductThird a Source #

Instances

Instances details
Thdable (a, b, c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird (a, b, c) Source #

Methods

thd :: (a, b, c) -> ProductThird (a, b, c) Source #

Thdable ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird ( Tuple3 a b c) Source #

Thdable (a, b, c, d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird (a, b, c, d) Source #

Methods

thd :: (a, b, c, d) -> ProductThird (a, b, c, d) Source #

Thdable ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Associated Types

type ProductThird ( Tuple4 a b c d) Source #

id :: forall (a :: k). Category cat => cat a a Source #

the identity morphism

maybe :: b -> (a -> b) -> Maybe a -> b Source #

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

Expand

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

either :: (a -> c) -> (b -> c) -> Either a b -> c Source #

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

Expand

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

flip :: (a -> b -> c) -> b -> a -> c Source #

flip f takes its (first) two arguments in the reverse order of f .

>>> flip (++) "hello" "world"
"worldhello"

const :: a -> b -> a Source #

const x is a unary function which evaluates to x for all inputs.

>>> const 42 "hello"
42
>>> map (const 42) [0..3]
[42,42,42,42]

error :: forall (r :: RuntimeRep ) (a :: TYPE r). HasCallStack => String -> a Source #

stop execution and displays an error message

putStr :: String -> IO () Source #

Print a string to standard output

putStrLn :: String -> IO () Source #

Print a string with a newline to standard output

getArgs :: IO [ String ] Source #

Returns a list of the program's command line arguments (not including the program name).

uncurry :: (a -> b -> c) -> (a, b) -> c Source #

uncurry converts a curried function to a function on pairs.

Examples

Expand
>>> uncurry (+) (1,2)
3
>>> uncurry ($) (show, 1)
"1"
>>> map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]

curry :: ((a, b) -> c) -> a -> b -> c Source #

curry converts an uncurried function to a curried function.

Examples

Expand
>>> curry fst 1 2
1

swap :: (a, b) -> (b, a) Source #

Swap the components of a pair.

until :: (a -> Bool ) -> (a -> a) -> a -> a Source #

until p f yields the result of applying f until p holds.

asTypeOf :: a -> a -> a Source #

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.

undefined :: forall (r :: RuntimeRep ) (a :: TYPE r). HasCallStack => a Source #

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.

seq :: forall (r :: RuntimeRep ) a (b :: TYPE r). a -> b -> b infixr 0 Source #

The value of seq a b is bottom if a is bottom, and otherwise equal to b . In other words, it evaluates the first argument a to weak head normal form (WHNF). 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.

class NormalForm a Source #

Data that can be fully evaluated in Normal Form

Minimal complete definition

toNormalForm

Instances

Instances details
NormalForm Bool
Instance details

Defined in Basement.NormalForm

NormalForm Char
Instance details

Defined in Basement.NormalForm

NormalForm Double
Instance details

Defined in Basement.NormalForm

NormalForm Float
Instance details

Defined in Basement.NormalForm

NormalForm Int
Instance details

Defined in Basement.NormalForm

NormalForm Int8
Instance details

Defined in Basement.NormalForm

NormalForm Int16
Instance details

Defined in Basement.NormalForm

NormalForm Int32
Instance details

Defined in Basement.NormalForm

NormalForm Int64
Instance details

Defined in Basement.NormalForm

NormalForm Integer
Instance details

Defined in Basement.NormalForm

NormalForm Natural
Instance details

Defined in Basement.NormalForm

NormalForm Word
Instance details

Defined in Basement.NormalForm

NormalForm Word8
Instance details

Defined in Basement.NormalForm

NormalForm Word16
Instance details

Defined in Basement.NormalForm

NormalForm Word32
Instance details

Defined in Basement.NormalForm

NormalForm Word64
Instance details

Defined in Basement.NormalForm

NormalForm ()
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: () -> () Source #

NormalForm CChar
Instance details

Defined in Basement.NormalForm

NormalForm CSChar
Instance details

Defined in Basement.NormalForm

NormalForm CUChar
Instance details

Defined in Basement.NormalForm

NormalForm CShort
Instance details

Defined in Basement.NormalForm

NormalForm CUShort
Instance details

Defined in Basement.NormalForm

NormalForm CInt
Instance details

Defined in Basement.NormalForm

NormalForm CUInt
Instance details

Defined in Basement.NormalForm

NormalForm CLong
Instance details

Defined in Basement.NormalForm

NormalForm CULong
Instance details

Defined in Basement.NormalForm

NormalForm CLLong
Instance details

Defined in Basement.NormalForm

NormalForm CULLong
Instance details

Defined in Basement.NormalForm

NormalForm CFloat
Instance details

Defined in Basement.NormalForm

NormalForm CDouble
Instance details

Defined in Basement.NormalForm

NormalForm String
Instance details

Defined in Basement.UTF8.Base

NormalForm Word256
Instance details

Defined in Basement.NormalForm

NormalForm Word128
Instance details

Defined in Basement.NormalForm

NormalForm Char7
Instance details

Defined in Basement.NormalForm

NormalForm CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

NormalForm Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

NormalForm Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

NormalForm Field Source #
Instance details

Defined in Foundation.Format.CSV.Types

NormalForm IPv6 Source #
Instance details

Defined in Foundation.Network.IPv6

NormalForm IPv4 Source #
Instance details

Defined in Foundation.Network.IPv4

NormalForm UUID Source #
Instance details

Defined in Foundation.UUID

NormalForm a => NormalForm [a]
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: [a] -> () Source #

NormalForm a => NormalForm ( Maybe a)
Instance details

Defined in Basement.NormalForm

NormalForm ( Ptr a)
Instance details

Defined in Basement.NormalForm

NormalForm a => NormalForm ( Array a)
Instance details

Defined in Basement.BoxedArray

NormalForm ( UArray ty)
Instance details

Defined in Basement.UArray.Base

NormalForm ( Block ty)
Instance details

Defined in Basement.Block.Base

NormalForm ( Offset a)
Instance details

Defined in Basement.NormalForm

NormalForm ( CountOf a)
Instance details

Defined in Basement.NormalForm

NormalForm ( Zn64 n)
Instance details

Defined in Basement.NormalForm

NormalForm ( Zn n)
Instance details

Defined in Basement.NormalForm

NormalForm a => NormalForm ( LE a)
Instance details

Defined in Basement.NormalForm

NormalForm a => NormalForm ( BE a)
Instance details

Defined in Basement.NormalForm

NormalForm ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

( NormalForm l, NormalForm r) => NormalForm ( Either l r)
Instance details

Defined in Basement.NormalForm

( NormalForm a, NormalForm b) => NormalForm (a, b)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b) -> () Source #

NormalForm ( BlockN n a)
Instance details

Defined in Basement.Sized.Block

NormalForm a => NormalForm ( ListN n a)
Instance details

Defined in Basement.Sized.List

( NormalForm a, NormalForm b) => NormalForm ( These a b)
Instance details

Defined in Basement.These

( NormalForm a, NormalForm b) => NormalForm ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

( NormalForm a, NormalForm b, NormalForm c) => NormalForm (a, b, c)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c) -> () Source #

( NormalForm a, NormalForm b, NormalForm c) => NormalForm ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

( NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (a, b, c, d)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c, d) -> () Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Methods

toNormalForm :: Tuple4 a b c d -> () Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e) => NormalForm (a, b, c, d, e)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c, d, e) -> () Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f) => NormalForm (a, b, c, d, e, f)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c, d, e, f) -> () Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g) => NormalForm (a, b, c, d, e, f, g)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c, d, e, f, g) -> () Source #

( NormalForm a, NormalForm b, NormalForm c, NormalForm d, NormalForm e, NormalForm f, NormalForm g, NormalForm h) => NormalForm (a, b, c, d, e, f, g, h)
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: (a, b, c, d, e, f, g, h) -> () Source #

Type classes

class Show a Source #

Conversion of values to readable String s.

Derived instances of Show have the following properties, which are compatible with derived instances of Read :

  • The result of show is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used.
  • If the constructor is defined to be an infix operator, then showsPrec will produce infix applications of the constructor.
  • the representation will be enclosed in parentheses if the precedence of the top-level constructor in x is less than d (associativity is ignored). Thus, if d is 0 then the result is never surrounded in parentheses; if d is 11 it is always surrounded in parentheses, unless it is an atomic expression.
  • If the constructor is defined using record syntax, then show will produce the record-syntax form, with the fields given in the same order as the original declaration.

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,

  • show (Leaf 1 :^: Leaf 2 :^: Leaf 3) produces the string "Leaf 1 :^: (Leaf 2 :^: Leaf 3)" .

Minimal complete definition

showsPrec | show

Instances

Instances details
Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show RuntimeRep

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecCount

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show VecElem

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show CallStack

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeTypeRep

Since: base-4.10.0.0

Instance details

Defined in Data.Typeable.Internal

Show ()

Since: base-2.1

Instance details

Defined in GHC.Show

Show TyCon

Since: base-2.1

Instance details

Defined in GHC.Show

Show Module

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show TrName

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show KindRep
Instance details

Defined in GHC.Show

Show TypeLitSort

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show DataType

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show Constr

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show DataRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show ConstrRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show Fixity

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Show RTSStats

Since: base-4.10.0.0

Instance details

Defined in GHC.Stats

Show GCDetails

Since: base-4.10.0.0

Instance details

Defined in GHC.Stats

Show Version

Since: base-2.1

Instance details

Defined in Data.Version

Show HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle

Show FD

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.FD

Show PatternMatchFail

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecSelError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecConError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show RecUpdError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show NoMethodError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show TypeError

Since: base-4.9.0.0

Instance details

Defined in Control.Exception.Base

Show NonTermination

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show NestedAtomically

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Show ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Show BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Show CDev
Instance details

Defined in System.Posix.Types

Show CIno
Instance details

Defined in System.Posix.Types

Show CMode
Instance details

Defined in System.Posix.Types

Show COff
Instance details

Defined in System.Posix.Types

Show CPid
Instance details

Defined in System.Posix.Types

Show CSsize
Instance details

Defined in System.Posix.Types

Show CGid
Instance details

Defined in System.Posix.Types

Show CNlink
Instance details

Defined in System.Posix.Types

Show CUid
Instance details

Defined in System.Posix.Types

Show CCc
Instance details

Defined in System.Posix.Types

Show CSpeed
Instance details

Defined in System.Posix.Types

Show CTcflag
Instance details

Defined in System.Posix.Types

Show CRLim
Instance details

Defined in System.Posix.Types

Show CBlkSize
Instance details

Defined in System.Posix.Types

Show CBlkCnt
Instance details

Defined in System.Posix.Types

Show CClockId
Instance details

Defined in System.Posix.Types

Show CFsBlkCnt
Instance details

Defined in System.Posix.Types

Show CFsFilCnt
Instance details

Defined in System.Posix.Types

Show CId
Instance details

Defined in System.Posix.Types

Show CKey
Instance details

Defined in System.Posix.Types

Show CSocklen
Instance details

Defined in System.Posix.Types

Show CNfds
Instance details

Defined in System.Posix.Types

Show Fd
Instance details

Defined in System.Posix.Types

Show BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show AllocationLimitExceeded

Since: base-4.7.1.0

Instance details

Defined in GHC.IO.Exception

Show CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Show AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Show AsyncException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Show ExitCode
Instance details

Defined in GHC.IO.Exception

Show IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show HandleType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Show SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Show TextEncoding

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show CodingProgress

Since: base-4.4.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Show MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.IO

Show IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Show ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Show ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Show SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Show SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Show CChar
Instance details

Defined in Foreign.C.Types

Show CSChar
Instance details

Defined in Foreign.C.Types

Show CUChar
Instance details

Defined in Foreign.C.Types

Show CShort
Instance details

Defined in Foreign.C.Types

Show CUShort
Instance details

Defined in Foreign.C.Types

Show CInt
Instance details

Defined in Foreign.C.Types

Show CUInt
Instance details

Defined in Foreign.C.Types

Show CLong
Instance details

Defined in Foreign.C.Types

Show CULong
Instance details

Defined in Foreign.C.Types

Show CLLong
Instance details

Defined in Foreign.C.Types

Show CULLong
Instance details

Defined in Foreign.C.Types

Show CBool
Instance details

Defined in Foreign.C.Types

Show CFloat
Instance details

Defined in Foreign.C.Types

Show CDouble
Instance details

Defined in Foreign.C.Types

Show CPtrdiff
Instance details

Defined in Foreign.C.Types

Show CSize
Instance details

Defined in Foreign.C.Types

Show CWchar
Instance details

Defined in Foreign.C.Types

Show CSigAtomic
Instance details

Defined in Foreign.C.Types

Show CClock
Instance details

Defined in Foreign.C.Types

Show CTime
Instance details

Defined in Foreign.C.Types

Show CUSeconds
Instance details

Defined in Foreign.C.Types

Show CSUSeconds
Instance details

Defined in Foreign.C.Types

Show CIntPtr
Instance details

Defined in Foreign.C.Types

Show CUIntPtr
Instance details

Defined in Foreign.C.Types

Show CIntMax
Instance details

Defined in Foreign.C.Types

Show CUIntMax
Instance details

Defined in Foreign.C.Types

Show WordPtr
Instance details

Defined in Foreign.Ptr

Show IntPtr
Instance details

Defined in Foreign.Ptr

Show IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Show GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Show SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Show

Show SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Show ASCII7_Invalid
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

showsPrec :: Int -> ASCII7_Invalid -> ShowS Source #

show :: ASCII7_Invalid -> String Source #

showList :: [ASCII7_Invalid] -> ShowS Source #

Show ISO_8859_1_Invalid
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

showsPrec :: Int -> ISO_8859_1_Invalid -> ShowS Source #

show :: ISO_8859_1_Invalid -> String Source #

showList :: [ISO_8859_1_Invalid] -> ShowS Source #

Show UTF16_Invalid
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

showsPrec :: Int -> UTF16_Invalid -> ShowS Source #

show :: UTF16_Invalid -> String Source #

showList :: [UTF16_Invalid] -> ShowS Source #

Show UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

showsPrec :: Int -> UTF32_Invalid -> ShowS Source #

show :: UTF32_Invalid -> String Source #

showList :: [UTF32_Invalid] -> ShowS Source #

Show Encoding
Instance details

Defined in Basement.String

Show String
Instance details

Defined in Basement.UTF8.Base

Show ValidationFailure
Instance details

Defined in Basement.UTF8.Types

Show AsciiString
Instance details

Defined in Basement.Types.AsciiString

Show OutOfBoundOperation
Instance details

Defined in Basement.Exception

Show OutOfBound
Instance details

Defined in Basement.Exception

Show RecastSourceSize
Instance details

Defined in Basement.Exception

Show RecastDestinationSize
Instance details

Defined in Basement.Exception

Show InvalidRecast
Instance details

Defined in Basement.Exception

Show NonEmptyCollectionIsEmpty
Instance details

Defined in Basement.Exception

Show FileSize
Instance details

Defined in Basement.Types.OffsetSize

Show Word256
Instance details

Defined in Basement.Types.Word256

Show Word128
Instance details

Defined in Basement.Types.Word128

Show Char7
Instance details

Defined in Basement.Types.Char7

Show Endianness
Instance details

Defined in Basement.Endianness

Show Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Show PartialError Source #
Instance details

Defined in Foundation.Partial

Show And Source #
Instance details

Defined in Foundation.Parser

Show Condition Source #
Instance details

Defined in Foundation.Parser

Show CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Show Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Show Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

Show Field Source #
Instance details

Defined in Foundation.Format.CSV.Types

Show Arch Source #
Instance details

Defined in Foundation.System.Info

Show OS Source #
Instance details

Defined in Foundation.System.Info

Show Seconds Source #
Instance details

Defined in Foundation.Time.Types

Show NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

Show IPv6 Source #
Instance details

Defined in Foundation.Network.IPv6

Show IPv4 Source #
Instance details

Defined in Foundation.Network.IPv4

Show UUID Source #
Instance details

Defined in Foundation.UUID

Show FileName Source #
Instance details

Defined in Foundation.VFS.FilePath

Show FilePath Source #
Instance details

Defined in Foundation.VFS.FilePath

Show Relativity Source #
Instance details

Defined in Foundation.VFS.FilePath

Show a => Show [a]

Since: base-2.1

Instance details

Defined in GHC.Show

Show a => Show ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Show a => Show ( Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show ( Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Show ( FunPtr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Show p => Show ( Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Show a => Show ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show m => Show ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show ( Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show a => Show ( ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Show a => Show ( Identity a)

This instance would be equivalent to the derived instances of the Identity newtype if the runIdentity field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Show ( ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show a => Show ( First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show ( Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Show a => Show ( Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show ( Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show ( Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show ( Down a)

This instance would be equivalent to the derived instances of the Down newtype if the getDown field were removed

Since: base-4.7.0.0

Instance details

Defined in Data.Ord

Show a => Show ( NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Show a => Show ( Array a)
Instance details

Defined in Basement.BoxedArray

( PrimType ty, Show ty) => Show ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Show ( Bits n)
Instance details

Defined in Basement.Bits

( PrimType ty, Show ty) => Show ( Block ty)
Instance details

Defined in Basement.Block.Base

Show a => Show ( NonEmpty a)
Instance details

Defined in Basement.NonEmpty

Show ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Show ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Show ( Zn64 n)
Instance details

Defined in Basement.Bounded

Show ( Zn n)
Instance details

Defined in Basement.Bounded

Show ( FinalPtr a)
Instance details

Defined in Basement.FinalPtr

Show a => Show ( LE a)
Instance details

Defined in Basement.Endianness

Show a => Show ( BE a)
Instance details

Defined in Basement.Endianness

Show a => Show ( DList a) Source #
Instance details

Defined in Foundation.List.DList

( PrimType ty, Show ty) => Show ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Show input => Show ( ParseError input) Source #
Instance details

Defined in Foundation.Parser

Show ( ParseError String ) Source #
Instance details

Defined in Foundation.Parser

( Show a, Show b) => Show ( Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Show ( V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( TypeRep a)
Instance details

Defined in Data.Typeable.Internal

( Show a, Show b) => Show (a, b)

Since: base-2.1

Instance details

Defined in GHC.Show

( Show a, Show b) => Show ( Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Show ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

( Ix a, Show a, Show b) => Show ( Array a b)

Since: base-2.1

Instance details

Defined in GHC.Arr

Show ( ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

( PrimType a, Show a) => Show ( BlockN n a)
Instance details

Defined in Basement.Sized.Block

Show a => Show ( ListN n a)
Instance details

Defined in Basement.Sized.List

( Show a, Show b) => Show ( These a b)
Instance details

Defined in Basement.These

( Show k, Show input) => Show ( Result input k) Source #
Instance details

Defined in Foundation.Parser

( Show a, Show b) => Show ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Show (f p) => Show ( Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Show ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Float p)
Instance details

Defined in GHC.Generics

Show ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

( Show a, Show b, Show c) => Show (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Show

Show a => Show ( Const a b)

This instance would be equivalent to the derived instances of the Const newtype if the getConst field were removed

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Const

Show (f a) => Show ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Show (f a) => Show ( Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Show ( Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Show (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

( Show a, Show b, Show c) => Show ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Show c => Show ( K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Show (f p), Show (g p)) => Show ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Show (f p), Show (g p)) => Show ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Show a, Show b, Show c, Show d) => Show (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d) -> ShowS Source #

show :: (a, b, c, d) -> String Source #

showList :: [(a, b, c, d)] -> ShowS Source #

Show (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

( Show a, Show b, Show c, Show d) => Show ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Show (f p) => Show ( M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Show (f (g p)) => Show ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e) -> ShowS Source #

show :: (a, b, c, d, e) -> String Source #

showList :: [(a, b, c, d, e)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f) -> ShowS Source #

show :: (a, b, c, d, e, f) -> String Source #

showList :: [(a, b, c, d, e, f)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS Source #

show :: (a, b, c, d, e, f, g) -> String Source #

showList :: [(a, b, c, d, e, f, g)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h) => Show (a, b, c, d, e, f, g, h)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h) -> String Source #

showList :: [(a, b, c, d, e, f, g, h)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i) => Show (a, b, c, d, e, f, g, h, i)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j) => Show (a, b, c, d, e, f, g, h, i, j)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k) => Show (a, b, c, d, e, f, g, h, i, j, k)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l) => Show (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> ShowS Source #

( Show a, Show b, Show c, Show d, Show e, Show f, Show g, Show h, Show i, Show j, Show k, Show l, Show m, Show n, Show o) => Show (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> ShowS Source #

show :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> String Source #

showList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> ShowS Source #

show :: Show a => a -> String Source #

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.

class Eq a => Ord a where Source #

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.

The Haskell Report defines no laws for Ord . However, <= is customarily expected to implement a non-strict partial order and have the following properties:

Transitivity
if x <= y && y <= z = True , then x <= z = True
Reflexivity
x <= x = True
Antisymmetry
if x <= y && y <= x = True , then x == y = True

Note that the following operator interactions are expected to hold:

  1. x >= y = y <= x
  2. x < y = x <= y && x /= y
  3. x > y = y < x
  4. x < y = compare x y == LT
  5. x > y = compare x y == GT
  6. x == y = compare x y == EQ
  7. min x y == if x <= y then x else y = True
  8. max x y == if x >= y then x else y = True

Note that (7.) and (8.) do not require min and max to return either of their arguments. The result is merely required to equal one of the arguments in terms of (==) .

Minimal complete definition: either compare or <= . Using compare can be more efficient for complex types.

Minimal complete definition

compare | (<=)

Methods

compare :: a -> a -> Ordering Source #

(<) :: a -> a -> Bool infix 4 Source #

(<=) :: a -> a -> Bool infix 4 Source #

(>) :: a -> a -> Bool infix 4 Source #

(>=) :: a -> a -> Bool infix 4 Source #

max :: a -> a -> a Source #

min :: a -> a -> a Source #

Instances

Instances details
Ord Bool
Instance details

Defined in GHC.Classes

Ord Char
Instance details

Defined in GHC.Classes

Ord Double

Note that due to the presence of NaN , Double 's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord 's operator interactions are not respected by Double 's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Ord Float

Note that due to the presence of NaN , Float 's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord 's operator interactions are not respected by Float 's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Ord Int
Instance details

Defined in GHC.Classes

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Integer
Instance details

Defined in GHC.Integer.Type

Ord Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Ord Ordering
Instance details

Defined in GHC.Classes

Ord Word
Instance details

Defined in GHC.Classes

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord SomeTypeRep
Instance details

Defined in Data.Typeable.Internal

Ord ()
Instance details

Defined in GHC.Classes

Ord TyCon
Instance details

Defined in GHC.Classes

Ord Version

Since: base-2.1

Instance details

Defined in Data.Version

Ord ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Ord BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Ord CDev
Instance details

Defined in System.Posix.Types

Ord CIno
Instance details

Defined in System.Posix.Types

Ord CMode
Instance details

Defined in System.Posix.Types

Ord COff
Instance details

Defined in System.Posix.Types

Ord CPid
Instance details

Defined in System.Posix.Types

Ord CSsize
Instance details

Defined in System.Posix.Types

Ord CGid
Instance details

Defined in System.Posix.Types

Ord CNlink
Instance details

Defined in System.Posix.Types

Ord CUid
Instance details

Defined in System.Posix.Types

Ord CCc
Instance details

Defined in System.Posix.Types

Ord CSpeed
Instance details

Defined in System.Posix.Types

Ord CTcflag
Instance details

Defined in System.Posix.Types

Ord CRLim
Instance details

Defined in System.Posix.Types

Ord CBlkSize
Instance details

Defined in System.Posix.Types

Ord CBlkCnt
Instance details

Defined in System.Posix.Types

Ord CClockId
Instance details

Defined in System.Posix.Types

Ord CFsBlkCnt
Instance details

Defined in System.Posix.Types

Ord CFsFilCnt
Instance details

Defined in System.Posix.Types

Ord CId
Instance details

Defined in System.Posix.Types

Ord CKey
Instance details

Defined in System.Posix.Types

Ord CSocklen
Instance details

Defined in System.Posix.Types

Ord CNfds
Instance details

Defined in System.Posix.Types

Ord Fd
Instance details

Defined in System.Posix.Types

Ord AsyncException

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord ArrayException

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Ord ExitCode
Instance details

Defined in GHC.IO.Exception

Ord BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord Newline

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord NewlineMode

Since: base-4.3.0.0

Instance details

Defined in GHC.IO.Handle.Types

Ord SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Ord ErrorCall

Since: base-4.7.0.0

Instance details

Defined in GHC.Exception

Ord ArithException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Ord All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ord Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Ord SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Ord SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Ord CChar
Instance details

Defined in Foreign.C.Types

Ord CSChar
Instance details

Defined in Foreign.C.Types

Ord CUChar
Instance details

Defined in Foreign.C.Types

Ord CShort
Instance details

Defined in Foreign.C.Types

Ord CUShort
Instance details

Defined in Foreign.C.Types

Ord CInt
Instance details

Defined in Foreign.C.Types

Ord CUInt
Instance details

Defined in Foreign.C.Types

Ord CLong
Instance details

Defined in Foreign.C.Types

Ord CULong
Instance details

Defined in Foreign.C.Types

Ord CLLong
Instance details

Defined in Foreign.C.Types

Ord CULLong
Instance details

Defined in Foreign.C.Types

Ord CBool
Instance details

Defined in Foreign.C.Types

Ord CFloat
Instance details

Defined in Foreign.C.Types

Ord CDouble
Instance details

Defined in Foreign.C.Types

Ord CPtrdiff
Instance details

Defined in Foreign.C.Types

Ord CSize
Instance details

Defined in Foreign.C.Types

Ord CWchar
Instance details

Defined in Foreign.C.Types

Ord CSigAtomic
Instance details

Defined in Foreign.C.Types

Ord CClock
Instance details

Defined in Foreign.C.Types

Ord CTime
Instance details

Defined in Foreign.C.Types

Ord CUSeconds
Instance details

Defined in Foreign.C.Types

Ord CSUSeconds
Instance details

Defined in Foreign.C.Types

Ord CIntPtr
Instance details

Defined in Foreign.C.Types

Ord CUIntPtr
Instance details

Defined in Foreign.C.Types

Ord CIntMax
Instance details

Defined in Foreign.C.Types

Ord CUIntMax
Instance details

Defined in Foreign.C.Types

Ord WordPtr
Instance details

Defined in Foreign.Ptr

Ord IntPtr
Instance details

Defined in Foreign.Ptr

Ord IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Ord GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Ord UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

compare :: UTF32_Invalid -> UTF32_Invalid -> Ordering Source #

(<) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

(<=) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

(>) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

(>=) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

max :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid Source #

min :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid Source #

Ord Encoding
Instance details

Defined in Basement.String

Ord String
Instance details

Defined in Basement.UTF8.Base

Ord AsciiString
Instance details

Defined in Basement.Types.AsciiString

Ord Addr
Instance details

Defined in Basement.Types.Ptr

Ord FileSize
Instance details

Defined in Basement.Types.OffsetSize

Ord Word256
Instance details

Defined in Basement.Types.Word256

Ord Word128
Instance details

Defined in Basement.Types.Word128

Ord Char7
Instance details

Defined in Basement.Types.Char7

Ord BigNat
Instance details

Defined in GHC.Integer.Type

Ord Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Ord Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

Ord Arch Source #
Instance details

Defined in Foundation.System.Info

Ord OS Source #
Instance details

Defined in Foundation.System.Info

Ord Seconds Source #
Instance details

Defined in Foundation.Time.Types

Ord NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

Ord IPv6 Source #
Instance details

Defined in Foundation.Network.IPv6

Ord IPv4 Source #
Instance details

Defined in Foundation.Network.IPv4

Ord UUID Source #
Instance details

Defined in Foundation.UUID

Ord FilePath Source #
Instance details

Defined in Foundation.VFS.FilePath

Ord a => Ord [a]
Instance details

Defined in GHC.Classes

Methods

compare :: [a] -> [a] -> Ordering Source #

(<) :: [a] -> [a] -> Bool Source #

(<=) :: [a] -> [a] -> Bool Source #

(>) :: [a] -> [a] -> Bool Source #

(>=) :: [a] -> [a] -> Bool Source #

max :: [a] -> [a] -> [a] Source #

min :: [a] -> [a] -> [a] Source #

Ord a => Ord ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Integral a => Ord ( Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Ord ( Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Ord ( FunPtr a)
Instance details

Defined in GHC.Ptr

Ord p => Ord ( Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Ord a => Ord ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord m => Ord ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord ( Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Ord ( ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Ord a => Ord ( Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Ord ( ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Ord a => Ord ( First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Ord a => Ord ( Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Ord a => Ord ( Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord ( Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord ( Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Ord a => Ord ( Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Ord a => Ord ( NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Ord a => Ord ( Array a)
Instance details

Defined in Basement.BoxedArray

( PrimType ty, Ord ty) => Ord ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Ord ( Bits n)
Instance details

Defined in Basement.Bits

( PrimType ty, Ord ty) => Ord ( Block ty)
Instance details

Defined in Basement.Block.Base

Ord ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Ord ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Ord ( Zn64 n)
Instance details

Defined in Basement.Bounded

Ord ( Zn n)
Instance details

Defined in Basement.Bounded

Ord ( FinalPtr a)
Instance details

Defined in Basement.FinalPtr

( ByteSwap a, Ord a) => Ord ( LE a)
Instance details

Defined in Basement.Endianness

( ByteSwap a, Ord a) => Ord ( BE a)
Instance details

Defined in Basement.Endianness

Ord a => Ord ( DList a) Source #
Instance details

Defined in Foundation.List.DList

( PrimType ty, Ord ty) => Ord ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

( Ord a, Ord b) => Ord ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Ord ( V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Ord ( TypeRep a)

Since: base-4.4.0.0

Instance details

Defined in Data.Typeable.Internal

( Ord a, Ord b) => Ord (a, b)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b) -> (a, b) -> Ordering Source #

(<) :: (a, b) -> (a, b) -> Bool Source #

(<=) :: (a, b) -> (a, b) -> Bool Source #

(>) :: (a, b) -> (a, b) -> Bool Source #

(>=) :: (a, b) -> (a, b) -> Bool Source #

max :: (a, b) -> (a, b) -> (a, b) Source #

min :: (a, b) -> (a, b) -> (a, b) Source #

Ord a => Ord ( Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

( Ix i, Ord e) => Ord ( Array i e)

Since: base-2.1

Instance details

Defined in GHC.Arr

( PrimType a, Ord a) => Ord ( BlockN n a)
Instance details

Defined in Basement.Sized.Block

Ord a => Ord ( ListN n a)
Instance details

Defined in Basement.Sized.List

( Ord a, Ord b) => Ord ( These a b)
Instance details

Defined in Basement.These

( Ord a, Ord b) => Ord ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Ord (f p) => Ord ( Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Ord ( URec ( Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Float p)
Instance details

Defined in GHC.Generics

Ord ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

( Ord a, Ord b, Ord c) => Ord (a, b, c)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c) -> (a, b, c) -> Ordering Source #

(<) :: (a, b, c) -> (a, b, c) -> Bool Source #

(<=) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>=) :: (a, b, c) -> (a, b, c) -> Bool Source #

max :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

min :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

Ord a => Ord ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Ord (f a) => Ord ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Ord (f a) => Ord ( Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Ord ( Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Ord (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

( Ord a, Ord b, Ord c) => Ord ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Ord c => Ord ( K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Ord (f p), Ord (g p)) => Ord ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :+: g) p -> (f :+: g) p -> Ordering Source #

(<) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(<=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(>) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(>=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

max :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

min :: (f :+: g) p -> (f :+: g) p -> (f :+: g) p Source #

( Ord (f p), Ord (g p)) => Ord ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :*: g) p -> (f :*: g) p -> Ordering Source #

(<) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(<=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(>) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(>=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

max :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

min :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

( Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d) -> (a, b, c, d) -> Ordering Source #

(<) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(<=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(>) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(>=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

max :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

min :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

Ord (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

( Ord a, Ord b, Ord c, Ord d) => Ord ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Ord (f p) => Ord ( M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: M1 i c f p -> M1 i c f p -> Ordering Source #

(<) :: M1 i c f p -> M1 i c f p -> Bool Source #

(<=) :: M1 i c f p -> M1 i c f p -> Bool Source #

(>) :: M1 i c f p -> M1 i c f p -> Bool Source #

(>=) :: M1 i c f p -> M1 i c f p -> Bool Source #

max :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

min :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

Ord (f (g p)) => Ord ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: (f :.: g) p -> (f :.: g) p -> Ordering Source #

(<) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(<=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(>) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(>=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

max :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

min :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

( Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering Source #

(<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering Source #

(<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h) => Ord (a, b, c, d, e, f, g, h)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

max :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

min :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i) => Ord (a, b, c, d, e, f, g, h, i)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

min :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j) => Ord (a, b, c, d, e, f, g, h, i, j)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

min :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k) => Ord (a, b, c, d, e, f, g, h, i, j, k)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l) => Ord (a, b, c, d, e, f, g, h, i, j, k, l)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

( Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g, Ord h, Ord i, Ord j, Ord k, Ord l, Ord m, Ord n, Ord o) => Ord (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
Instance details

Defined in GHC.Classes

Methods

compare :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Ordering Source #

(<) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(<=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(>) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(>=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

max :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

min :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

class Eq a where Source #

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 .

The Haskell Report defines no laws for Eq . However, == is customarily expected to implement an equivalence relationship where two values comparing equal are indistinguishable by "public" functions, with a "public" function being one not allowing to see implementation details. For example, for a type representing non-normalised natural numbers modulo 100, a "public" function doesn't make the difference between 1 and 201. It is expected to have the following properties:

Reflexivity
x == x = True
Symmetry
x == y = y == x
Transitivity
if x == y && y == z = True , then x == z = True
Substitutivity
if x == y = True and f is a "public" function whose return type is an instance of Eq , then f x == f y = True
Negation
x /= y = not (x == y)

Minimal complete definition: either == or /= .

Minimal complete definition

(==) | (/=)

Methods

(==) :: a -> a -> Bool infix 4 Source #

(/=) :: a -> a -> Bool infix 4 Source #

Instances

Instances details
Eq Bool
Instance details

Defined in GHC.Classes

Eq Char
Instance details

Defined in GHC.Classes

Eq Double

Note that due to the presence of NaN , Double 's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double 's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Eq Float

Note that due to the presence of NaN , Float 's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float 's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Eq Int
Instance details

Defined in GHC.Classes

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Integer
Instance details

Defined in GHC.Integer.Type

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Eq Ordering
Instance details

Defined in GHC.Classes

Eq Word
Instance details

Defined in GHC.Classes

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq SomeTypeRep
Instance details

Defined in Data.Typeable.Internal

Eq ()
Instance details

Defined in GHC.Classes

Methods

(==) :: () -> () -> Bool Source #

(/=) :: () -> () -> Bool Source #

Eq TyCon
Instance details

Defined in GHC.Classes

Eq Module
Instance details

Defined in GHC.Classes

Eq TrName
Instance details

Defined in GHC.Classes

Eq SpecConstrAnnotation

Since: base-4.3.0.0

Instance details

Defined in GHC.Exts

Eq Constr

Equality of constructors

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Eq DataRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Eq ConstrRep

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Eq Fixity

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Eq Version

Since: base-2.1

Instance details

Defined in Data.Version

Eq HandlePosn

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle

Eq ThreadId

Since: base-4.2.0.0

Instance details

Defined in GHC.Conc.Sync

Eq BlockReason

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Eq ThreadStatus

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Eq CDev
Instance details

Defined in System.Posix.Types

Eq CIno
Instance details

Defined in System.Posix.Types

Eq CMode
Instance details

Defined in System.Posix.Types

Eq COff
Instance details

Defined in System.Posix.Types

Eq CPid
Instance details

Defined in System.Posix.Types

Eq CSsize
Instance details

Defined in System.Posix.Types

Eq CGid
Instance details

Defined in System.Posix.Types

Eq CNlink
Instance details

Defined in System.Posix.Types

Eq CUid
Instance details

Defined in System.Posix.Types

Eq CCc
Instance details

Defined in System.Posix.Types

Eq CSpeed
Instance details

Defined in System.Posix.Types

Eq CTcflag
Instance details

Defined in System.Posix.Types

Eq CRLim
Instance details

Defined in System.Posix.Types

Eq CBlkSize
Instance details

Defined in System.Posix.Types

Eq CBlkCnt
Instance details

Defined in System.Posix.Types

Eq CClockId
Instance details

Defined in System.Posix.Types

Eq CFsBlkCnt
Instance details

Defined in System.Posix.Types

Eq CFsFilCnt
Instance details

Defined in System.Posix.Types

Eq CId
Instance details

Defined in System.Posix.Types

Eq CKey
Instance details

Defined in System.Posix.Types

Eq CSocklen
Instance details

Defined in System.Posix.Types

Eq CNfds
Instance details

Defined in System.Posix.Types

Eq Fd
Instance details

Defined in System.Posix.Types

Eq Errno

Since: base-2.1

Instance details

Defined in Foreign.C.Error

Eq AsyncException

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Eq ArrayException

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Exception

Eq ExitCode
Instance details

Defined in GHC.IO.Exception

Eq IOErrorType

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Eq Handle

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Handle.Types

Eq BufferMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Eq Newline

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Eq NewlineMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Handle.Types

Eq IODeviceType

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Eq SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Eq CodingProgress

Since: base-4.4.0.0

Instance details

Defined in GHC.IO.Encoding.Types

Eq MaskingState

Since: base-4.3.0.0

Instance details

Defined in GHC.IO

Eq IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Eq ErrorCall

Since: base-4.7.0.0

Instance details

Defined in GHC.Exception

Eq ArithException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Eq All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq Fixity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Eq Associativity

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Eq SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq SomeSymbol

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeLits

Eq SomeNat

Since: base-4.7.0.0

Instance details

Defined in GHC.TypeNats

Eq CChar
Instance details

Defined in Foreign.C.Types

Eq CSChar
Instance details

Defined in Foreign.C.Types

Eq CUChar
Instance details

Defined in Foreign.C.Types

Eq CShort
Instance details

Defined in Foreign.C.Types

Eq CUShort
Instance details

Defined in Foreign.C.Types

Eq CInt
Instance details

Defined in Foreign.C.Types

Eq CUInt
Instance details

Defined in Foreign.C.Types

Eq CLong
Instance details

Defined in Foreign.C.Types

Eq CULong
Instance details

Defined in Foreign.C.Types

Eq CLLong
Instance details

Defined in Foreign.C.Types

Eq CULLong
Instance details

Defined in Foreign.C.Types

Eq CBool
Instance details

Defined in Foreign.C.Types

Eq CFloat
Instance details

Defined in Foreign.C.Types

Eq CDouble
Instance details

Defined in Foreign.C.Types

Eq CPtrdiff
Instance details

Defined in Foreign.C.Types

Eq CSize
Instance details

Defined in Foreign.C.Types

Eq CWchar
Instance details

Defined in Foreign.C.Types

Eq CSigAtomic
Instance details

Defined in Foreign.C.Types

Eq CClock
Instance details

Defined in Foreign.C.Types

Eq CTime
Instance details

Defined in Foreign.C.Types

Eq CUSeconds
Instance details

Defined in Foreign.C.Types

Eq CSUSeconds
Instance details

Defined in Foreign.C.Types

Eq CIntPtr
Instance details

Defined in Foreign.C.Types

Eq CUIntPtr
Instance details

Defined in Foreign.C.Types

Eq CIntMax
Instance details

Defined in Foreign.C.Types

Eq CUIntMax
Instance details

Defined in Foreign.C.Types

Eq WordPtr
Instance details

Defined in Foreign.Ptr

Eq IntPtr
Instance details

Defined in Foreign.Ptr

Eq IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Eq GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Eq SrcLoc

Since: base-4.9.0.0

Instance details

Defined in GHC.Stack.Types

Eq CM
Instance details

Defined in Basement.UTF8.Types

Methods

(==) :: CM -> CM -> Bool Source #

(/=) :: CM -> CM -> Bool Source #

Eq ASCII7_Invalid
Instance details

Defined in Basement.String.Encoding.ASCII7

Methods

(==) :: ASCII7_Invalid -> ASCII7_Invalid -> Bool Source #

(/=) :: ASCII7_Invalid -> ASCII7_Invalid -> Bool Source #

Eq ISO_8859_1_Invalid
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Methods

(==) :: ISO_8859_1_Invalid -> ISO_8859_1_Invalid -> Bool Source #

(/=) :: ISO_8859_1_Invalid -> ISO_8859_1_Invalid -> Bool Source #

Eq UTF16_Invalid
Instance details

Defined in Basement.String.Encoding.UTF16

Methods

(==) :: UTF16_Invalid -> UTF16_Invalid -> Bool Source #

(/=) :: UTF16_Invalid -> UTF16_Invalid -> Bool Source #

Eq UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

(==) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

(/=) :: UTF32_Invalid -> UTF32_Invalid -> Bool Source #

Eq Encoding
Instance details

Defined in Basement.String

Eq String
Instance details

Defined in Basement.UTF8.Base

Eq ValidationFailure
Instance details

Defined in Basement.UTF8.Types

Eq AsciiString
Instance details

Defined in Basement.Types.AsciiString

Eq OutOfBoundOperation
Instance details

Defined in Basement.Exception

Eq RecastSourceSize
Instance details

Defined in Basement.Exception

Eq RecastDestinationSize
Instance details

Defined in Basement.Exception

Eq Addr
Instance details

Defined in Basement.Types.Ptr

Eq FileSize
Instance details

Defined in Basement.Types.OffsetSize

Eq Word256
Instance details

Defined in Basement.Types.Word256

Eq Word128
Instance details

Defined in Basement.Types.Word128

Eq Char7
Instance details

Defined in Basement.Types.Char7

Eq Endianness
Instance details

Defined in Basement.Endianness

Eq BigNat
Instance details

Defined in GHC.Integer.Type

Eq Sign Source #
Instance details

Defined in Foundation.Numerical

Eq Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Eq PartialError Source #
Instance details

Defined in Foundation.Partial

Eq And Source #
Instance details

Defined in Foundation.Parser

Eq Condition Source #
Instance details

Defined in Foundation.Parser

Eq CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Eq Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Eq Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

Eq Field Source #
Instance details

Defined in Foundation.Format.CSV.Types

Eq Arch Source #
Instance details

Defined in Foundation.System.Info

Eq OS Source #
Instance details

Defined in Foundation.System.Info

Eq Seconds Source #
Instance details

Defined in Foundation.Time.Types

Eq NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

Eq IPv6 Source #
Instance details

Defined in Foundation.Network.IPv6

Eq IPv4 Source #
Instance details

Defined in Foundation.Network.IPv4

Eq UUID Source #
Instance details

Defined in Foundation.UUID

Eq FileName Source #
Instance details

Defined in Foundation.VFS.FilePath

Eq FilePath Source #
Instance details

Defined in Foundation.VFS.FilePath

Eq Relativity Source #
Instance details

Defined in Foundation.VFS.FilePath

Eq a => Eq [a]
Instance details

Defined in GHC.Classes

Methods

(==) :: [a] -> [a] -> Bool Source #

(/=) :: [a] -> [a] -> Bool Source #

Eq a => Eq ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Eq a => Eq ( Ratio a)

Since: base-2.1

Instance details

Defined in GHC.Real

Eq ( Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Eq ( FunPtr a)
Instance details

Defined in GHC.Ptr

Eq p => Eq ( Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Eq a => Eq ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq m => Eq ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq ( Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq a => Eq ( ZipList a)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

Eq a => Eq ( Identity a)

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Eq ( TVar a)

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Eq ( ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Eq ( IORef a)

Pointer equality.

Since: base-4.0.0.0

Instance details

Defined in GHC.IORef

Eq a => Eq ( First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Eq a => Eq ( Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Eq a => Eq ( Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq ( Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq ( Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq ( Down a)

Since: base-4.6.0.0

Instance details

Defined in Data.Ord

Eq a => Eq ( NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Eq a => Eq ( Array a)
Instance details

Defined in Basement.BoxedArray

( PrimType ty, Eq ty) => Eq ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Eq ( Bits n)
Instance details

Defined in Basement.Bits

( PrimType ty, Eq ty) => Eq ( Block ty)
Instance details

Defined in Basement.Block.Base

Eq a => Eq ( NonEmpty a)
Instance details

Defined in Basement.NonEmpty

Eq ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Eq ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Eq ( Zn64 n)
Instance details

Defined in Basement.Bounded

Eq ( Zn n)
Instance details

Defined in Basement.Bounded

Eq ( FinalPtr a)
Instance details

Defined in Basement.FinalPtr

Eq a => Eq ( LE a)
Instance details

Defined in Basement.Endianness

Eq a => Eq ( BE a)
Instance details

Defined in Basement.Endianness

Eq a => Eq ( DList a) Source #
Instance details

Defined in Foundation.List.DList

PrimType ty => Eq ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

( Eq a, Eq b) => Eq ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

Eq ( V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( U1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( TypeRep a)

Since: base-2.1

Instance details

Defined in Data.Typeable.Internal

( Eq a, Eq b) => Eq (a, b)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b) -> (a, b) -> Bool Source #

(/=) :: (a, b) -> (a, b) -> Bool Source #

Eq a => Eq ( Arg a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Eq ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

( Ix i, Eq e) => Eq ( Array i e)

Since: base-2.1

Instance details

Defined in GHC.Arr

PrimType a => Eq ( BlockN n a)
Instance details

Defined in Basement.Sized.Block

Eq a => Eq ( ListN n a)
Instance details

Defined in Basement.Sized.List

( Eq a, Eq b) => Eq ( These a b)
Instance details

Defined in Basement.These

( Eq a, Eq b) => Eq ( Tuple2 a b) Source #
Instance details

Defined in Foundation.Tuple

Eq (f p) => Eq ( Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Eq ( URec ( Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Float p)
Instance details

Defined in GHC.Generics

Eq ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

( Eq a, Eq b, Eq c) => Eq (a, b, c)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c) -> (a, b, c) -> Bool Source #

(/=) :: (a, b, c) -> (a, b, c) -> Bool Source #

Eq a => Eq ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Eq (f a) => Eq ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Eq (f a) => Eq ( Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Eq ( Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

Eq (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

Eq ( STArray s i e)

Since: base-2.1

Instance details

Defined in GHC.Arr

( Eq a, Eq b, Eq c) => Eq ( Tuple3 a b c) Source #
Instance details

Defined in Foundation.Tuple

Eq c => Eq ( K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

( Eq (f p), Eq (g p)) => Eq ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

(/=) :: (f :+: g) p -> (f :+: g) p -> Bool Source #

( Eq (f p), Eq (g p)) => Eq ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

(/=) :: (f :*: g) p -> (f :*: g) p -> Bool Source #

( Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

(/=) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

Eq (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

( Eq a, Eq b, Eq c, Eq d) => Eq ( Tuple4 a b c d) Source #
Instance details

Defined in Foundation.Tuple

Eq (f p) => Eq ( M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: M1 i c f p -> M1 i c f p -> Bool Source #

(/=) :: M1 i c f p -> M1 i c f p -> Bool Source #

Eq (f (g p)) => Eq ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

(/=) :: (f :.: g) p -> (f :.: g) p -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

(/=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

(/=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h) => Eq (a, b, c, d, e, f, g, h)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i) => Eq (a, b, c, d, e, f, g, h, i)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j) => Eq (a, b, c, d, e, f, g, h, i, j)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k) => Eq (a, b, c, d, e, f, g, h, i, j, k)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l) => Eq (a, b, c, d, e, f, g, h, i, j, k, l)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool Source #

( Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g, Eq h, Eq i, Eq j, Eq k, Eq l, Eq m, Eq n, Eq o) => Eq (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
Instance details

Defined in GHC.Classes

Methods

(==) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

(/=) :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool Source #

class Bounded a where Source #

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 .

Instances

Instances details
Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Bounded Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Bounded VecCount

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Bounded VecElem

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Bounded ()

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded CDev
Instance details

Defined in System.Posix.Types

Bounded CIno
Instance details

Defined in System.Posix.Types

Bounded CMode
Instance details

Defined in System.Posix.Types

Bounded COff
Instance details

Defined in System.Posix.Types

Bounded CPid
Instance details

Defined in System.Posix.Types

Bounded CSsize
Instance details

Defined in System.Posix.Types

Bounded CGid
Instance details

Defined in System.Posix.Types

Bounded CNlink
Instance details

Defined in System.Posix.Types

Bounded CUid
Instance details

Defined in System.Posix.Types

Bounded CTcflag
Instance details

Defined in System.Posix.Types

Bounded CRLim
Instance details

Defined in System.Posix.Types

Bounded CBlkSize
Instance details

Defined in System.Posix.Types

Bounded CBlkCnt
Instance details

Defined in System.Posix.Types

Bounded CClockId
Instance details

Defined in System.Posix.Types

Bounded CFsBlkCnt
Instance details

Defined in System.Posix.Types

Bounded CFsFilCnt
Instance details

Defined in System.Posix.Types

Bounded CId
Instance details

Defined in System.Posix.Types

Bounded CKey
Instance details

Defined in System.Posix.Types

Bounded CSocklen
Instance details

Defined in System.Posix.Types

Bounded CNfds
Instance details

Defined in System.Posix.Types

Bounded Fd
Instance details

Defined in System.Posix.Types

Bounded All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Bounded Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Bounded Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Bounded SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Bounded SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Bounded DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Bounded CChar
Instance details

Defined in Foreign.C.Types

Bounded CSChar
Instance details

Defined in Foreign.C.Types

Bounded CUChar
Instance details

Defined in Foreign.C.Types

Bounded CShort
Instance details

Defined in Foreign.C.Types

Bounded CUShort
Instance details

Defined in Foreign.C.Types

Bounded CInt
Instance details

Defined in Foreign.C.Types

Bounded CUInt
Instance details

Defined in Foreign.C.Types

Bounded CLong
Instance details

Defined in Foreign.C.Types

Bounded CULong
Instance details

Defined in Foreign.C.Types

Bounded CLLong
Instance details

Defined in Foreign.C.Types

Bounded CULLong
Instance details

Defined in Foreign.C.Types

Bounded CBool
Instance details

Defined in Foreign.C.Types

Bounded CPtrdiff
Instance details

Defined in Foreign.C.Types

Bounded CSize
Instance details

Defined in Foreign.C.Types

Bounded CWchar
Instance details

Defined in Foreign.C.Types

Bounded CSigAtomic
Instance details

Defined in Foreign.C.Types

Bounded CIntPtr
Instance details

Defined in Foreign.C.Types

Bounded CUIntPtr
Instance details

Defined in Foreign.C.Types

Bounded CIntMax
Instance details

Defined in Foreign.C.Types

Bounded CUIntMax
Instance details

Defined in Foreign.C.Types

Bounded WordPtr
Instance details

Defined in Foreign.Ptr

Bounded IntPtr
Instance details

Defined in Foreign.Ptr

Bounded GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Bounded UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

minBound :: UTF32_Invalid Source #

maxBound :: UTF32_Invalid Source #

Bounded Encoding
Instance details

Defined in Basement.String

Bounded Word256
Instance details

Defined in Basement.Types.Word256

Bounded Word128
Instance details

Defined in Basement.Types.Word128

Bounded Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

Bounded Arch Source #
Instance details

Defined in Foundation.System.Info

Bounded OS Source #
Instance details

Defined in Foundation.System.Info

Bounded Seconds Source #
Instance details

Defined in Foundation.Time.Types

Bounded NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

Bounded a => Bounded ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Bounded a => Bounded ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Bounded a => Bounded ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Bounded a => Bounded ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Bounded m => Bounded ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Bounded a => Bounded ( Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Bounded a => Bounded ( Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Bounded a => Bounded ( Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Bounded a => Bounded ( Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Bounded a => Bounded ( Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

SizeValid n => Bounded ( Bits n)
Instance details

Defined in Basement.Bits

( Bounded a, Bounded b) => Bounded (a, b)

Since: base-2.1

Instance details

Defined in GHC.Enum

Bounded ( Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

( Bounded a, Bounded b, Bounded c) => Bounded (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c) Source #

maxBound :: (a, b, c) Source #

Bounded a => Bounded ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

( Applicative f, Bounded a) => Bounded ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Coercible a b => Bounded ( Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

a ~ b => Bounded (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

( Bounded a, Bounded b, Bounded c, Bounded d) => Bounded (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d) Source #

maxBound :: (a, b, c, d) Source #

a ~~ b => Bounded (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e) => Bounded (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e) Source #

maxBound :: (a, b, c, d, e) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f) => Bounded (a, b, c, d, e, f)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f) Source #

maxBound :: (a, b, c, d, e, f) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g) => Bounded (a, b, c, d, e, f, g)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g) Source #

maxBound :: (a, b, c, d, e, f, g) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h) => Bounded (a, b, c, d, e, f, g, h)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h) Source #

maxBound :: (a, b, c, d, e, f, g, h) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i) => Bounded (a, b, c, d, e, f, g, h, i)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i) Source #

maxBound :: (a, b, c, d, e, f, g, h, i) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j) => Bounded (a, b, c, d, e, f, g, h, i, j)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k) => Bounded (a, b, c, d, e, f, g, h, i, j, k)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

( Bounded a, Bounded b, Bounded c, Bounded d, Bounded e, Bounded f, Bounded g, Bounded h, Bounded i, Bounded j, Bounded k, Bounded l, Bounded m, Bounded n, Bounded o) => Bounded (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

minBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

maxBound :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

class Enum a where Source #

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

Minimal complete definition

toEnum , fromEnum

Methods

succ :: a -> a Source #

the successor of a value. For numeric types, succ adds 1.

pred :: a -> a Source #

the predecessor of a value. For numeric types, pred subtracts 1.

toEnum :: Int -> a Source #

Convert from an Int .

fromEnum :: a -> Int Source #

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 .

enumFrom :: a -> [a] Source #

Used in Haskell's translation of [n..] with [n..] = enumFrom n , a possible implementation being enumFrom n = n : enumFrom (succ n) . For example:

  • enumFrom 4 :: [Integer] = [4,5,6,7,...]
  • enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]

enumFromThen :: a -> a -> [a] Source #

Used in Haskell's translation of [n,n'..] with [n,n'..] = enumFromThen n n' , a possible implementation being enumFromThen n n' = n : n' : worker (f x) (f x n') , worker s v = v : worker s (s v) , x = fromEnum n' - fromEnum n and f n y | n > 0 = f (n - 1) (succ y) | n < 0 = f (n + 1) (pred y) | otherwise = y For example:

  • enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
  • enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]

enumFromTo :: a -> a -> [a] Source #

Used in Haskell's translation of [n..m] with [n..m] = enumFromTo n m , a possible implementation being enumFromTo n m | n <= m = n : enumFromTo (succ n) m | otherwise = [] . For example:

  • enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
  • enumFromTo 42 1 :: [Integer] = []

enumFromThenTo :: a -> a -> a -> [a] Source #

Used in Haskell's translation of [n,n'..m] with [n,n'..m] = enumFromThenTo n n' m , a possible implementation being enumFromThenTo n n' m = worker (f x) (c x) n m , x = fromEnum n' - fromEnum n , c x = bool (>=) ( (x 0) f n y | n > 0 = f (n - 1) (succ y) | n < 0 = f (n + 1) (pred y) | otherwise = y and worker s c v m | c v m = v : worker s c (s v) m | otherwise = [] For example:

  • enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
  • enumFromThenTo 6 8 2 :: [Int] = []

Instances

Instances details
Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Enum Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum VecCount

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Enum VecElem

Since: base-4.10.0.0

Instance details

Defined in GHC.Enum

Enum ()

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum CDev
Instance details

Defined in System.Posix.Types

Enum CIno
Instance details

Defined in System.Posix.Types

Enum CMode
Instance details

Defined in System.Posix.Types

Enum COff
Instance details

Defined in System.Posix.Types

Enum CPid
Instance details

Defined in System.Posix.Types

Enum CSsize
Instance details

Defined in System.Posix.Types

Enum CGid
Instance details

Defined in System.Posix.Types

Enum CNlink
Instance details

Defined in System.Posix.Types

Enum CUid
Instance details

Defined in System.Posix.Types

Enum CCc
Instance details

Defined in System.Posix.Types

Enum CSpeed
Instance details

Defined in System.Posix.Types

Enum CTcflag
Instance details

Defined in System.Posix.Types

Enum CRLim
Instance details

Defined in System.Posix.Types

Enum CBlkSize
Instance details

Defined in System.Posix.Types

Enum CBlkCnt
Instance details

Defined in System.Posix.Types

Enum CClockId
Instance details

Defined in System.Posix.Types

Enum CFsBlkCnt
Instance details

Defined in System.Posix.Types

Enum CFsFilCnt
Instance details

Defined in System.Posix.Types

Enum CId
Instance details

Defined in System.Posix.Types

Enum CKey
Instance details

Defined in System.Posix.Types

Enum CSocklen
Instance details

Defined in System.Posix.Types

Enum CNfds
Instance details

Defined in System.Posix.Types

Enum Fd
Instance details

Defined in System.Posix.Types

Enum SeekMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.Device

Enum Associativity

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Enum CChar
Instance details

Defined in Foreign.C.Types

Enum CSChar
Instance details

Defined in Foreign.C.Types

Enum CUChar
Instance details

Defined in Foreign.C.Types

Enum CShort
Instance details

Defined in Foreign.C.Types

Enum CUShort
Instance details

Defined in Foreign.C.Types

Enum CInt
Instance details

Defined in Foreign.C.Types

Enum CUInt
Instance details

Defined in Foreign.C.Types

Enum CLong
Instance details

Defined in Foreign.C.Types

Enum CULong
Instance details

Defined in Foreign.C.Types

Enum CLLong
Instance details

Defined in Foreign.C.Types

Enum CULLong
Instance details

Defined in Foreign.C.Types

Enum CBool
Instance details

Defined in Foreign.C.Types

Enum CFloat
Instance details

Defined in Foreign.C.Types

Enum CDouble
Instance details

Defined in Foreign.C.Types

Enum CPtrdiff
Instance details

Defined in Foreign.C.Types

Enum CSize
Instance details

Defined in Foreign.C.Types

Enum CWchar
Instance details

Defined in Foreign.C.Types

Enum CSigAtomic
Instance details

Defined in Foreign.C.Types

Enum CClock
Instance details

Defined in Foreign.C.Types

Enum CTime
Instance details

Defined in Foreign.C.Types

Enum CUSeconds
Instance details

Defined in Foreign.C.Types

Enum CSUSeconds
Instance details

Defined in Foreign.C.Types

Enum CIntPtr
Instance details

Defined in Foreign.C.Types

Enum CUIntPtr
Instance details

Defined in Foreign.C.Types

Enum CIntMax
Instance details

Defined in Foreign.C.Types

Enum CUIntMax
Instance details

Defined in Foreign.C.Types

Enum WordPtr
Instance details

Defined in Foreign.Ptr

Enum IntPtr
Instance details

Defined in Foreign.Ptr

Enum IOMode

Since: base-4.2.0.0

Instance details

Defined in GHC.IO.IOMode

Enum GeneralCategory

Since: base-2.1

Instance details

Defined in GHC.Unicode

Enum UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Methods

succ :: UTF32_Invalid -> UTF32_Invalid Source #

pred :: UTF32_Invalid -> UTF32_Invalid Source #

toEnum :: Int -> UTF32_Invalid Source #

fromEnum :: UTF32_Invalid -> Int Source #

enumFrom :: UTF32_Invalid -> [UTF32_Invalid] Source #

enumFromThen :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] Source #

enumFromTo :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] Source #

enumFromThenTo :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] Source #

Enum Encoding
Instance details

Defined in Basement.String

Enum Word256
Instance details

Defined in Basement.Types.Word256

Enum Word128
Instance details

Defined in Basement.Types.Word128

Enum Escaping Source #
Instance details

Defined in Foundation.Format.CSV.Types

Enum Arch Source #
Instance details

Defined in Foundation.System.Info

Enum OS Source #
Instance details

Defined in Foundation.System.Info

Enum Seconds Source #
Instance details

Defined in Foundation.Time.Types

Enum NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

Integral a => Enum ( Ratio a)

Since: base-2.0.1

Instance details

Defined in GHC.Real

Enum a => Enum ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum ( WrappedMonoid a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Enum a => Enum ( Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Enum a => Enum ( Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

SizeValid n => Enum ( Bits n)
Instance details

Defined in Basement.Bits

Enum ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Enum ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Enum ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Enum a => Enum ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Enum (f a) => Enum ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Enum (f a) => Enum ( Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Coercible a b => Enum ( Coercion a b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Coercion

a ~ b => Enum (a :~: b)

Since: base-4.7.0.0

Instance details

Defined in Data.Type.Equality

a ~~ b => Enum (a :~~: b)

Since: base-4.10.0.0

Instance details

Defined in Data.Type.Equality

class Functor (f :: Type -> Type ) where Source #

A type f is a Functor if it provides a function fmap which, given any types a and b lets you apply any function from (a -> b) to turn an f a into an f b , preserving the structure of f . Furthermore f needs to adhere to the following:

Identity
fmap id == id
Composition
fmap (f . g) == fmap f . fmap g

Note, that the second law follows from the free theorem of the type fmap and the first law, so you need only check that the former condition holds.

Minimal complete definition

fmap

Methods

fmap :: (a -> b) -> f a -> f b Source #

Using ApplicativeDo : ' fmap f as ' can be understood as the do expression

do a <- as
   pure (f a)

with an inferred Functor constraint.

(<$) :: a -> f b -> f a infixl 4 Source #

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.

Using ApplicativeDo : ' a <$ bs ' can be understood as the do expression

do bs
   pure a

with an inferred Functor constraint.

Instances

Instances details
Functor []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> [a] -> [b] Source #

(<$) :: a -> [b] -> [a] Source #

Functor Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Functor IO

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> IO a -> IO b Source #

(<$) :: a -> IO b -> IO a Source #

Functor Par1

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor Min

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> Min a -> Min b Source #

(<$) :: a -> Min b -> Min a Source #

Functor Max

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a -> b) -> Max a -> Max b Source #

(<$) :: a -> Max b -> Max a Source #

Functor First

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Functor Last

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Functor Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Functor ZipList

Since: base-2.1

Instance details

Defined in Control.Applicative

Functor Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Functor Handler

Since: base-4.6.0.0

Instance details

Defined in Control.Exception

Functor STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

fmap :: (a -> b) -> STM a -> STM b Source #

(<$) :: a -> STM b -> STM a Source #

Functor First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Functor Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Functor Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Functor Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b Source #

(<$) :: a -> Sum b -> Sum a Source #

Functor Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Functor Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Functor ReadP

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Functor Array
Instance details

Defined in Basement.BoxedArray

Functor P

Since: base-4.8.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

fmap :: (a -> b) -> P a -> P b Source #

(<$) :: a -> P b -> P a Source #

Functor DList Source #
Instance details

Defined in Foundation.List.DList

Functor Partial Source #
Instance details

Defined in Foundation.Partial

Functor Gen Source #
Instance details

Defined in Foundation.Check.Gen

Methods

fmap :: (a -> b) -> Gen a -> Gen b Source #

(<$) :: a -> Gen b -> Gen a Source #

Functor Check Source #
Instance details

Defined in Foundation.Check.Types

Functor ( Either a)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

Functor ( V1 :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> V1 a -> V1 b Source #

(<$) :: a -> V1 b -> V1 a Source #

Functor ( U1 :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> U1 a -> U1 b Source #

(<$) :: a -> U1 b -> U1 a Source #

Functor ( (,) a)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b) -> (a, a0) -> (a, b) Source #

(<$) :: a0 -> (a, b) -> (a, a0) Source #

Functor ( Arg a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

fmap :: (a0 -> b) -> Arg a a0 -> Arg a b Source #

(<$) :: a0 -> Arg a b -> Arg a a0 Source #

Monad m => Functor ( WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

Arrow a => Functor ( ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Functor ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Functor ( Array i)

Since: base-2.1

Instance details

Defined in GHC.Arr

Methods

fmap :: (a -> b) -> Array i a -> Array i b Source #

(<$) :: a -> Array i b -> Array i a Source #

Functor ( ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

fmap :: (a -> b) -> ST s a -> ST s b Source #

(<$) :: a -> ST s b -> ST s a Source #

Functor ( These a)
Instance details

Defined in Basement.These

Methods

fmap :: (a0 -> b) -> These a a0 -> These a b Source #

(<$) :: a0 -> These a b -> These a a0 Source #

Functor m => Functor ( ResourceT m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Functor ( Parser input) Source #
Instance details

Defined in Foundation.Parser

Methods

fmap :: (a -> b) -> Parser input a -> Parser input b Source #

(<$) :: a -> Parser input b -> Parser input a Source #

Functor ( Result input) Source #
Instance details

Defined in Foundation.Parser

Methods

fmap :: (a -> b) -> Result input a -> Result input b Source #

(<$) :: a -> Result input b -> Result input a Source #

Functor ( MonadRandomState gen) Source #
Instance details

Defined in Foundation.Random.DRG

Functor f => Functor ( Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> Rec1 f a -> Rec1 f b Source #

(<$) :: a -> Rec1 f b -> Rec1 f a Source #

Functor ( URec Char :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor ( URec Double :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor ( URec Float :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor ( URec Int :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor ( URec Word :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Functor ( URec ( Ptr ()) :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec ( Ptr ()) a -> URec ( Ptr ()) b Source #

(<$) :: a -> URec ( Ptr ()) b -> URec ( Ptr ()) a Source #

Functor ( (,,) a b)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

(<$) :: a0 -> (a, b, b0) -> (a, b, a0) Source #

Arrow a => Functor ( WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Functor m => Functor ( Kleisli m a)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Methods

fmap :: (a0 -> b) -> Kleisli m a a0 -> Kleisli m a b Source #

(<$) :: a0 -> Kleisli m a b -> Kleisli m a a0 Source #

Functor ( Const m :: Type -> Type )

Since: base-2.1

Instance details

Defined in Data.Functor.Const

Methods

fmap :: (a -> b) -> Const m a -> Const m b Source #

(<$) :: a -> Const m b -> Const m a Source #

Functor f => Functor ( Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b Source #

(<$) :: a -> Ap f b -> Ap f a Source #

Functor f => Functor ( Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b Source #

(<$) :: a -> Alt f b -> Alt f a Source #

Monad m => Functor ( State s m)
Instance details

Defined in Basement.Compat.MonadTrans

Methods

fmap :: (a -> b) -> State s m a -> State s m b Source #

(<$) :: a -> State s m b -> State s m a Source #

Monad m => Functor ( Reader r m)
Instance details

Defined in Basement.Compat.MonadTrans

Methods

fmap :: (a -> b) -> Reader r m a -> Reader r m b Source #

(<$) :: a -> Reader r m b -> Reader r m a Source #

Functor m => Functor ( StateT s m) Source #
Instance details

Defined in Foundation.Monad.State

Methods

fmap :: (a -> b) -> StateT s m a -> StateT s m b Source #

(<$) :: a -> StateT s m b -> StateT s m a Source #

Functor m => Functor ( ReaderT r m) Source #
Instance details

Defined in Foundation.Monad.Reader

Methods

fmap :: (a -> b) -> ReaderT r m a -> ReaderT r m b Source #

(<$) :: a -> ReaderT r m b -> ReaderT r m a Source #

Functor m => Functor ( ExceptT e m) Source #
Instance details

Defined in Foundation.Monad.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b Source #

(<$) :: a -> ExceptT e m b -> ExceptT e m a Source #

Monad m => Functor ( ZipSink i m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Methods

fmap :: (a -> b) -> ZipSink i m a -> ZipSink i m b Source #

(<$) :: a -> ZipSink i m b -> ZipSink i m a Source #

Functor ((->) r :: Type -> Type )

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> (r -> a) -> r -> b Source #

(<$) :: a -> (r -> b) -> r -> a Source #

Functor ( K1 i c :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> K1 i c a -> K1 i c b Source #

(<$) :: a -> K1 i c b -> K1 i c a Source #

( Functor f, Functor g) => Functor (f :+: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :+: g) a -> (f :+: g) b Source #

(<$) :: a -> (f :+: g) b -> (f :+: g) a Source #

( Functor f, Functor g) => Functor (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

(<$) :: a -> (f :*: g) b -> (f :*: g) a Source #

Functor ( (,,,) a b c)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

fmap :: (a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source #

(<$) :: a0 -> (a, b, c, b0) -> (a, b, c, a0) Source #

Functor ( Conduit i o m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Methods

fmap :: (a -> b) -> Conduit i o m a -> Conduit i o m b Source #

(<$) :: a -> Conduit i o m b -> Conduit i o m a Source #

Functor f => Functor ( M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> M1 i c f a -> M1 i c f b Source #

(<$) :: a -> M1 i c f b -> M1 i c f a Source #

( Functor f, Functor g) => Functor (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

(<$) :: a -> (f :.: g) b -> (f :.: g) a Source #

Monad state => Functor ( Builder collection mutCollection step state err)
Instance details

Defined in Basement.MutableBuilder

Methods

fmap :: (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b Source #

(<$) :: a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a Source #

class Integral a where Source #

Integral Literal support

e.g. 123 :: Integer 123 :: Word8

Instances

Instances details
Integral Double
Instance details

Defined in Basement.Compat.NumLiteral

Integral Float
Instance details

Defined in Basement.Compat.NumLiteral

Integral Int
Instance details

Defined in Basement.Compat.NumLiteral

Integral Int8
Instance details

Defined in Basement.Compat.NumLiteral

Integral Int16
Instance details

Defined in Basement.Compat.NumLiteral

Integral Int32
Instance details

Defined in Basement.Compat.NumLiteral

Integral Int64
Instance details

Defined in Basement.Compat.NumLiteral

Integral Integer
Instance details

Defined in Basement.Compat.NumLiteral

Integral Natural
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word8
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word16
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word32
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word64
Instance details

Defined in Basement.Compat.NumLiteral

Integral COff
Instance details

Defined in Basement.Compat.NumLiteral

Integral CChar
Instance details

Defined in Basement.Compat.NumLiteral

Integral CSChar
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUChar
Instance details

Defined in Basement.Compat.NumLiteral

Integral CShort
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUShort
Instance details

Defined in Basement.Compat.NumLiteral

Integral CInt
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUInt
Instance details

Defined in Basement.Compat.NumLiteral

Integral CLong
Instance details

Defined in Basement.Compat.NumLiteral

Integral CULong
Instance details

Defined in Basement.Compat.NumLiteral

Integral CLLong
Instance details

Defined in Basement.Compat.NumLiteral

Integral CULLong
Instance details

Defined in Basement.Compat.NumLiteral

Integral CBool
Instance details

Defined in Basement.Compat.NumLiteral

Integral CFloat
Instance details

Defined in Basement.Compat.NumLiteral

Integral CDouble
Instance details

Defined in Basement.Compat.NumLiteral

Integral CPtrdiff
Instance details

Defined in Basement.Compat.NumLiteral

Integral CSize
Instance details

Defined in Basement.Compat.NumLiteral

Integral CWchar
Instance details

Defined in Basement.Compat.NumLiteral

Integral CSigAtomic
Instance details

Defined in Basement.Compat.NumLiteral

Integral CClock
Instance details

Defined in Basement.Compat.NumLiteral

Integral CTime
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUSeconds
Instance details

Defined in Basement.Compat.NumLiteral

Integral CSUSeconds
Instance details

Defined in Basement.Compat.NumLiteral

Integral CIntPtr
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUIntPtr
Instance details

Defined in Basement.Compat.NumLiteral

Integral CIntMax
Instance details

Defined in Basement.Compat.NumLiteral

Integral CUIntMax
Instance details

Defined in Basement.Compat.NumLiteral

Integral IntPtr
Instance details

Defined in Basement.Compat.NumLiteral

Integral Word256
Instance details

Defined in Basement.Types.Word256

Integral Word128
Instance details

Defined in Basement.Types.Word128

Integral ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Integral ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

( KnownNat n, NatWithinBound Word64 n) => Integral ( Zn64 n)
Instance details

Defined in Basement.Bounded

KnownNat n => Integral ( Zn n)
Instance details

Defined in Basement.Bounded

class HasNegation a where Source #

Negation support

e.g. -(f x)

Methods

negate :: a -> a Source #

Instances

Instances details
HasNegation Double
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Float
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int8
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int16
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int32
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int64
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Integer
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word8
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word16
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word32
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word64
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CChar
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CSChar
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CShort
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CInt
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CLong
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CLLong
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CFloat
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CDouble
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CPtrdiff
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CWchar
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation CIntMax
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word256
Instance details

Defined in Basement.Types.Word256

HasNegation Word128
Instance details

Defined in Basement.Types.Word128

class Bifunctor (p :: Type -> Type -> Type ) where Source #

A bifunctor is a type constructor that takes two type arguments and is a functor in both arguments. That is, unlike with Functor , a type constructor such as Either does not need to be partially applied for a Bifunctor instance, and the methods in this class permit mapping functions over the Left value or the Right value, or both at the same time.

Formally, the class Bifunctor represents a bifunctor from Hask -> Hask .

Intuitively it is a bifunctor where both the first and second arguments are covariant.

You can define a Bifunctor by either defining bimap or by defining both first and second .

If you supply bimap , you should ensure that:

bimap id id ≡ id

If you supply first and second , ensure:

first id ≡ id
second id ≡ id

If you supply both, you should also ensure:

bimap f g ≡ first f . second g

These ensure by parametricity:

bimap  (f . g) (h . i) ≡ bimap f h . bimap g i
first  (f . g) ≡ first  f . first  g
second (f . g) ≡ second f . second g

Since: base-4.8.0.0

Minimal complete definition

bimap | first , second

Methods

bimap :: (a -> b) -> (c -> d) -> p a c -> p b d Source #

Map over both arguments at the same time.

bimap f g ≡ first f . second g

Examples

Expand
>>> bimap toUpper (+1) ('j', 3)
('J',4)
>>> bimap toUpper (+1) (Left 'j')
Left 'J'
>>> bimap toUpper (+1) (Right 3)
Right 4

first :: (a -> b) -> p a c -> p b c Source #

Map covariantly over the first argument.

first f ≡ bimap f id

Examples

Expand
>>> first toUpper ('j', 3)
('J',3)
>>> first toUpper (Left 'j')
Left 'J'

second :: (b -> c) -> p a b -> p a c Source #

Map covariantly over the second argument.

second ≡ bimap id

Examples

Expand
>>> second (+1) ('j', 3)
('j',4)
>>> second (+1) (Right 3)
Right 4

Instances

Instances details
Bifunctor Either

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d Source #

first :: (a -> b) -> Either a c -> Either b c Source #

second :: (b -> c) -> Either a b -> Either a c Source #

Bifunctor (,)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (a, c) -> (b, d) Source #

first :: (a -> b) -> (a, c) -> (b, c) Source #

second :: (b -> c) -> (a, b) -> (a, c) Source #

Bifunctor Arg

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

bimap :: (a -> b) -> (c -> d) -> Arg a c -> Arg b d Source #

first :: (a -> b) -> Arg a c -> Arg b c Source #

second :: (b -> c) -> Arg a b -> Arg a c Source #

Bifunctor These
Instance details

Defined in Basement.These

Methods

bimap :: (a -> b) -> (c -> d) -> These a c -> These b d Source #

first :: (a -> b) -> These a c -> These b c Source #

second :: (b -> c) -> These a b -> These a c Source #

Bifunctor Tuple2 Source #
Instance details

Defined in Foundation.Tuple

Methods

bimap :: (a -> b) -> (c -> d) -> Tuple2 a c -> Tuple2 b d Source #

first :: (a -> b) -> Tuple2 a c -> Tuple2 b c Source #

second :: (b -> c) -> Tuple2 a b -> Tuple2 a c Source #

Bifunctor ( (,,) x1)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, a, c) -> (x1, b, d) Source #

first :: (a -> b) -> (x1, a, c) -> (x1, b, c) Source #

second :: (b -> c) -> (x1, a, b) -> (x1, a, c) Source #

Bifunctor ( Const :: Type -> Type -> Type )

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Const a c -> Const b d Source #

first :: (a -> b) -> Const a c -> Const b c Source #

second :: (b -> c) -> Const a b -> Const a c Source #

Bifunctor ( K1 i :: Type -> Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> K1 i a c -> K1 i b d Source #

first :: (a -> b) -> K1 i a c -> K1 i b c Source #

second :: (b -> c) -> K1 i a b -> K1 i a c Source #

Bifunctor ( (,,,) x1 x2)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, a, c) -> (x1, x2, b, d) Source #

first :: (a -> b) -> (x1, x2, a, c) -> (x1, x2, b, c) Source #

second :: (b -> c) -> (x1, x2, a, b) -> (x1, x2, a, c) Source #

Bifunctor ( (,,,,) x1 x2 x3)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, a, c) -> (x1, x2, x3, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, a, b) -> (x1, x2, x3, a, c) Source #

Bifunctor ( (,,,,,) x1 x2 x3 x4)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, x4, a, c) -> (x1, x2, x3, x4, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, x4, a, b) -> (x1, x2, x3, x4, a, c) Source #

Bifunctor ( (,,,,,,) x1 x2 x3 x4 x5)

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, d) Source #

first :: (a -> b) -> (x1, x2, x3, x4, x5, a, c) -> (x1, x2, x3, x4, x5, b, c) Source #

second :: (b -> c) -> (x1, x2, x3, x4, x5, a, b) -> (x1, x2, x3, x4, x5, a, c) Source #

class Functor f => Applicative (f :: Type -> Type ) where Source #

A functor with application, providing operations to

  • embed pure expressions ( pure ), and
  • sequence computations and combine their results ( <*> and liftA2 ).

A minimal complete definition must include implementations of pure and of either <*> or liftA2 . If it defines both, then they must behave the same as their default definitions:

(<*>) = liftA2 id
liftA2 f x y = f <$> x <*> y

Further, any definition must satisfy the following:

Identity
pure id <*> v = v
Composition
pure (.) <*> u <*> v <*> w = u <*> (v <*> w)
Homomorphism
pure f <*> pure x = pure (f x)
Interchange
u <*> pure y = pure ($ y) <*> u

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

It may be useful to note that supposing

forall x y. p (q x y) = f x . g y

it follows from the above that

liftA2 p (liftA2 q u v) = liftA2 f u . liftA2 g v

If f is also a Monad , it should satisfy

(which implies that pure and <*> satisfy the applicative functor laws).

Minimal complete definition

pure , ( (<*>) | liftA2 )

Methods

pure :: a -> f a Source #

Lift a value.

(<*>) :: f (a -> b) -> f a -> f b infixl 4 Source #

Sequential application.

A few functors support an implementation of <*> that is more efficient than the default one.

Using ApplicativeDo : ' fs <*> as ' can be understood as the do expression

do f <- fs
   a <- as
   pure (f a)

liftA2 :: (a -> b -> c) -> f a -> f b -> f c Source #

Lift a binary function to actions.

Some functors support an implementation of liftA2 that is more efficient than the default one. In particular, if fmap is an expensive operation, it is likely better to use liftA2 than to fmap over the structure and then use <*> .

This became a typeclass method in 4.10.0.0. Prior to that, it was a function defined in terms of <*> and fmap .

Using ApplicativeDo : ' liftA2 f as bs ' can be understood as the do expression

do a <- as
   b <- bs
   pure (f a b)

(*>) :: f a -> f b -> f b infixl 4 Source #

Sequence actions, discarding the value of the first argument.

' as *> bs ' can be understood as the do expression

do as
   bs

This is a tad complicated for our ApplicativeDo extension which will give it a Monad constraint. For an Applicative constraint we write it of the form

do _ <- as
   b <- bs
   pure b

(<*) :: f a -> f b -> f a infixl 4 Source #

Sequence actions, discarding the value of the second argument.

Using ApplicativeDo : ' as <* bs ' can be understood as the do expression

do a <- as
   bs
   pure a

Instances

Instances details
Applicative []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> [a] Source #

(<*>) :: [a -> b] -> [a] -> [b] Source #

liftA2 :: (a -> b -> c) -> [a] -> [b] -> [c] Source #

(*>) :: [a] -> [b] -> [b] Source #

(<*) :: [a] -> [b] -> [a] Source #

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Applicative IO

Since: base-2.1

Instance details

Defined in GHC.Base

Applicative Par1

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Applicative Min

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Applicative Max

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Applicative First

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Applicative Last

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Applicative Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Applicative ZipList
f <$> ZipList xs1 <*> ... <*> ZipList xsN
    = ZipList (zipWithN f xs1 ... xsN)

where zipWithN refers to the zipWith function of the appropriate arity ( zipWith , zipWith3 , zipWith4 , ...). For example:

(\a b c -> stimes c [a, b]) <$> ZipList "abcd" <*> ZipList "567" <*> ZipList [1..]
    = ZipList (zipWith3 (\a b c -> stimes c [a, b]) "abcd" "567" [1..])
    = ZipList {getZipList = ["a5","b6b6","c7c7c7"]}

Since: base-2.1

Instance details

Defined in Control.Applicative

Applicative Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Applicative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Applicative First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Applicative Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Applicative Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Applicative Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Applicative ReadP

Since: base-4.6.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Applicative P

Since: base-4.5.0.0

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

pure :: a -> P a Source #

(<*>) :: P (a -> b) -> P a -> P b Source #

liftA2 :: (a -> b -> c) -> P a -> P b -> P c Source #

(*>) :: P a -> P b -> P b Source #

(<*) :: P a -> P b -> P a Source #

Applicative DList Source #
Instance details

Defined in Foundation.List.DList

Applicative Partial Source #
Instance details

Defined in Foundation.Partial

Applicative Gen Source #
Instance details

Defined in Foundation.Check.Gen

Applicative Check Source #
Instance details

Defined in Foundation.Check.Types

Applicative ( Either e)

Since: base-3.0

Instance details

Defined in Data.Either

Applicative ( U1 :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Monoid a => Applicative ( (,) a)

For tuples, the Monoid constraint on a determines how the first values merge. For example, String s concatenate:

("hello ", (+15)) <*> ("world!", 2002)
("hello world!",2017)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, a0) Source #

(<*>) :: (a, a0 -> b) -> (a, a0) -> (a, b) Source #

liftA2 :: (a0 -> b -> c) -> (a, a0) -> (a, b) -> (a, c) Source #

(*>) :: (a, a0) -> (a, b) -> (a, b) Source #

(<*) :: (a, a0) -> (a, b) -> (a, a0) Source #

Monad m => Applicative ( WrappedMonad m)

Since: base-2.1

Instance details

Defined in Control.Applicative

Arrow a => Applicative ( ArrowMonad a)

Since: base-4.6.0.0

Instance details

Defined in Control.Arrow

Applicative ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Applicative ( ST s)

Since: base-4.4.0.0

Instance details

Defined in GHC.ST

Methods

pure :: a -> ST s a Source #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b Source #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c Source #

(*>) :: ST s a -> ST s b -> ST s b Source #

(<*) :: ST s a -> ST s b -> ST s a Source #

Applicative m => Applicative ( ResourceT m) Source #
Instance details

Defined in Foundation.Conduit.Internal

ParserSource input => Applicative ( Parser input) Source #
Instance details

Defined in Foundation.Parser

Methods

pure :: a -> Parser input a Source #

(<*>) :: Parser input (a -> b) -> Parser input a -> Parser input b Source #

liftA2 :: (a -> b -> c) -> Parser input a -> Parser input b -> Parser input c Source #

(*>) :: Parser input a -> Parser input b -> Parser input b Source #

(<*) :: Parser input a -> Parser input b -> Parser input a Source #

Applicative ( MonadRandomState gen) Source #
Instance details

Defined in Foundation.Random.DRG

Applicative f => Applicative ( Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

( Monoid a, Monoid b) => Applicative ( (,,) a b)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, b, a0) Source #

(<*>) :: (a, b, a0 -> b0) -> (a, b, a0) -> (a, b, b0) Source #

liftA2 :: (a0 -> b0 -> c) -> (a, b, a0) -> (a, b, b0) -> (a, b, c) Source #

(*>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

(<*) :: (a, b, a0) -> (a, b, b0) -> (a, b, a0) Source #

Arrow a => Applicative ( WrappedArrow a b)

Since: base-2.1

Instance details

Defined in Control.Applicative

Applicative m => Applicative ( Kleisli m a)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Monoid m => Applicative ( Const m :: Type -> Type )

Since: base-2.0.1

Instance details

Defined in Data.Functor.Const

Applicative f => Applicative ( Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Ap f a Source #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b Source #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c Source #

(*>) :: Ap f a -> Ap f b -> Ap f b Source #

(<*) :: Ap f a -> Ap f b -> Ap f a Source #

Applicative f => Applicative ( Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monad m => Applicative ( State s m)
Instance details

Defined in Basement.Compat.MonadTrans

Methods

pure :: a -> State s m a Source #

(<*>) :: State s m (a -> b) -> State s m a -> State s m b Source #

liftA2 :: (a -> b -> c) -> State s m a -> State s m b -> State s m c Source #

(*>) :: State s m a -> State s m b -> State s m b Source #

(<*) :: State s m a -> State s m b -> State s m a Source #

Monad m => Applicative ( Reader r m)
Instance details

Defined in Basement.Compat.MonadTrans

( Applicative m, Monad m) => Applicative ( StateT s m) Source #
Instance details

Defined in Foundation.Monad.State

Applicative m => Applicative ( ReaderT r m) Source #
Instance details

Defined in Foundation.Monad.Reader

Monad m => Applicative ( ExceptT e m) Source #
Instance details

Defined in Foundation.Monad.Except

Monad m => Applicative ( ZipSink i m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Applicative ((->) r :: Type -> Type )

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

pure :: a -> r -> a Source #

(<*>) :: (r -> (a -> b)) -> (r -> a) -> r -> b Source #

liftA2 :: (a -> b -> c) -> (r -> a) -> (r -> b) -> r -> c Source #

(*>) :: (r -> a) -> (r -> b) -> r -> b Source #

(<*) :: (r -> a) -> (r -> b) -> r -> a Source #

Monoid c => Applicative ( K1 i c :: Type -> Type )

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> K1 i c a Source #

(<*>) :: K1 i c (a -> b) -> K1 i c a -> K1 i c b Source #

liftA2 :: (a -> b -> c0) -> K1 i c a -> K1 i c b -> K1 i c c0 Source #

(*>) :: K1 i c a -> K1 i c b -> K1 i c b Source #

(<*) :: K1 i c a -> K1 i c b -> K1 i c a Source #

( Applicative f, Applicative g) => Applicative (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :*: g) a Source #

(<*>) :: (f :*: g) (a -> b) -> (f :*: g) a -> (f :*: g) b Source #

liftA2 :: (a -> b -> c) -> (f :*: g) a -> (f :*: g) b -> (f :*: g) c Source #

(*>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

(<*) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) a Source #

( Monoid a, Monoid b, Monoid c) => Applicative ( (,,,) a b c)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a0 -> (a, b, c, a0) Source #

(<*>) :: (a, b, c, a0 -> b0) -> (a, b, c, a0) -> (a, b, c, b0) Source #

liftA2 :: (a0 -> b0 -> c0) -> (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, c0) Source #

(*>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source #

(<*) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, a0) Source #

Applicative ( Conduit i o m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Methods

pure :: a -> Conduit i o m a Source #

(<*>) :: Conduit i o m (a -> b) -> Conduit i o m a -> Conduit i o m b Source #

liftA2 :: (a -> b -> c) -> Conduit i o m a -> Conduit i o m b -> Conduit i o m c Source #

(*>) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m b Source #

(<*) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m a Source #

Applicative f => Applicative ( M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> M1 i c f a Source #

(<*>) :: M1 i c f (a -> b) -> M1 i c f a -> M1 i c f b Source #

liftA2 :: (a -> b -> c0) -> M1 i c f a -> M1 i c f b -> M1 i c f c0 Source #

(*>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

(<*) :: M1 i c f a -> M1 i c f b -> M1 i c f a Source #

( Applicative f, Applicative g) => Applicative (f :.: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

pure :: a -> (f :.: g) a Source #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b Source #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c Source #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b Source #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a Source #

Monad state => Applicative ( Builder collection mutCollection step state err)
Instance details

Defined in Basement.MutableBuilder

Methods

pure :: a -> Builder collection mutCollection step state err a Source #

(<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b Source #

liftA2 :: (a -> b -> c) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err c Source #

(*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b Source #

(<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a Source #

class Applicative m => Monad (m :: Type -> Type ) where Source #

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:

Left identity
return a >>= k = k a
Right identity
m >>= return = m
Associativity
m >>= (\x -> k x >>= h) = (m >>= k) >>= h

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.

Minimal complete definition

(>>=)

Methods

(>>=) :: m a -> (a -> m b) -> m b infixl 1 Source #

Sequentially compose two actions, passing any value produced by the first as an argument to the second.

' as >>= bs ' can be understood as the do expression

do a <- as
   bs a

(>>) :: m a -> m b -> m b infixl 1 Source #

Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.

' as >> bs ' can be understood as the do expression

do as
   bs

return :: a -> m a Source #

Inject a value into the monadic type.

Instances

Instances details
Monad []

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: [a] -> (a -> [b]) -> [b] Source #

(>>) :: [a] -> [b] -> [b] Source #

return :: a -> [a] Source #

Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Monad IO

Since: base-2.1

Instance details

Defined in GHC.Base

Monad Par1

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Monad Min

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monad Max

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monad First

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monad Last

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monad Option

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monad Identity

Since: base-4.8.0.0

Instance details

Defined in Data.Functor.Identity

Monad STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Monad First

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Monad Last

Since: base-4.8.0.0

Instance details

Defined in Data.Monoid

Monad Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monad Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monad Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monad Down

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Monad ReadP

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monad P

Since: base-2.1

Instance details

Defined in Text.ParserCombinators.ReadP

Methods

(>>=) :: P a -> (a -> P b) -> P b Source #

(>>) :: P a -> P b -> P b Source #

return :: a -> P a Source #

Monad DList Source #
Instance details

Defined in Foundation.List.DList

Monad Partial Source #
Instance details

Defined in Foundation.Partial

Monad Gen Source #
Instance details

Defined in Foundation.Check.Gen

Monad Check Source #
Instance details

Defined in Foundation.Check.Types

Monad ( Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

Monad ( U1 :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Monoid a => Monad ( (,) a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, a0) -> (a0 -> (a, b)) -> (a, b) Source #

(>>) :: (a, a0) -> (a, b) -> (a, b) Source #

return :: a0 -> (a, a0) Source #

Monad m => Monad ( WrappedMonad m)

Since: base-4.7.0.0

Instance details

Defined in Control.Applicative

ArrowApply a => Monad ( ArrowMonad a)

Since: base-2.1

Instance details

Defined in Control.Arrow

Monad ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Monad ( ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Monad m => Monad ( ResourceT m) Source #
Instance details

Defined in Foundation.Conduit.Internal

ParserSource input => Monad ( Parser input) Source #
Instance details

Defined in Foundation.Parser

Methods

(>>=) :: Parser input a -> (a -> Parser input b) -> Parser input b Source #

(>>) :: Parser input a -> Parser input b -> Parser input b Source #

return :: a -> Parser input a Source #

Monad ( MonadRandomState gen) Source #
Instance details

Defined in Foundation.Random.DRG

Monad f => Monad ( Rec1 f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

( Monoid a, Monoid b) => Monad ( (,,) a b)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, b, a0) -> (a0 -> (a, b, b0)) -> (a, b, b0) Source #

(>>) :: (a, b, a0) -> (a, b, b0) -> (a, b, b0) Source #

return :: a0 -> (a, b, a0) Source #

Monad m => Monad ( Kleisli m a)

Since: base-4.14.0.0

Instance details

Defined in Control.Arrow

Monad f => Monad ( Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Monad f => Monad ( Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monad m => Monad ( State r m)
Instance details

Defined in Basement.Compat.MonadTrans

Monad m => Monad ( Reader r m)
Instance details

Defined in Basement.Compat.MonadTrans

( Functor m, Monad m) => Monad ( StateT s m) Source #
Instance details

Defined in Foundation.Monad.State

Monad m => Monad ( ReaderT r m) Source #
Instance details

Defined in Foundation.Monad.Reader

Monad m => Monad ( ExceptT e m) Source #
Instance details

Defined in Foundation.Monad.Except

Monad ((->) r :: Type -> Type )

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

(>>=) :: (r -> a) -> (a -> r -> b) -> r -> b Source #

(>>) :: (r -> a) -> (r -> b) -> r -> b Source #

return :: a -> r -> a Source #

( Monad f, Monad g) => Monad (f :*: g)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: (f :*: g) a -> (a -> (f :*: g) b) -> (f :*: g) b Source #

(>>) :: (f :*: g) a -> (f :*: g) b -> (f :*: g) b Source #

return :: a -> (f :*: g) a Source #

( Monoid a, Monoid b, Monoid c) => Monad ( (,,,) a b c)

Since: base-4.14.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: (a, b, c, a0) -> (a0 -> (a, b, c, b0)) -> (a, b, c, b0) Source #

(>>) :: (a, b, c, a0) -> (a, b, c, b0) -> (a, b, c, b0) Source #

return :: a0 -> (a, b, c, a0) Source #

Monad ( Conduit i o m) Source #
Instance details

Defined in Foundation.Conduit.Internal

Methods

(>>=) :: Conduit i o m a -> (a -> Conduit i o m b) -> Conduit i o m b Source #

(>>) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m b Source #

return :: a -> Conduit i o m a Source #

Monad f => Monad ( M1 i c f)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(>>=) :: M1 i c f a -> (a -> M1 i c f b) -> M1 i c f b Source #

(>>) :: M1 i c f a -> M1 i c f b -> M1 i c f b Source #

return :: a -> M1 i c f a Source #

Monad state => Monad ( Builder collection mutCollection step state err)
Instance details

Defined in Basement.MutableBuilder

Methods

(>>=) :: Builder collection mutCollection step state err a -> (a -> Builder collection mutCollection step state err b) -> Builder collection mutCollection step state err b Source #

(>>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b Source #

return :: a -> Builder collection mutCollection step state err a Source #

(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 Source #

Same as >>= , but with the arguments interchanged.

class IsString a where Source #

Class for string-like datastructures; used by the overloaded string extension (-XOverloadedStrings in GHC).

class IsList l where Source #

The IsList class and its methods are intended to be used in conjunction with the OverloadedLists extension.

Since: base-4.7.0.0

Minimal complete definition

fromList , toList

Associated Types

type Item l Source #

The Item type function returns the type of items of the structure l .

Methods

fromList :: [ Item l] -> l Source #

The fromList function constructs the structure l from the given list of Item l

fromListN :: Int -> [ Item l] -> l Source #

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.

toList :: l -> [ Item l] Source #

The toList function extracts a list of Item l from the structure l . It should satisfy fromList . toList = id.

Instances

Instances details
IsList CallStack

Be aware that 'fromList . toList = id' only for unfrozen CallStack s, since toList removes frozenness information.

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item CallStack Source #

IsList Version

Since: base-4.8.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item Version Source #

IsList String
Instance details

Defined in Basement.UTF8.Base

Associated Types

type Item String Source #

IsList AsciiString
Instance details

Defined in Basement.Types.AsciiString

IsList Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Associated Types

type Item Bitmap Source #

IsList CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Associated Types

type Item CSV Source #

IsList Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Associated Types

type Item Row Source #

IsList [a]

Since: base-4.7.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item [a] Source #

IsList ( ZipList a)

Since: base-4.15.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item ( ZipList a) Source #

IsList ( NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Exts

Associated Types

type Item ( NonEmpty a) Source #

IsList ( Array ty)
Instance details

Defined in Basement.BoxedArray

Associated Types

type Item ( Array ty) Source #

PrimType ty => IsList ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Associated Types

type Item ( UArray ty) Source #

PrimType ty => IsList ( Block ty)
Instance details

Defined in Basement.Block.Base

Associated Types

type Item ( Block ty) Source #

IsList c => IsList ( NonEmpty c)
Instance details

Defined in Basement.NonEmpty

Associated Types

type Item ( NonEmpty c) Source #

IsList ( DList a) Source #
Instance details

Defined in Foundation.List.DList

Associated Types

type Item ( DList a) Source #

PrimType ty => IsList ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Associated Types

type Item ( ChunkedUArray ty) Source #

Numeric type classes

class ( Integral a, Eq a, Ord a) => IsIntegral a where Source #

Number literals, convertible through the generic Integer type.

all number are Enum'erable, meaning that you can move to next element

Instances

Instances details
IsIntegral Int
Instance details

Defined in Basement.Numerical.Number

IsIntegral Int8
Instance details

Defined in Basement.Numerical.Number

IsIntegral Int16
Instance details

Defined in Basement.Numerical.Number

IsIntegral Int32
Instance details

Defined in Basement.Numerical.Number

IsIntegral Int64
Instance details

Defined in Basement.Numerical.Number

IsIntegral Integer
Instance details

Defined in Basement.Numerical.Number

IsIntegral Natural
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word8
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word16
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word32
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word64
Instance details

Defined in Basement.Numerical.Number

IsIntegral CChar
Instance details

Defined in Basement.Numerical.Number

IsIntegral CSChar
Instance details

Defined in Basement.Numerical.Number

IsIntegral CUChar
Instance details

Defined in Basement.Numerical.Number

IsIntegral CShort
Instance details

Defined in Basement.Numerical.Number

IsIntegral CUShort
Instance details

Defined in Basement.Numerical.Number

IsIntegral CInt
Instance details

Defined in Basement.Numerical.Number

IsIntegral CUInt
Instance details

Defined in Basement.Numerical.Number

IsIntegral CLong
Instance details

Defined in Basement.Numerical.Number

IsIntegral CULong
Instance details

Defined in Basement.Numerical.Number

IsIntegral CLLong
Instance details

Defined in Basement.Numerical.Number

IsIntegral CULLong
Instance details

Defined in Basement.Numerical.Number

IsIntegral CBool
Instance details

Defined in Basement.Numerical.Number

IsIntegral CPtrdiff
Instance details

Defined in Basement.Numerical.Number

IsIntegral CSize
Instance details

Defined in Basement.Numerical.Number

IsIntegral CWchar
Instance details

Defined in Basement.Numerical.Number

IsIntegral CSigAtomic
Instance details

Defined in Basement.Numerical.Number

IsIntegral CIntPtr
Instance details

Defined in Basement.Numerical.Number

IsIntegral CUIntPtr
Instance details

Defined in Basement.Numerical.Number

IsIntegral CIntMax
Instance details

Defined in Basement.Numerical.Number

IsIntegral CUIntMax
Instance details

Defined in Basement.Numerical.Number

IsIntegral Word256
Instance details

Defined in Basement.Types.Word256

IsIntegral Word128
Instance details

Defined in Basement.Types.Word128

IsIntegral ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

IsIntegral ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

( KnownNat n, NatWithinBound Word64 n) => IsIntegral ( Zn64 n)
Instance details

Defined in Basement.Bounded

KnownNat n => IsIntegral ( Zn n)
Instance details

Defined in Basement.Bounded

class IsIntegral a => IsNatural a where Source #

Non Negative Number literals, convertible through the generic Natural type

Instances

Instances details
IsNatural Natural
Instance details

Defined in Basement.Numerical.Number

IsNatural Word
Instance details

Defined in Basement.Numerical.Number

IsNatural Word8
Instance details

Defined in Basement.Numerical.Number

IsNatural Word16
Instance details

Defined in Basement.Numerical.Number

IsNatural Word32
Instance details

Defined in Basement.Numerical.Number

IsNatural Word64
Instance details

Defined in Basement.Numerical.Number

IsNatural CUChar
Instance details

Defined in Basement.Numerical.Number

IsNatural CUShort
Instance details

Defined in Basement.Numerical.Number

IsNatural CUInt
Instance details

Defined in Basement.Numerical.Number

IsNatural CULong
Instance details

Defined in Basement.Numerical.Number

IsNatural CULLong
Instance details

Defined in Basement.Numerical.Number

IsNatural CSize
Instance details

Defined in Basement.Numerical.Number

IsNatural CUIntPtr
Instance details

Defined in Basement.Numerical.Number

IsNatural CUIntMax
Instance details

Defined in Basement.Numerical.Number

IsNatural Word256
Instance details

Defined in Basement.Types.Word256

IsNatural Word128
Instance details

Defined in Basement.Types.Word128

IsNatural ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

IsNatural ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

( KnownNat n, NatWithinBound Word64 n) => IsNatural ( Zn64 n)
Instance details

Defined in Basement.Bounded

KnownNat n => IsNatural ( Zn n)
Instance details

Defined in Basement.Bounded

class Additive a where Source #

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

Minimal complete definition

azero , (+)

Methods

azero :: a Source #

(+) :: a -> a -> a infixl 6 Source #

scale :: IsNatural n => n -> a -> a Source #

Instances

Instances details
Additive Double
Instance details

Defined in Basement.Numerical.Additive

Additive Float
Instance details

Defined in Basement.Numerical.Additive

Additive Int
Instance details

Defined in Basement.Numerical.Additive

Additive Int8
Instance details

Defined in Basement.Numerical.Additive

Additive Int16
Instance details

Defined in Basement.Numerical.Additive

Additive Int32
Instance details

Defined in Basement.Numerical.Additive

Additive Int64
Instance details

Defined in Basement.Numerical.Additive

Additive Integer
Instance details

Defined in Basement.Numerical.Additive

Additive Natural
Instance details

Defined in Basement.Numerical.Additive

Additive Rational
Instance details

Defined in Basement.Numerical.Additive

Additive Word
Instance details

Defined in Basement.Numerical.Additive

Additive Word8
Instance details

Defined in Basement.Numerical.Additive

Additive Word16
Instance details

Defined in Basement.Numerical.Additive

Additive Word32
Instance details

Defined in Basement.Numerical.Additive

Additive Word64
Instance details

Defined in Basement.Numerical.Additive

Additive COff
Instance details

Defined in Basement.Numerical.Additive

Additive CChar
Instance details

Defined in Basement.Numerical.Additive

Additive CSChar
Instance details

Defined in Basement.Numerical.Additive

Additive CUChar
Instance details

Defined in Basement.Numerical.Additive

Additive CShort
Instance details

Defined in Basement.Numerical.Additive

Additive CUShort
Instance details

Defined in Basement.Numerical.Additive

Additive CInt
Instance details

Defined in Basement.Numerical.Additive

Additive CUInt
Instance details

Defined in Basement.Numerical.Additive

Additive CLong
Instance details

Defined in Basement.Numerical.Additive

Additive CULong
Instance details

Defined in Basement.Numerical.Additive

Additive CLLong
Instance details

Defined in Basement.Numerical.Additive

Additive CULLong
Instance details

Defined in Basement.Numerical.Additive

Additive CFloat
Instance details

Defined in Basement.Numerical.Additive

Additive CDouble
Instance details

Defined in Basement.Numerical.Additive

Additive CPtrdiff
Instance details

Defined in Basement.Numerical.Additive

Additive CSize
Instance details

Defined in Basement.Numerical.Additive

Additive CWchar
Instance details

Defined in Basement.Numerical.Additive

Additive CSigAtomic
Instance details

Defined in Basement.Numerical.Additive

Additive CClock
Instance details

Defined in Basement.Numerical.Additive

Additive CTime
Instance details

Defined in Basement.Numerical.Additive

Additive CUSeconds
Instance details

Defined in Basement.Numerical.Additive

Additive CSUSeconds
Instance details

Defined in Basement.Numerical.Additive

Additive CIntPtr
Instance details

Defined in Basement.Numerical.Additive

Additive CUIntPtr
Instance details

Defined in Basement.Numerical.Additive

Additive CIntMax
Instance details

Defined in Basement.Numerical.Additive

Additive CUIntMax
Instance details

Defined in Basement.Numerical.Additive

Additive Word256
Instance details

Defined in Basement.Numerical.Additive

Additive Word128
Instance details

Defined in Basement.Numerical.Additive

Additive Seconds Source #
Instance details

Defined in Foundation.Time.Types

Additive NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

SizeValid n => Additive ( Bits n)
Instance details

Defined in Basement.Bits

Additive ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Additive ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

( KnownNat n, NatWithinBound Word64 n) => Additive ( Zn64 n)
Instance details

Defined in Basement.Numerical.Additive

KnownNat n => Additive ( Zn n)
Instance details

Defined in Basement.Numerical.Additive

class Subtractive a where Source #

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

Associated Types

type Difference a Source #

Methods

(-) :: a -> a -> Difference a infixl 6 Source #

Instances

Instances details
Subtractive Char
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Double
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Float
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Int
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int Source #

Subtractive Int8
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Int16
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Int32
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Int64
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Integer
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Natural
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word8
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word16
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word32
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word64
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive COff
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CChar
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CSChar
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUChar
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CShort
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUShort
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CInt
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUInt
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CLong
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CULong
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CLLong
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CULLong
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CBool
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CFloat
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CDouble
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CPtrdiff
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CSize
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CWchar
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CSigAtomic
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CClock
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CTime
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUSeconds
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CSUSeconds
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CIntPtr
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUIntPtr
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CIntMax
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive CUIntMax
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word256
Instance details

Defined in Basement.Numerical.Subtractive

Subtractive Word128
Instance details

Defined in Basement.Numerical.Subtractive

SizeValid n => Subtractive ( Bits n)
Instance details

Defined in Basement.Bits

Associated Types

type Difference ( Bits n) Source #

Subtractive ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference ( Offset ty) Source #

Subtractive ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference ( CountOf ty) Source #

( KnownNat n, NatWithinBound Word64 n) => Subtractive ( Zn64 n)
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference ( Zn64 n) Source #

KnownNat n => Subtractive ( Zn n)
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference ( Zn n) Source #

class Multiplicative a where Source #

Represent class of things that can be multiplied together

x * midentity = x
midentity * x = x

Minimal complete definition

midentity , (*)

Methods

midentity :: a Source #

Identity element over multiplication

(*) :: a -> a -> a infixl 7 Source #

Multiplication of 2 elements that result in another element

(^) :: ( IsNatural n, Enum n, IDivisible n) => a -> n -> a infixr 8 Source #

Raise to power, repeated multiplication e.g. > a ^ 2 = a * a > a ^ 10 = (a ^ 5) * (a ^ 5) .. (^) :: (IsNatural n) => a -> n -> a

Instances

Instances details
Multiplicative Double
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Float
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Int
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Int8
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Int16
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Int32
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Int64
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Integer
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Natural
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Rational
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word8
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word16
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word32
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word64
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative COff
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CChar
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSChar
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUChar
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CShort
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUShort
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CInt
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUInt
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CLong
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CULong
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CLLong
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CULLong
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CFloat
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CDouble
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CPtrdiff
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSize
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CWchar
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSigAtomic
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CClock
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CTime
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUSeconds
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CSUSeconds
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CIntPtr
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUIntPtr
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CIntMax
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative CUIntMax
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word256
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Word128
Instance details

Defined in Basement.Numerical.Multiplicative

SizeValid n => Multiplicative ( Bits n)
Instance details

Defined in Basement.Bits

class ( Additive a, Multiplicative a) => IDivisible a where Source #

Represent types that supports an euclidian division

(x ‘div‘ y) * y + (x ‘mod‘ y) == x

Minimal complete definition

div , mod | divMod

Methods

div :: a -> a -> a Source #

mod :: a -> a -> a Source #

divMod :: a -> a -> (a, a) Source #

Instances

Instances details
IDivisible Int
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int8
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int16
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int32
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int64
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Integer
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Natural
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word8
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word16
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word32
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word64
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CChar
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CSChar
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUChar
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CShort
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUShort
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CInt
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUInt
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CLong
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CULong
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CLLong
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CULLong
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CPtrdiff
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CSize
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CWchar
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CSigAtomic
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CIntPtr
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUIntPtr
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CIntMax
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible CUIntMax
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word256
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word128
Instance details

Defined in Basement.Numerical.Multiplicative

SizeValid n => IDivisible ( Bits n)
Instance details

Defined in Basement.Bits

class Multiplicative a => Divisible a where Source #

Support for division between same types

This is likely to change to represent specific mathematic divisions

Methods

(/) :: a -> a -> a infixl 7 Source #

Data types

data Maybe a Source #

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.

Constructors

Nothing
Just a

Instances

Instances details
Monad Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Functor Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

MonadFix Maybe

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Maybe a) -> Maybe a Source #

MonadFail Maybe

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Applicative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

Foldable Maybe

Since: base-2.1

Instance details

Defined in Data.Foldable

Traversable Maybe

Since: base-2.1

Instance details

Defined in Data.Traversable

Alternative Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

MonadPlus Maybe

Since: base-2.1

Instance details

Defined in GHC.Base

MonadFailure Maybe
Instance details

Defined in Basement.Monad

Associated Types

type Failure Maybe Source #

Eq a => Eq ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Data a => Data ( Maybe a)

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Maybe a -> c ( Maybe a) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Maybe a) Source #

toConstr :: Maybe a -> Constr Source #

dataTypeOf :: Maybe a -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Maybe a)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Maybe a)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Maybe a -> Maybe a Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Maybe a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Maybe a -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Maybe a -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Maybe a -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Maybe a -> m ( Maybe a) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Maybe a -> m ( Maybe a) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Maybe a -> m ( Maybe a) Source #

Ord a => Ord ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Maybe

Read a => Read ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Read

Show a => Show ( Maybe a)

Since: base-2.1

Instance details

Defined in GHC.Show

Generic ( Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( Maybe a) :: Type -> Type Source #

Semigroup a => Semigroup ( Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup a => Monoid ( Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid : "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S ."

Since 4.11.0 : constraint on inner a value generalised from Monoid to Semigroup .

Since: base-2.1

Instance details

Defined in GHC.Base

NormalForm a => NormalForm ( Maybe a)
Instance details

Defined in Basement.NormalForm

SingKind a => SingKind ( Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep ( Maybe a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> DemoteRep ( Maybe a)

Arbitrary a => Arbitrary ( Maybe a) Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField a => IsField ( Maybe a) Source #
Instance details

Defined in Foundation.Format.CSV.Types

Generic1 Maybe

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Maybe :: k -> Type Source #

Methods

from1 :: forall (a :: k). Maybe a -> Rep1 Maybe a Source #

to1 :: forall (a :: k). Rep1 Maybe a -> Maybe a Source #

SingI (' Nothing :: Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ' Nothing

From ( Maybe a) ( Either () a)
Instance details

Defined in Basement.From

SingI a2 => SingI (' Just a2 :: Maybe a1)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing (' Just a2)

type Failure Maybe
Instance details

Defined in Basement.Monad

type Rep ( Maybe a)
Instance details

Defined in GHC.Generics

type DemoteRep ( Maybe a)
Instance details

Defined in GHC.Generics

type DemoteRep ( Maybe a) = Maybe (DemoteRep a)
data Sing (b :: Maybe a)
Instance details

Defined in GHC.Generics

data Sing (b :: Maybe a) where
type Rep1 Maybe
Instance details

Defined in GHC.Generics

data Ordering Source #

Constructors

LT
EQ
GT

Instances

Instances details
Bounded Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Ordering

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Ordering
Instance details

Defined in GHC.Classes

Data Ordering

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Ordering -> c Ordering Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Ordering Source #

toConstr :: Ordering -> Constr Source #

dataTypeOf :: Ordering -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Ordering ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Ordering ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Ordering -> Ordering Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Ordering -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Ordering -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Ordering -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Ordering -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Ordering -> m Ordering Source #

Ord Ordering
Instance details

Defined in GHC.Classes

Read Ordering

Since: base-2.1

Instance details

Defined in GHC.Read

Show Ordering

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Ordering

Since: base-2.1

Instance details

Defined in GHC.Ix

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

type Rep Ordering
Instance details

Defined in GHC.Generics

data Bool Source #

Constructors

False
True

Instances

Instances details
Bounded Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Bool

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Bool
Instance details

Defined in GHC.Classes

Data Bool

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Bool -> c Bool Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Bool Source #

toConstr :: Bool -> Constr Source #

dataTypeOf :: Bool -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Bool ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Bool ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Bool -> Bool Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Bool -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Bool -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Bool -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Bool -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Bool -> m Bool Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Bool -> m Bool Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Bool -> m Bool Source #

Ord Bool
Instance details

Defined in GHC.Classes

Read Bool

Since: base-2.1

Instance details

Defined in GHC.Read

Show Bool

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Bool

Since: base-2.1

Instance details

Defined in GHC.Ix

Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type Source #

Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Bool

Interpret Bool as 1-bit bit-field

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

FiniteBits Bool

Since: base-4.7.0.0

Instance details

Defined in Data.Bits

FiniteBitsOps Bool
Instance details

Defined in Basement.Bits

BitOps Bool
Instance details

Defined in Basement.Bits

NormalForm Bool
Instance details

Defined in Basement.NormalForm

SingKind Bool

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Bool

Methods

fromSing :: forall (a :: Bool ). Sing a -> DemoteRep Bool

Arbitrary Bool Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Bool Source #
Instance details

Defined in Foundation.Format.CSV.Types

IsProperty Bool Source #
Instance details

Defined in Foundation.Check.Property

SingI ' False

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ' False

SingI ' True

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing ' True

IsProperty ( String , Bool ) Source #
Instance details

Defined in Foundation.Check.Property

type Rep Bool
Instance details

Defined in GHC.Generics

type DemoteRep Bool
Instance details

Defined in GHC.Generics

type DemoteRep Bool = Bool
data Sing (a :: Bool )
Instance details

Defined in GHC.Generics

data Sing (a :: Bool ) where

data Char Source #

The character type Char is an enumeration whose values represent Unicode (or equivalently ISO/IEC 10646) code points (i.e. 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 ).

Instances

Instances details
Bounded Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Char

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Char
Instance details

Defined in GHC.Classes

Data Char

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Char -> c Char Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Char Source #

toConstr :: Char -> Constr Source #

dataTypeOf :: Char -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Char ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Char ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Char -> Char Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Char -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Char -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Char -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Char -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Char -> m Char Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Char -> m Char Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Char -> m Char Source #

Ord Char
Instance details

Defined in GHC.Classes

Read Char

Since: base-2.1

Instance details

Defined in GHC.Read

Show Char

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Char

Since: base-2.1

Instance details

Defined in GHC.Ix

PrintfArg Char

Since: base-2.1

Instance details

Defined in Text.Printf

IsChar Char

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

NormalForm Char
Instance details

Defined in Basement.NormalForm

PrimType Char
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Char
Instance details

Defined in Basement.PrimType

Subtractive Char
Instance details

Defined in Basement.Numerical.Subtractive

StorableFixed Char Source #
Instance details

Defined in Foundation.Class.Storable

Storable Char Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Char Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Char Source #
Instance details

Defined in Foundation.Format.CSV.Types

Generic1 ( URec Char :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Char ) :: k -> Type Source #

Foldable ( UChar :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UChar :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

IsField [ Char ] Source #
Instance details

Defined in Foundation.Format.CSV.Types

Functor ( URec Char :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic ( URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( URec Char p) :: Type -> Type Source #

type PrimSize Char
Instance details

Defined in Basement.PrimType

type Difference Char
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Char
Instance details

Defined in Basement.Nat

data URec Char (p :: k)

Used for marking occurrences of Char#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Char :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Char p)
Instance details

Defined in GHC.Generics

data Char7 Source #

ASCII value between 0x0 and 0x7f

Instances

Instances details
Eq Char7
Instance details

Defined in Basement.Types.Char7

Ord Char7
Instance details

Defined in Basement.Types.Char7

Show Char7
Instance details

Defined in Basement.Types.Char7

NormalForm Char7
Instance details

Defined in Basement.NormalForm

PrimType Char7
Instance details

Defined in Basement.PrimType

Arbitrary Char7 Source #
Instance details

Defined in Foundation.Check.Arbitrary

type PrimSize Char7
Instance details

Defined in Basement.PrimType

type NatNumMaxBound Char7
Instance details

Defined in Basement.Nat

data IO a Source #

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.

Instances

Instances details
Monad IO

Since: base-2.1

Instance details

Defined in GHC.Base

Functor IO

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

fmap :: (a -> b) -> IO a -> IO b Source #

(<$) :: a -> IO b -> IO a Source #

MonadFix IO

Since: base-2.1

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> IO a) -> IO a Source #

MonadFail IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.Fail

Applicative IO

Since: base-2.1

Instance details

Defined in GHC.Base

MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Alternative IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

MonadPlus IO

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

PrimMonad IO
Instance details

Defined in Basement.Monad

MonadBracket IO Source #
Instance details

Defined in Foundation.Monad.Exception

Methods

generalBracket :: IO a -> (a -> b -> IO ignored1) -> (a -> SomeException -> IO ignored2) -> (a -> IO b) -> IO b Source #

MonadCatch IO Source #
Instance details

Defined in Foundation.Monad.Exception

Methods

catch :: Exception e => IO a -> (e -> IO a) -> IO a Source #

MonadThrow IO Source #
Instance details

Defined in Foundation.Monad.Exception

MonadRandom IO Source #
Instance details

Defined in Foundation.Random.Class

Semigroup a => Semigroup ( IO a)

Since: base-4.10.0.0

Instance details

Defined in GHC.Base

Monoid a => Monoid ( IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

a ~ () => PrintfType ( IO a)

Since: base-4.7.0.0

Instance details

Defined in Text.Printf

Methods

spr :: String -> [UPrintf] -> IO a

a ~ () => HPrintfType ( IO a)

Since: base-4.7.0.0

Instance details

Defined in Text.Printf

Methods

hspr :: Handle -> String -> [UPrintf] -> IO a

type PrimVar IO
Instance details

Defined in Basement.Monad

type PrimState IO
Instance details

Defined in Basement.Monad

data Either a b Source #

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

Expand

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 String s, and the Right constructor can be used only on Int s:

>>> 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 Int s.

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

Constructors

Left a
Right b

Instances

Instances details
Bifunctor Either

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d Source #

first :: (a -> b) -> Either a c -> Either b c Source #

second :: (b -> c) -> Either a b -> Either a c Source #

Monad ( Either e)

Since: base-4.4.0.0

Instance details

Defined in Data.Either

Functor ( Either a)

Since: base-3.0

Instance details

Defined in Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

MonadFix ( Either e)

Since: base-4.3.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Either e a) -> Either e a Source #

Applicative ( Either e)

Since: base-3.0

Instance details

Defined in Data.Either

Foldable ( Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Either a m -> m Source #

foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source #

foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source #

foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source #

foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

toList :: Either a a0 -> [a0] Source #

null :: Either a a0 -> Bool Source #

length :: Either a a0 -> Int Source #

elem :: Eq a0 => a0 -> Either a a0 -> Bool Source #

maximum :: Ord a0 => Either a a0 -> a0 Source #

minimum :: Ord a0 => Either a a0 -> a0 Source #

sum :: Num a0 => Either a a0 -> a0 Source #

product :: Num a0 => Either a a0 -> a0 Source #

Traversable ( Either a)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f ( Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f ( Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m ( Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m ( Either a a0) Source #

MonadFailure ( Either a)
Instance details

Defined in Basement.Monad

Associated Types

type Failure ( Either a) Source #

Generic1 ( Either a :: Type -> Type )

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 ( Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 ( Either a) a0 -> Either a a0 Source #

From ( Maybe a) ( Either () a)
Instance details

Defined in Basement.From

( Eq a, Eq b) => Eq ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

( Data a, Data b) => Data ( Either a b)

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b0. Data d => c (d -> b0) -> d -> c b0) -> ( forall g. g -> c g) -> Either a b -> c ( Either a b) Source #

gunfold :: ( forall b0 r. Data b0 => c (b0 -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Either a b) Source #

toConstr :: Either a b -> Constr Source #

dataTypeOf :: Either a b -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Either a b)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Either a b)) Source #

gmapT :: ( forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Either a b -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Either a b -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Either a b -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Either a b -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Either a b -> m ( Either a b) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Either a b -> m ( Either a b) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Either a b -> m ( Either a b) Source #

( Ord a, Ord b) => Ord ( Either a b)

Since: base-2.1

Instance details

Defined in Data.Either

( Read a, Read b) => Read ( Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

( Show a, Show b) => Show ( Either a b)

Since: base-3.0

Instance details

Defined in Data.Either

Generic ( Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( Either a b) :: Type -> Type Source #

Semigroup ( Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

( NormalForm l, NormalForm r) => NormalForm ( Either l r)
Instance details

Defined in Basement.NormalForm

( Arbitrary l, Arbitrary r) => Arbitrary ( Either l r) Source #
Instance details

Defined in Foundation.Check.Arbitrary

From ( Either a b) ( These a b)
Instance details

Defined in Basement.From

type Failure ( Either a)
Instance details

Defined in Basement.Monad

type Failure ( Either a) = a
type Rep1 ( Either a :: Type -> Type )
Instance details

Defined in GHC.Generics

type Rep ( Either a b)
Instance details

Defined in GHC.Generics

Numbers

data Int8 Source #

8-bit signed integer type

Instances

Instances details
Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Int8 -> c Int8 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Int8 Source #

toConstr :: Int8 -> Constr Source #

dataTypeOf :: Int8 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Int8 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Int8 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Int8 -> Int8 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Int8 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Int8 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Int8 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Int8 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Int8 -> m Int8 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int8 -> m Int8 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int8 -> m Int8 Source #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBitsOps Int8
Instance details

Defined in Basement.Bits

BitOps Int8
Instance details

Defined in Basement.Bits

NormalForm Int8
Instance details

Defined in Basement.NormalForm

PrimType Int8
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int8
Instance details

Defined in Basement.PrimType

Multiplicative Int8
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int8
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Int8
Instance details

Defined in Basement.Numerical.Additive

Subtractive Int8
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Int8
Instance details

Defined in Basement.Numerical.Number

Integral Int8
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int8
Instance details

Defined in Basement.Compat.NumLiteral

Signed Int8 Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Int8 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Int8 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Int8 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Int8 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Int8 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Int8 -> st -> st Source #

From Int8 Int
Instance details

Defined in Basement.From

From Int8 Int16
Instance details

Defined in Basement.From

From Int8 Int32
Instance details

Defined in Basement.From

From Int8 Int64
Instance details

Defined in Basement.From

Cast Int8 Word8
Instance details

Defined in Basement.Cast

Cast Word8 Int8
Instance details

Defined in Basement.Cast

IntegralDownsize Int Int8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int8
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int64
Instance details

Defined in Basement.IntegralConv

type PrimSize Int8
Instance details

Defined in Basement.PrimType

type Difference Int8
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int8
Instance details

Defined in Basement.Nat

data Int16 Source #

16-bit signed integer type

Instances

Instances details
Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int16

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Int16 -> c Int16 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Int16 Source #

toConstr :: Int16 -> Constr Source #

dataTypeOf :: Int16 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Int16 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Int16 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Int16 -> Int16 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Int16 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Int16 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Int16 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Int16 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Int16 -> m Int16 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int16 -> m Int16 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int16 -> m Int16 Source #

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBitsOps Int16
Instance details

Defined in Basement.Bits

BitOps Int16
Instance details

Defined in Basement.Bits

NormalForm Int16
Instance details

Defined in Basement.NormalForm

PrimType Int16
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int16
Instance details

Defined in Basement.PrimType

Multiplicative Int16
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int16
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Int16
Instance details

Defined in Basement.Numerical.Additive

Subtractive Int16
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Int16
Instance details

Defined in Basement.Numerical.Number

Integral Int16
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int16
Instance details

Defined in Basement.Compat.NumLiteral

Signed Int16 Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Int16 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Int16 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Int16 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Int16 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Int16 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Int16 -> st -> st Source #

From Int8 Int16
Instance details

Defined in Basement.From

From Int16 Int
Instance details

Defined in Basement.From

From Int16 Int32
Instance details

Defined in Basement.From

From Int16 Int64
Instance details

Defined in Basement.From

From Word8 Int16
Instance details

Defined in Basement.From

Cast Int16 Word16
Instance details

Defined in Basement.Cast

Cast Word16 Int16
Instance details

Defined in Basement.Cast

IntegralDownsize Int Int16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int16
Instance details

Defined in Basement.IntegralConv

type PrimSize Int16
Instance details

Defined in Basement.PrimType

type Difference Int16
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int16
Instance details

Defined in Basement.Nat

data Int32 Source #

32-bit signed integer type

Instances

Instances details
Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Int32 -> c Int32 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Int32 Source #

toConstr :: Int32 -> Constr Source #

dataTypeOf :: Int32 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Int32 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Int32 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Int32 -> Int32 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Int32 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Int32 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Int32 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Int32 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Int32 -> m Int32 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int32 -> m Int32 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int32 -> m Int32 Source #

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBitsOps Int32
Instance details

Defined in Basement.Bits

BitOps Int32
Instance details

Defined in Basement.Bits

NormalForm Int32
Instance details

Defined in Basement.NormalForm

PrimType Int32
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int32
Instance details

Defined in Basement.PrimType

Multiplicative Int32
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int32
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Int32
Instance details

Defined in Basement.Numerical.Additive

Subtractive Int32
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Int32
Instance details

Defined in Basement.Numerical.Number

Integral Int32
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int32
Instance details

Defined in Basement.Compat.NumLiteral

Signed Int32 Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Int32 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Int32 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Int32 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Int32 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Int32 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Int32 -> st -> st Source #

From Int8 Int32
Instance details

Defined in Basement.From

From Int16 Int32
Instance details

Defined in Basement.From

From Int32 Int
Instance details

Defined in Basement.From

From Int32 Int64
Instance details

Defined in Basement.From

From Word8 Int32
Instance details

Defined in Basement.From

From Word16 Int32
Instance details

Defined in Basement.From

Cast Int32 Word32
Instance details

Defined in Basement.Cast

Cast Word32 Int32
Instance details

Defined in Basement.Cast

IntegralDownsize Int Int32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int32 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int32 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int32
Instance details

Defined in Basement.IntegralConv

type PrimSize Int32
Instance details

Defined in Basement.PrimType

type Difference Int32
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int32
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int32 = 2147483647

data Int64 Source #

64-bit signed integer type

Instances

Instances details
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int64

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Int64 -> c Int64 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Int64 Source #

toConstr :: Int64 -> Constr Source #

dataTypeOf :: Int64 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Int64 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Int64 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Int64 -> Int64 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Int64 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Int64 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Int64 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Int64 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Int64 -> m Int64 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int64 -> m Int64 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int64 -> m Int64 Source #

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

PrintfArg Int64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

FiniteBitsOps Int64
Instance details

Defined in Basement.Bits

BitOps Int64
Instance details

Defined in Basement.Bits

NormalForm Int64
Instance details

Defined in Basement.NormalForm

PrimType Int64
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int64
Instance details

Defined in Basement.PrimType

Multiplicative Int64
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int64
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Int64
Instance details

Defined in Basement.Numerical.Additive

Subtractive Int64
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Int64
Instance details

Defined in Basement.Numerical.Number

Integral Int64
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int64
Instance details

Defined in Basement.Compat.NumLiteral

Signed Int64 Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Int64 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Int64 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Int64 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Int64 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Int64 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Int64 -> st -> st Source #

From Int Int64
Instance details

Defined in Basement.From

From Int8 Int64
Instance details

Defined in Basement.From

From Int16 Int64
Instance details

Defined in Basement.From

From Int32 Int64
Instance details

Defined in Basement.From

From Word8 Int64
Instance details

Defined in Basement.From

From Word16 Int64
Instance details

Defined in Basement.From

From Word32 Int64
Instance details

Defined in Basement.From

Cast Int Int64
Instance details

Defined in Basement.Cast

Cast Int64 Int
Instance details

Defined in Basement.Cast

Cast Int64 Word
Instance details

Defined in Basement.Cast

Cast Int64 Word64
Instance details

Defined in Basement.Cast

Cast Word Int64
Instance details

Defined in Basement.Cast

Cast Word64 Int64
Instance details

Defined in Basement.Cast

IntegralDownsize Int64 Int
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int32 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int64
Instance details

Defined in Basement.IntegralConv

type PrimSize Int64
Instance details

Defined in Basement.PrimType

type Difference Int64
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int64
Instance details

Defined in Basement.Nat

type NatNumMaxBound Int64 = 9223372036854775807

data Word8 Source #

8-bit unsigned integer type

Instances

Instances details
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word8 -> c Word8 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word8 Source #

toConstr :: Word8 -> Constr Source #

dataTypeOf :: Word8 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word8 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word8 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word8 -> Word8 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word8 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word8 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word8 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word8 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word8 -> m Word8 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word8 -> m Word8 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word8 -> m Word8 Source #

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word8

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

FiniteBitsOps Word8
Instance details

Defined in Basement.Bits

BitOps Word8
Instance details

Defined in Basement.Bits

NormalForm Word8
Instance details

Defined in Basement.NormalForm

PrimType Word8
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word8
Instance details

Defined in Basement.PrimType

Multiplicative Word8
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word8
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word8
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word8
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word8
Instance details

Defined in Basement.Numerical.Number

IsNatural Word8
Instance details

Defined in Basement.Numerical.Number

Integral Word8
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word8
Instance details

Defined in Basement.Compat.NumLiteral

StorableFixed Word8 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word8 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word8 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word8 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word8 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word8 -> st -> st Source #

From Word8 Int
Instance details

Defined in Basement.From

From Word8 Int16
Instance details

Defined in Basement.From

From Word8 Int32
Instance details

Defined in Basement.From

From Word8 Int64
Instance details

Defined in Basement.From

From Word8 Word
Instance details

Defined in Basement.From

From Word8 Word16
Instance details

Defined in Basement.From

From Word8 Word32
Instance details

Defined in Basement.From

From Word8 Word64
Instance details

Defined in Basement.From

From Word8 Word256
Instance details

Defined in Basement.From

From Word8 Word128
Instance details

Defined in Basement.From

Cast Int8 Word8
Instance details

Defined in Basement.Cast

Cast Word8 Int8
Instance details

Defined in Basement.Cast

IntegralDownsize Integer Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word16 Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word32 Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word8
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word64
Instance details

Defined in Basement.IntegralConv

From String ( UArray Word8 )
Instance details

Defined in Basement.From

From AsciiString ( UArray Word8 )
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word8 n) => From ( Zn64 n) Word8
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word8 n) => From ( Zn n) Word8
Instance details

Defined in Basement.From

TryFrom ( UArray Word8 ) String
Instance details

Defined in Basement.From

Cast ( Block a) ( Block Word8 )
Instance details

Defined in Basement.Cast

type PrimSize Word8
Instance details

Defined in Basement.PrimType

type Difference Word8
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word8
Instance details

Defined in Basement.Nat

data Word16 Source #

16-bit unsigned integer type

Instances

Instances details
Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word16

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word16 -> c Word16 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word16 Source #

toConstr :: Word16 -> Constr Source #

dataTypeOf :: Word16 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word16 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word16 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word16 -> Word16 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word16 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word16 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word16 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word16 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word16 -> m Word16 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word16 -> m Word16 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word16 -> m Word16 Source #

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word16

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

FiniteBitsOps Word16
Instance details

Defined in Basement.Bits

BitOps Word16
Instance details

Defined in Basement.Bits

NormalForm Word16
Instance details

Defined in Basement.NormalForm

PrimType Word16
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word16
Instance details

Defined in Basement.PrimType

Multiplicative Word16
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word16
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word16
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word16
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word16
Instance details

Defined in Basement.Numerical.Number

IsNatural Word16
Instance details

Defined in Basement.Numerical.Number

ByteSwap Word16
Instance details

Defined in Basement.Endianness

Integral Word16
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word16
Instance details

Defined in Basement.Compat.NumLiteral

StorableFixed Word16 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word16 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word16 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word16 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word16 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word16 -> st -> st Source #

From Word8 Word16
Instance details

Defined in Basement.From

From Word16 Int
Instance details

Defined in Basement.From

From Word16 Int32
Instance details

Defined in Basement.From

From Word16 Int64
Instance details

Defined in Basement.From

From Word16 Word
Instance details

Defined in Basement.From

From Word16 Word32
Instance details

Defined in Basement.From

From Word16 Word64
Instance details

Defined in Basement.From

From Word16 Word256
Instance details

Defined in Basement.From

From Word16 Word128
Instance details

Defined in Basement.From

Cast Int16 Word16
Instance details

Defined in Basement.Cast

Cast Word16 Int16
Instance details

Defined in Basement.Cast

IntegralDownsize Integer Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word16 Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word32 Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word16
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word64
Instance details

Defined in Basement.IntegralConv

StorableFixed ( LE Word16 ) Source #
Instance details

Defined in Foundation.Class.Storable

StorableFixed ( BE Word16 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( LE Word16 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( BE Word16 ) Source #
Instance details

Defined in Foundation.Class.Storable

( KnownNat n, NatWithinBound Word16 n) => From ( Zn64 n) Word16
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word16 n) => From ( Zn n) Word16
Instance details

Defined in Basement.From

type PrimSize Word16
Instance details

Defined in Basement.PrimType

type Difference Word16
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word16
Instance details

Defined in Basement.Nat

data Word32 Source #

32-bit unsigned integer type

Instances

Instances details
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word32 -> c Word32 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word32 Source #

toConstr :: Word32 -> Constr Source #

dataTypeOf :: Word32 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word32 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word32 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word32 -> Word32 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word32 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word32 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word32 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word32 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word32 -> m Word32 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word32 -> m Word32 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word32 -> m Word32 Source #

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word32

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

FiniteBitsOps Word32
Instance details

Defined in Basement.Bits

BitOps Word32
Instance details

Defined in Basement.Bits

NormalForm Word32
Instance details

Defined in Basement.NormalForm

PrimType Word32
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word32
Instance details

Defined in Basement.PrimType

Multiplicative Word32
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word32
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word32
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word32
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word32
Instance details

Defined in Basement.Numerical.Number

IsNatural Word32
Instance details

Defined in Basement.Numerical.Number

ByteSwap Word32
Instance details

Defined in Basement.Endianness

Integral Word32
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word32
Instance details

Defined in Basement.Compat.NumLiteral

StorableFixed Word32 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word32 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word32 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word32 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word32 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word32 -> st -> st Source #

From Word8 Word32
Instance details

Defined in Basement.From

From Word16 Word32
Instance details

Defined in Basement.From

From Word32 Int
Instance details

Defined in Basement.From

From Word32 Int64
Instance details

Defined in Basement.From

From Word32 Word
Instance details

Defined in Basement.From

From Word32 Word64
Instance details

Defined in Basement.From

From Word32 Word256
Instance details

Defined in Basement.From

From Word32 Word128
Instance details

Defined in Basement.From

Cast Int32 Word32
Instance details

Defined in Basement.Cast

Cast Word32 Int32
Instance details

Defined in Basement.Cast

IntegralDownsize Integer Word32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word32 Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word32 Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word32 Word
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word32 Word64
Instance details

Defined in Basement.IntegralConv

StorableFixed ( LE Word32 ) Source #
Instance details

Defined in Foundation.Class.Storable

StorableFixed ( BE Word32 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( LE Word32 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( BE Word32 ) Source #
Instance details

Defined in Foundation.Class.Storable

( KnownNat n, NatWithinBound Word32 n) => From ( Zn64 n) Word32
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word32 n) => From ( Zn n) Word32
Instance details

Defined in Basement.From

type PrimSize Word32
Instance details

Defined in Basement.PrimType

type Difference Word32
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word32
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word32 = 4294967295

data Word64 Source #

64-bit unsigned integer type

Instances

Instances details
Bounded Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Integral Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word64

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word64 -> c Word64 Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word64 Source #

toConstr :: Word64 -> Constr Source #

dataTypeOf :: Word64 -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word64 ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word64 ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word64 -> Word64 Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word64 -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word64 -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word64 -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word64 -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word64 -> m Word64 Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word64 -> m Word64 Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word64 -> m Word64 Source #

Num Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word64

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word64

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word64

Since: base-2.1

Instance details

Defined in GHC.Word

PrintfArg Word64

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word64

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word64

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

FiniteBitsOps Word64
Instance details

Defined in Basement.Bits

BitOps Word64
Instance details

Defined in Basement.Bits

NormalForm Word64
Instance details

Defined in Basement.NormalForm

PrimType Word64
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word64
Instance details

Defined in Basement.PrimType

Multiplicative Word64
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word64
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word64
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word64
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word64
Instance details

Defined in Basement.Numerical.Number

IsNatural Word64
Instance details

Defined in Basement.Numerical.Number

ByteSwap Word64
Instance details

Defined in Basement.Endianness

Integral Word64
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word64
Instance details

Defined in Basement.Compat.NumLiteral

StorableFixed Word64 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word64 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word64 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word64 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word64 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word64 -> st -> st Source #

From Word Word64
Instance details

Defined in Basement.From

From Word8 Word64
Instance details

Defined in Basement.From

From Word16 Word64
Instance details

Defined in Basement.From

From Word32 Word64
Instance details

Defined in Basement.From

From Word64 Word256
Instance details

Defined in Basement.From

From Word64 Word128
Instance details

Defined in Basement.From

Cast Int Word64
Instance details

Defined in Basement.Cast

Cast Int64 Word64
Instance details

Defined in Basement.Cast

Cast Word Word64
Instance details

Defined in Basement.Cast

Cast Word64 Int
Instance details

Defined in Basement.Cast

Cast Word64 Int64
Instance details

Defined in Basement.Cast

Cast Word64 Word
Instance details

Defined in Basement.Cast

IntegralDownsize Integer Word64
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word64
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word64 Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word Word64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word32 Word64
Instance details

Defined in Basement.IntegralConv

StorableFixed ( LE Word64 ) Source #
Instance details

Defined in Foundation.Class.Storable

StorableFixed ( BE Word64 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( LE Word64 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( BE Word64 ) Source #
Instance details

Defined in Foundation.Class.Storable

From ( Zn64 n) Word64
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word64 n) => From ( Zn n) Word64
Instance details

Defined in Basement.From

type PrimSize Word64
Instance details

Defined in Basement.PrimType

type Difference Word64
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word64
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word64 = 18446744073709551615

data Word Source #

A Word is an unsigned integral type, with the same size as Int .

Instances

Instances details
Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Word
Instance details

Defined in GHC.Classes

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Data Word

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Word -> c Word Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Word Source #

toConstr :: Word -> Constr Source #

dataTypeOf :: Word -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Word ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Word ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Word -> Word Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Word -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Word -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Word -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Word -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Word -> m Word Source #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Word
Instance details

Defined in GHC.Classes

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Ix

PrintfArg Word

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word

Since: base-2.1

Instance details

Defined in Data.Bits

FiniteBits Word

Since: base-4.6.0.0

Instance details

Defined in Data.Bits

FiniteBitsOps Word
Instance details

Defined in Basement.Bits

BitOps Word
Instance details

Defined in Basement.Bits

NormalForm Word
Instance details

Defined in Basement.NormalForm

PrimType Word
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word
Instance details

Defined in Basement.PrimType

Multiplicative Word
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word
Instance details

Defined in Basement.Numerical.Number

IsNatural Word
Instance details

Defined in Basement.Numerical.Number

Integral Word
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Word
Instance details

Defined in Basement.Compat.NumLiteral

Arbitrary Word Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word Source #
Instance details

Defined in Foundation.Format.CSV.Types

From Word Word64
Instance details

Defined in Basement.From

From Word8 Word
Instance details

Defined in Basement.From

From Word16 Word
Instance details

Defined in Basement.From

From Word32 Word
Instance details

Defined in Basement.From

Cast Int Word
Instance details

Defined in Basement.Cast

Cast Int64 Word
Instance details

Defined in Basement.Cast

Cast Word Int
Instance details

Defined in Basement.Cast

Cast Word Int64
Instance details

Defined in Basement.Cast

Cast Word Word64
Instance details

Defined in Basement.Cast

Cast Word64 Word
Instance details

Defined in Basement.Cast

IntegralDownsize Word Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Word Word32
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word Word64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Word
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word16 Word
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word32 Word
Instance details

Defined in Basement.IntegralConv

From Word ( Offset ty)
Instance details

Defined in Basement.From

From Word ( CountOf ty)
Instance details

Defined in Basement.From

Generic1 ( URec Word :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Word ) :: k -> Type Source #

Foldable ( UWord :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UWord :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

From ( CountOf ty) Word
Instance details

Defined in Basement.From

Functor ( URec Word :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic ( URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( URec Word p) :: Type -> Type Source #

type PrimSize Word
Instance details

Defined in Basement.PrimType

type Difference Word
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word
Instance details

Defined in Basement.Nat

data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Word :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Word p)
Instance details

Defined in GHC.Generics

data Word128 Source #

128 bits Word

Instances

Instances details
Bounded Word128
Instance details

Defined in Basement.Types.Word128

Enum Word128
Instance details

Defined in Basement.Types.Word128

Eq Word128
Instance details

Defined in Basement.Types.Word128

Num Word128
Instance details

Defined in Basement.Types.Word128

Ord Word128
Instance details

Defined in Basement.Types.Word128

Show Word128
Instance details

Defined in Basement.Types.Word128

Storable Word128
Instance details

Defined in Basement.Types.Word128

Bits Word128
Instance details

Defined in Basement.Types.Word128

FiniteBitsOps Word128
Instance details

Defined in Basement.Bits

BitOps Word128
Instance details

Defined in Basement.Bits

NormalForm Word128
Instance details

Defined in Basement.NormalForm

PrimType Word128
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word128
Instance details

Defined in Basement.PrimType

Multiplicative Word128
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word128
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word128
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word128
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word128
Instance details

Defined in Basement.Types.Word128

IsNatural Word128
Instance details

Defined in Basement.Types.Word128

Integral Word128
Instance details

Defined in Basement.Types.Word128

HasNegation Word128
Instance details

Defined in Basement.Types.Word128

StorableFixed Word128 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word128 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word128 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word128 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word128 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word128 -> st -> st Source #

From Word8 Word128
Instance details

Defined in Basement.From

From Word16 Word128
Instance details

Defined in Basement.From

From Word32 Word128
Instance details

Defined in Basement.From

From Word64 Word128
Instance details

Defined in Basement.From

From Word128 Word256
Instance details

Defined in Basement.From

StorableFixed ( LE Word128 ) Source #
Instance details

Defined in Foundation.Class.Storable

StorableFixed ( BE Word128 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( LE Word128 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( BE Word128 ) Source #
Instance details

Defined in Foundation.Class.Storable

From ( Zn64 n) Word128
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word128 n) => From ( Zn n) Word128
Instance details

Defined in Basement.From

type PrimSize Word128
Instance details

Defined in Basement.PrimType

type Difference Word128
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word128
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word128 = 340282366920938463463374607431768211455

data Word256 Source #

256 bits Word

Instances

Instances details
Bounded Word256
Instance details

Defined in Basement.Types.Word256

Enum Word256
Instance details

Defined in Basement.Types.Word256

Eq Word256
Instance details

Defined in Basement.Types.Word256

Num Word256
Instance details

Defined in Basement.Types.Word256

Ord Word256
Instance details

Defined in Basement.Types.Word256

Show Word256
Instance details

Defined in Basement.Types.Word256

Storable Word256
Instance details

Defined in Basement.Types.Word256

Bits Word256
Instance details

Defined in Basement.Types.Word256

FiniteBitsOps Word256
Instance details

Defined in Basement.Bits

BitOps Word256
Instance details

Defined in Basement.Bits

NormalForm Word256
Instance details

Defined in Basement.NormalForm

PrimType Word256
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word256
Instance details

Defined in Basement.PrimType

Multiplicative Word256
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Word256
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Word256
Instance details

Defined in Basement.Numerical.Additive

Subtractive Word256
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Word256
Instance details

Defined in Basement.Types.Word256

IsNatural Word256
Instance details

Defined in Basement.Types.Word256

Integral Word256
Instance details

Defined in Basement.Types.Word256

HasNegation Word256
Instance details

Defined in Basement.Types.Word256

StorableFixed Word256 Source #
Instance details

Defined in Foundation.Class.Storable

Storable Word256 Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Word256 Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Word256 Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Word256 Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Word256 -> st -> st Source #

From Word8 Word256
Instance details

Defined in Basement.From

From Word16 Word256
Instance details

Defined in Basement.From

From Word32 Word256
Instance details

Defined in Basement.From

From Word64 Word256
Instance details

Defined in Basement.From

From Word128 Word256
Instance details

Defined in Basement.From

StorableFixed ( LE Word256 ) Source #
Instance details

Defined in Foundation.Class.Storable

StorableFixed ( BE Word256 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( LE Word256 ) Source #
Instance details

Defined in Foundation.Class.Storable

Storable ( BE Word256 ) Source #
Instance details

Defined in Foundation.Class.Storable

From ( Zn64 n) Word256
Instance details

Defined in Basement.From

( KnownNat n, NatWithinBound Word256 n) => From ( Zn n) Word256
Instance details

Defined in Basement.From

type PrimSize Word256
Instance details

Defined in Basement.PrimType

type Difference Word256
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Word256
Instance details

Defined in Basement.Nat

type NatNumMaxBound Word256 = 115792089237316195423570985008687907853269984665640564039457584007913129639935

data Int Source #

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.

Instances

Instances details
Bounded Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Int

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Int
Instance details

Defined in GHC.Classes

Integral Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Data Int

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Int -> c Int Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Int Source #

toConstr :: Int -> Constr Source #

dataTypeOf :: Int -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Int ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Int ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Int -> Int Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Int -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Int -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Int -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Int -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Int -> m Int Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int -> m Int Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Int -> m Int Source #

Num Int

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Int
Instance details

Defined in GHC.Classes

Read Int

Since: base-2.1

Instance details

Defined in GHC.Read

Real Int

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Int

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Int

Since: base-2.1

Instance details

Defined in GHC.Ix

PrintfArg Int

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Int

Since: base-2.1

Instance details

Defined in Data.Bits

FiniteBits Int

Since: base-4.6.0.0

Instance details

Defined in Data.Bits

NormalForm Int
Instance details

Defined in Basement.NormalForm

PrimType Int
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int :: Nat Source #

PrimMemoryComparable Int
Instance details

Defined in Basement.PrimType

Multiplicative Int
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Int
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Int
Instance details

Defined in Basement.Numerical.Additive

Subtractive Int
Instance details

Defined in Basement.Numerical.Subtractive

Associated Types

type Difference Int Source #

IsIntegral Int
Instance details

Defined in Basement.Numerical.Number

Integral Int
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Int
Instance details

Defined in Basement.Compat.NumLiteral

Signed Int Source #
Instance details

Defined in Foundation.Numerical

Arbitrary Int Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Int Source #
Instance details

Defined in Foundation.Format.CSV.Types

From Int Int64
Instance details

Defined in Basement.From

From Int8 Int
Instance details

Defined in Basement.From

From Int16 Int
Instance details

Defined in Basement.From

From Int32 Int
Instance details

Defined in Basement.From

From Word8 Int
Instance details

Defined in Basement.From

From Word16 Int
Instance details

Defined in Basement.From

From Word32 Int
Instance details

Defined in Basement.From

Cast Int Int64
Instance details

Defined in Basement.Cast

Cast Int Word
Instance details

Defined in Basement.Cast

Cast Int Word64
Instance details

Defined in Basement.Cast

Cast Int64 Int
Instance details

Defined in Basement.Cast

Cast Word Int
Instance details

Defined in Basement.Cast

Cast Word64 Int
Instance details

Defined in Basement.Cast

IntegralDownsize Int Int8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int Int16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int Int32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Int64 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int Int64
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int8 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int16 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Int32 Int
Instance details

Defined in Basement.IntegralConv

IntegralUpsize Word8 Int
Instance details

Defined in Basement.IntegralConv

TryFrom Int ( Offset ty)
Instance details

Defined in Basement.From

TryFrom Int ( CountOf ty)
Instance details

Defined in Basement.From

Generic1 ( URec Int :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Int ) :: k -> Type Source #

Foldable ( UInt :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UInt :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

From ( CountOf ty) Int
Instance details

Defined in Basement.From

Functor ( URec Int :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic ( URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( URec Int p) :: Type -> Type Source #

type PrimSize Int
Instance details

Defined in Basement.PrimType

type Difference Int
Instance details

Defined in Basement.Numerical.Subtractive

type NatNumMaxBound Int
Instance details

Defined in Basement.Nat

data URec Int (p :: k)

Used for marking occurrences of Int#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Int :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Int p)
Instance details

Defined in GHC.Generics

data Integer Source #

Arbitrary precision integers. In contrast with fixed-size integral types such as Int , the Integer type represents the entire infinite range of integers.

For more information about this type's representation, see the comments in its implementation.

Instances

Instances details
Enum Integer

Since: base-2.1

Instance details

Defined in GHC.Enum

Eq Integer
Instance details

Defined in GHC.Integer.Type

Integral Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Data Integer

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Integer -> c Integer Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Integer Source #

toConstr :: Integer -> Constr Source #

dataTypeOf :: Integer -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Integer ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Integer ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Integer -> Integer Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Integer -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Integer -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Integer -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Integer -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Integer -> m Integer Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Integer -> m Integer Source #

Num Integer

Since: base-2.1

Instance details

Defined in GHC.Num

Ord Integer
Instance details

Defined in GHC.Integer.Type

Read Integer

Since: base-2.1

Instance details

Defined in GHC.Read

Real Integer

Since: base-2.0.1

Instance details

Defined in GHC.Real

Show Integer

Since: base-2.1

Instance details

Defined in GHC.Show

Ix Integer

Since: base-2.1

Instance details

Defined in GHC.Ix

PrintfArg Integer

Since: base-2.1

Instance details

Defined in Text.Printf

Bits Integer

Since: base-2.1

Instance details

Defined in Data.Bits

NormalForm Integer
Instance details

Defined in Basement.NormalForm

Multiplicative Integer
Instance details

Defined in Basement.Numerical.Multiplicative

Multiplicative Rational
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Integer
Instance details

Defined in Basement.Numerical.Multiplicative

Divisible Rational
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Integer
Instance details

Defined in Basement.Numerical.Additive

Additive Rational
Instance details

Defined in Basement.Numerical.Additive

Subtractive Integer
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Integer
Instance details

Defined in Basement.Numerical.Number

Integral Integer
Instance details

Defined in Basement.Compat.NumLiteral

Fractional Rational
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Integer
Instance details

Defined in Basement.Compat.NumLiteral

IntegralRounding Rational Source #
Instance details

Defined in Foundation.Numerical

Signed Integer Source #
Instance details

Defined in Foundation.Numerical

Arbitrary Integer Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Integer Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Integer Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Integer -> st -> st Source #

IsIntegral n => From n Integer
Instance details

Defined in Basement.From

IntegralDownsize Integer Int8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Int64
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Natural
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Word32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Integer Word64
Instance details

Defined in Basement.IntegralConv

IsIntegral a => IntegralUpsize a Integer
Instance details

Defined in Basement.IntegralConv

type Difference Integer
Instance details

Defined in Basement.Numerical.Subtractive

data Natural Source #

Type representing arbitrary-precision non-negative integers.

>>> 2^100 :: Natural
1267650600228229401496703205376

Operations whose result would be negative throw ( Underflow :: ArithException ) ,

>>> -1 :: Natural
*** Exception: arithmetic underflow

Since: base-4.8.0.0

Instances

Instances details
Enum Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Enum

Eq Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Integral Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Data Natural

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Natural -> c Natural Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Natural Source #

toConstr :: Natural -> Constr Source #

dataTypeOf :: Natural -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Natural ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Natural ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Natural -> Natural Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Natural -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Natural -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Natural -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Natural -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Natural -> m Natural Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Natural -> m Natural Source #

Num Natural

Note that Natural 's Num instance isn't a ring: no element but 0 has an additive inverse. It is a semiring though.

Since: base-4.8.0.0

Instance details

Defined in GHC.Num

Ord Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Natural

Read Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Read

Real Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Real

Show Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Show

Ix Natural

Since: base-4.8.0.0

Instance details

Defined in GHC.Ix

PrintfArg Natural

Since: base-4.8.0.0

Instance details

Defined in Text.Printf

Bits Natural

Since: base-4.8.0

Instance details

Defined in Data.Bits

NormalForm Natural
Instance details

Defined in Basement.NormalForm

Multiplicative Natural
Instance details

Defined in Basement.Numerical.Multiplicative

IDivisible Natural
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Natural
Instance details

Defined in Basement.Numerical.Additive

Subtractive Natural
Instance details

Defined in Basement.Numerical.Subtractive

IsIntegral Natural
Instance details

Defined in Basement.Numerical.Number

IsNatural Natural
Instance details

Defined in Basement.Numerical.Number

Integral Natural
Instance details

Defined in Basement.Compat.NumLiteral

Arbitrary Natural Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Natural Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable Natural Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Natural -> st -> st Source #

IsNatural n => From n Natural
Instance details

Defined in Basement.From

IntegralDownsize Integer Natural
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word8
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word16
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word32
Instance details

Defined in Basement.IntegralConv

IntegralDownsize Natural Word64
Instance details

Defined in Basement.IntegralConv

IsNatural a => IntegralUpsize a Natural
Instance details

Defined in Basement.IntegralConv

type Difference Natural
Instance details

Defined in Basement.Numerical.Subtractive

type Rational = Ratio Integer Source #

Arbitrary-precision rational numbers, represented as a ratio of two Integer values. A rational number may be constructed using the % operator.

data Float Source #

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.

Instances

Instances details
Eq Float

Note that due to the presence of NaN , Float 's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Float)
False

Also note that Float 's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Float)
True
>>> recip 0 == recip (-0 :: Float)
False
Instance details

Defined in GHC.Classes

Floating Float

Since: base-2.1

Instance details

Defined in GHC.Float

Data Float

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Float -> c Float Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Float Source #

toConstr :: Float -> Constr Source #

dataTypeOf :: Float -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Float ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Float ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Float -> Float Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Float -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Float -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Float -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Float -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Float -> m Float Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Float -> m Float Source #

Ord Float

Note that due to the presence of NaN , Float 's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Float)
False

Also note that, due to the same, Ord 's operator interactions are not respected by Float 's instance:

>>> (0/0 :: Float) > 1
False
>>> compare (0/0 :: Float) 1
GT
Instance details

Defined in GHC.Classes

Read Float

Since: base-2.1

Instance details

Defined in GHC.Read

RealFloat Float

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Float

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

NormalForm Float
Instance details

Defined in Basement.NormalForm

PrimType Float
Instance details

Defined in Basement.PrimType

Multiplicative Float
Instance details

Defined in Basement.Numerical.Multiplicative

Divisible Float
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Float
Instance details

Defined in Basement.Numerical.Additive

Subtractive Float
Instance details

Defined in Basement.Numerical.Subtractive

Integral Float
Instance details

Defined in Basement.Compat.NumLiteral

Fractional Float
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Float
Instance details

Defined in Basement.Compat.NumLiteral

Trigonometry Float Source #
Instance details

Defined in Foundation.Math.Trigonometry

FloatingPoint Float Source #
Instance details

Defined in Foundation.Numerical.Floating

IntegralRounding Float Source #
Instance details

Defined in Foundation.Numerical

Signed Float Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Float Source #
Instance details

Defined in Foundation.Class.Storable

Storable Float Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Float Source #
Instance details

Defined in Foundation.Check.Arbitrary

Generic1 ( URec Float :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Float ) :: k -> Type Source #

Foldable ( UFloat :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UFloat :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Functor ( URec Float :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Float p)
Instance details

Defined in GHC.Generics

Ord ( URec Float p)
Instance details

Defined in GHC.Generics

Show ( URec Float p)
Instance details

Defined in GHC.Generics

Generic ( URec Float p)
Instance details

Defined in GHC.Generics

type PrimSize Float
Instance details

Defined in Basement.PrimType

type Difference Float
Instance details

Defined in Basement.Numerical.Subtractive

data URec Float (p :: k)

Used for marking occurrences of Float#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Float :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Float p)
Instance details

Defined in GHC.Generics

data Double Source #

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.

Instances

Instances details
Eq Double

Note that due to the presence of NaN , Double 's Eq instance does not satisfy reflexivity.

>>> 0/0 == (0/0 :: Double)
False

Also note that Double 's Eq instance does not satisfy substitutivity:

>>> 0 == (-0 :: Double)
True
>>> recip 0 == recip (-0 :: Double)
False
Instance details

Defined in GHC.Classes

Floating Double

Since: base-2.1

Instance details

Defined in GHC.Float

Data Double

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Double -> c Double Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Double Source #

toConstr :: Double -> Constr Source #

dataTypeOf :: Double -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Double ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Double ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Double -> Double Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Double -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Double -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Double -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Double -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Double -> m Double Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Double -> m Double Source #

Ord Double

Note that due to the presence of NaN , Double 's Ord instance does not satisfy reflexivity.

>>> 0/0 <= (0/0 :: Double)
False

Also note that, due to the same, Ord 's operator interactions are not respected by Double 's instance:

>>> (0/0 :: Double) > 1
False
>>> compare (0/0 :: Double) 1
GT
Instance details

Defined in GHC.Classes

Read Double

Since: base-2.1

Instance details

Defined in GHC.Read

RealFloat Double

Since: base-2.1

Instance details

Defined in GHC.Float

PrintfArg Double

Since: base-2.1

Instance details

Defined in Text.Printf

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

NormalForm Double
Instance details

Defined in Basement.NormalForm

PrimType Double
Instance details

Defined in Basement.PrimType

Multiplicative Double
Instance details

Defined in Basement.Numerical.Multiplicative

Divisible Double
Instance details

Defined in Basement.Numerical.Multiplicative

Additive Double
Instance details

Defined in Basement.Numerical.Additive

Subtractive Double
Instance details

Defined in Basement.Numerical.Subtractive

Integral Double
Instance details

Defined in Basement.Compat.NumLiteral

Fractional Double
Instance details

Defined in Basement.Compat.NumLiteral

HasNegation Double
Instance details

Defined in Basement.Compat.NumLiteral

Trigonometry Double Source #
Instance details

Defined in Foundation.Math.Trigonometry

FloatingPoint Double Source #
Instance details

Defined in Foundation.Numerical.Floating

IntegralRounding Double Source #
Instance details

Defined in Foundation.Numerical

Signed Double Source #
Instance details

Defined in Foundation.Numerical

StorableFixed Double Source #
Instance details

Defined in Foundation.Class.Storable

Storable Double Source #
Instance details

Defined in Foundation.Class.Storable

Arbitrary Double Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField Double Source #
Instance details

Defined in Foundation.Format.CSV.Types

Generic1 ( URec Double :: k -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 ( URec Double ) :: k -> Type Source #

Foldable ( UDouble :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Traversable ( UDouble :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Functor ( URec Double :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Eq ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Ord ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Show ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Generic ( URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type PrimSize Double
Instance details

Defined in Basement.PrimType

type Difference Double
Instance details

Defined in Basement.Numerical.Subtractive

data URec Double (p :: k)

Used for marking occurrences of Double#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 ( URec Double :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep ( URec Double p)
Instance details

Defined in GHC.Generics

newtype CountOf ty Source #

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.

Constructors

CountOf Int

Instances

Instances details
From Word ( CountOf ty)
Instance details

Defined in Basement.From

TryFrom Int ( CountOf ty)
Instance details

Defined in Basement.From

Enum ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Eq ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Num ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Ord ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Show ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Semigroup ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Monoid ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

NormalForm ( CountOf a)
Instance details

Defined in Basement.NormalForm

Additive ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Subtractive ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference ( CountOf ty) Source #

IsIntegral ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

IsNatural ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Integral ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Arbitrary ( CountOf ty) Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField ( CountOf a) Source #
Instance details

Defined in Foundation.Format.CSV.Types

From ( CountOf ty) Word
Instance details

Defined in Basement.From

From ( CountOf ty) Int
Instance details

Defined in Basement.From

type Difference ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

type NatNumMaxBound ( CountOf x)
Instance details

Defined in Basement.Types.OffsetSize

newtype Offset ty Source #

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.

Constructors

Offset Int

Instances

Instances details
From Word ( Offset ty)
Instance details

Defined in Basement.From

TryFrom Int ( Offset ty)
Instance details

Defined in Basement.From

Enum ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Eq ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Num ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Ord ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Show ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

NormalForm ( Offset a)
Instance details

Defined in Basement.NormalForm

Additive ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Subtractive ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Associated Types

type Difference ( Offset ty) Source #

IsIntegral ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

IsNatural ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

Integral ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

IsField ( Offset a) Source #
Instance details

Defined in Foundation.Format.CSV.Types

type Difference ( Offset ty)
Instance details

Defined in Basement.Types.OffsetSize

type NatNumMaxBound ( Offset x)
Instance details

Defined in Basement.Types.OffsetSize

Collection types

data UArray ty Source #

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

Instances

Instances details
From String ( UArray Word8 )
Instance details

Defined in Basement.From

From AsciiString ( UArray Word8 )
Instance details

Defined in Basement.From

PrimType ty => IsList ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Associated Types

type Item ( UArray ty) Source #

( PrimType ty, Eq ty) => Eq ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Data ty => Data ( UArray ty)
Instance details

Defined in Basement.UArray.Base

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> UArray ty -> c ( UArray ty) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( UArray ty) Source #

toConstr :: UArray ty -> Constr Source #

dataTypeOf :: UArray ty -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( UArray ty)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( UArray ty)) Source #

gmapT :: ( forall b. Data b => b -> b) -> UArray ty -> UArray ty Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> UArray ty -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> UArray ty -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> UArray ty -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> UArray ty -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> UArray ty -> m ( UArray ty) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> UArray ty -> m ( UArray ty) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> UArray ty -> m ( UArray ty) Source #

( PrimType ty, Ord ty) => Ord ( UArray ty)
Instance details

Defined in Basement.UArray.Base

( PrimType ty, Show ty) => Show ( UArray ty)
Instance details

Defined in Basement.UArray.Base

PrimType ty => Semigroup ( UArray ty)
Instance details

Defined in Basement.UArray.Base

PrimType ty => Monoid ( UArray ty)
Instance details

Defined in Basement.UArray.Base

NormalForm ( UArray ty)
Instance details

Defined in Basement.UArray.Base

PrimType ty => Copy ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Copy

PrimType ty => Collection ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Collection

PrimType ty => Buildable ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

PrimType ty => Fold1able ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

PrimType ty => Foldable ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: ( Element ( UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: ( Element ( UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => IndexedCollection ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Indexed

PrimType ty => InnerFunctor ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.InnerFunctor

PrimType ty => Sequential ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf ( Element ( UArray ty)) -> UArray ty -> ( UArray ty, UArray ty) Source #

revSplitAt :: CountOf ( Element ( UArray ty)) -> UArray ty -> ( UArray ty, UArray ty) Source #

splitOn :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> [ UArray ty] Source #

break :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

breakEnd :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

breakElem :: Element ( UArray ty) -> UArray ty -> ( UArray ty, UArray ty) Source #

takeWhile :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

dropWhile :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

intersperse :: Element ( UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element ( UArray ty) -> UArray ty -> Element ( UArray ty) Source #

span :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

spanEnd :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

filter :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

partition :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe ( Element ( UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe ( UArray ty, Element ( UArray ty)) Source #

snoc :: UArray ty -> Element ( UArray ty) -> UArray ty Source #

cons :: Element ( UArray ty) -> UArray ty -> UArray ty Source #

find :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> Maybe ( Element ( UArray ty)) Source #

sortBy :: ( Element ( UArray ty) -> Element ( UArray ty) -> Ordering ) -> UArray ty -> UArray ty Source #

singleton :: Element ( UArray ty) -> UArray ty Source #

head :: NonEmpty ( UArray ty) -> Element ( UArray ty) Source #

last :: NonEmpty ( UArray ty) -> Element ( UArray ty) Source #

tail :: NonEmpty ( UArray ty) -> UArray ty Source #

init :: NonEmpty ( UArray ty) -> UArray ty Source #

replicate :: CountOf ( Element ( UArray ty)) -> Element ( UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

stripPrefix :: UArray ty -> UArray ty -> Maybe ( UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe ( UArray ty) Source #

PrimType ty => Zippable ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Zippable

PrimType a => Hashable ( UArray a) Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => UArray a -> st -> st Source #

TryFrom ( UArray Word8 ) String
Instance details

Defined in Basement.From

PrimType ty => From ( Array ty) ( UArray ty)
Instance details

Defined in Basement.From

PrimType ty => From ( UArray ty) ( Block ty)
Instance details

Defined in Basement.From

PrimType ty => From ( UArray ty) ( Array ty)
Instance details

Defined in Basement.From

PrimType ty => From ( Block ty) ( UArray ty)
Instance details

Defined in Basement.From

( NatWithinBound ( CountOf ty) n, KnownNat n, PrimType ty) => TryFrom ( UArray ty) ( BlockN n ty)
Instance details

Defined in Basement.From

( NatWithinBound Int n, PrimType ty) => From ( BlockN n ty) ( UArray ty)
Instance details

Defined in Basement.From

type Item ( UArray ty)
Instance details

Defined in Basement.UArray.Base

type Item ( UArray ty) = ty
type Element ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Element

type Element ( UArray ty) = ty
type Mutable ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step ( UArray ty) = ty

class Eq ty => PrimType ty Source #

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.

Instances

Instances details
PrimType Char
Instance details

Defined in Basement.PrimType

PrimType Double
Instance details

Defined in Basement.PrimType

PrimType Float
Instance details

Defined in Basement.PrimType

PrimType Int
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int :: Nat Source #

PrimType Int8
Instance details

Defined in Basement.PrimType

PrimType Int16
Instance details

Defined in Basement.PrimType

PrimType Int32
Instance details

Defined in Basement.PrimType

PrimType Int64
Instance details

Defined in Basement.PrimType

PrimType Word
Instance details

Defined in Basement.PrimType

PrimType Word8
Instance details

Defined in Basement.PrimType

PrimType Word16
Instance details

Defined in Basement.PrimType

PrimType Word32
Instance details

Defined in Basement.PrimType

PrimType Word64
Instance details

Defined in Basement.PrimType

PrimType CChar
Instance details

Defined in Basement.PrimType

PrimType CUChar
Instance details

Defined in Basement.PrimType

PrimType Word256
Instance details

Defined in Basement.PrimType

PrimType Word128
Instance details

Defined in Basement.PrimType

PrimType Char7
Instance details

Defined in Basement.PrimType

PrimType Seconds Source #
Instance details

Defined in Foundation.Time.Types

PrimType NanoSeconds Source #
Instance details

Defined in Foundation.Time.Types

PrimType a => PrimType ( LE a)
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize ( LE a) :: Nat Source #

PrimType a => PrimType ( BE a)
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize ( BE a) :: Nat Source #

data Array a Source #

Array of a

Instances

Instances details
Functor Array
Instance details

Defined in Basement.BoxedArray

Mappable Array Source #
Instance details

Defined in Foundation.Collection.Mappable

IsList ( Array ty)
Instance details

Defined in Basement.BoxedArray

Associated Types

type Item ( Array ty) Source #

Eq a => Eq ( Array a)
Instance details

Defined in Basement.BoxedArray

Data ty => Data ( Array ty)
Instance details

Defined in Basement.BoxedArray

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Array ty -> c ( Array ty) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Array ty) Source #

toConstr :: Array ty -> Constr Source #

dataTypeOf :: Array ty -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c ( Array ty)) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c ( Array ty)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Array ty -> Array ty Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Array ty -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Array ty -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Array ty -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Array ty -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Array ty -> m ( Array ty) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Array ty -> m ( Array ty) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Array ty -> m ( Array ty) Source #

Ord a => Ord ( Array a)
Instance details

Defined in Basement.BoxedArray

Show a => Show ( Array a)
Instance details

Defined in Basement.BoxedArray

Semigroup ( Array a)
Instance details

Defined in Basement.BoxedArray

Monoid ( Array a)
Instance details

Defined in Basement.BoxedArray

NormalForm a => NormalForm ( Array a)
Instance details

Defined in Basement.BoxedArray

Copy ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Copy

Collection ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Collection

Buildable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

Methods

append :: forall (prim :: Type -> Type ) err. PrimMonad prim => Element ( Array ty) -> Builder ( Array ty) ( Mutable ( Array ty)) ( Step ( Array ty)) prim err () Source #

build :: PrimMonad prim => Int -> Builder ( Array ty) ( Mutable ( Array ty)) ( Step ( Array ty)) prim err () -> prim ( Either err ( Array ty)) Source #

Fold1able ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Foldable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: ( Element ( Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: ( Element ( Array ty) -> a -> a) -> a -> Array ty -> a Source #

IndexedCollection ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Indexed

InnerFunctor ( Array ty) Source #
Instance details

Defined in Foundation.Collection.InnerFunctor

Sequential ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf ( Element ( Array ty)) -> Array ty -> ( Array ty, Array ty) Source #

revSplitAt :: CountOf ( Element ( Array ty)) -> Array ty -> ( Array ty, Array ty) Source #

splitOn :: ( Element ( Array ty) -> Bool ) -> Array ty -> [ Array ty] Source #

break :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

breakEnd :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

breakElem :: Element ( Array ty) -> Array ty -> ( Array ty, Array ty) Source #

takeWhile :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

dropWhile :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

intersperse :: Element ( Array ty) -> Array ty -> Array ty Source #

intercalate :: Element ( Array ty) -> Array ty -> Element ( Array ty) Source #

span :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

spanEnd :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

filter :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

partition :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe ( Element ( Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe ( Array ty, Element ( Array ty)) Source #

snoc :: Array ty -> Element ( Array ty) -> Array ty Source #

cons :: Element ( Array ty) -> Array ty -> Array ty Source #

find :: ( Element ( Array ty) -> Bool ) -> Array ty -> Maybe ( Element ( Array ty)) Source #

sortBy :: ( Element ( Array ty) -> Element ( Array ty) -> Ordering ) -> Array ty -> Array ty Source #

singleton :: Element ( Array ty) -> Array ty Source #

head :: NonEmpty ( Array ty) -> Element ( Array ty) Source #

last :: NonEmpty ( Array ty) -> Element ( Array ty) Source #

tail :: NonEmpty ( Array ty) -> Array ty Source #

init :: NonEmpty ( Array ty) -> Array ty Source #

replicate :: CountOf ( Element ( Array ty)) -> Element ( Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

isInfixOf :: Array ty -> Array ty -> Bool Source #

stripPrefix :: Array ty -> Array ty -> Maybe ( Array ty) Source #

stripSuffix :: Array ty -> Array ty -> Maybe ( Array ty) Source #

BoxedZippable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Zippable

Methods

zip :: ( Sequential a, Sequential b, Element ( Array ty) ~ ( Element a, Element b)) => a -> b -> Array ty Source #

zip3 :: ( Sequential a, Sequential b, Sequential c, Element ( Array ty) ~ ( Element a, Element b, Element c)) => a -> b -> c -> Array ty Source #

zip4 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> Array ty Source #

zip5 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> Array ty Source #

zip6 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> Array ty Source #

zip7 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> Array ty Source #

unzip :: ( Sequential a, Sequential b, Element ( Array ty) ~ ( Element a, Element b)) => Array ty -> (a, b) Source #

unzip3 :: ( Sequential a, Sequential b, Sequential c, Element ( Array ty) ~ ( Element a, Element b, Element c)) => Array ty -> (a, b, c) Source #

unzip4 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d)) => Array ty -> (a, b, c, d) Source #

unzip5 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e)) => Array ty -> (a, b, c, d, e) Source #

unzip6 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e, Element f)) => Array ty -> (a, b, c, d, e, f) Source #

unzip7 :: ( Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element ( Array ty) ~ ( Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => Array ty -> (a, b, c, d, e, f, g) Source #

Zippable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Zippable

Hashable a => Hashable ( Array a) Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => Array a -> st -> st Source #

PrimType ty => From ( Array ty) ( UArray ty)
Instance details

Defined in Basement.From

PrimType ty => From ( Array ty) ( Block ty)
Instance details

Defined in Basement.From

PrimType ty => From ( UArray ty) ( Array ty)
Instance details

Defined in Basement.From

( NatWithinBound ( CountOf ty) n, KnownNat n, PrimType ty) => TryFrom ( Array ty) ( BlockN n ty)
Instance details

Defined in Basement.From

( NatWithinBound Int n, PrimType ty) => From ( BlockN n ty) ( Array ty)
Instance details

Defined in Basement.From

type Item ( Array ty)
Instance details

Defined in Basement.BoxedArray

type Item ( Array ty) = ty
type Element ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Element

type Element ( Array ty) = ty
type Mutable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step ( Array ty) = ty

data String Source #

Opaque packed array of characters in the UTF8 encoding

Instances

Instances details
IsList String
Instance details

Defined in Basement.UTF8.Base

Associated Types

type Item String Source #

Eq String
Instance details

Defined in Basement.UTF8.Base

Data String
Instance details

Defined in Basement.UTF8.Base

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> String -> c String Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c String Source #

toConstr :: String -> Constr Source #

dataTypeOf :: String -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c String ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c String ) Source #

gmapT :: ( forall b. Data b => b -> b) -> String -> String Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> String -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> String -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> String -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> String -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> String -> m String Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> String -> m String Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> String -> m String Source #

Ord String
Instance details

Defined in Basement.UTF8.Base

Show String
Instance details

Defined in Basement.UTF8.Base

IsString String
Instance details

Defined in Basement.UTF8.Base

Semigroup String
Instance details

Defined in Basement.UTF8.Base

Monoid String
Instance details

Defined in Basement.UTF8.Base

NormalForm String
Instance details

Defined in Basement.UTF8.Base

Copy String Source #
Instance details

Defined in Foundation.Collection.Copy

Collection String Source #
Instance details

Defined in Foundation.Collection.Collection

Buildable String Source #
Instance details

Defined in Foundation.Collection.Buildable

IndexedCollection String Source #
Instance details

Defined in Foundation.Collection.Indexed

InnerFunctor String Source #
Instance details

Defined in Foundation.Collection.InnerFunctor

Sequential String Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element String ) -> String -> String Source #

revTake :: CountOf ( Element String ) -> String -> String Source #

drop :: CountOf ( Element String ) -> String -> String Source #

revDrop :: CountOf ( Element String ) -> String -> String Source #

splitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

revSplitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

splitOn :: ( Element String -> Bool ) -> String -> [ String ] Source #

break :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakElem :: Element String -> String -> ( String , String ) Source #

takeWhile :: ( Element String -> Bool ) -> String -> String Source #

dropWhile :: ( Element String -> Bool ) -> String -> String Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

spanEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

filter :: ( Element String -> Bool ) -> String -> String Source #

partition :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe ( Element String , String ) Source #

unsnoc :: String -> Maybe ( String , Element String ) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: ( Element String -> Bool ) -> String -> Maybe ( Element String ) Source #

sortBy :: ( Element String -> Element String -> Ordering ) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

replicate :: CountOf ( Element String ) -> Element String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Zippable String Source #
Instance details

Defined in Foundation.Collection.Zippable

ParserSource String Source #
Instance details

Defined in Foundation.Parser

Associated Types

type Chunk String Source #

Arbitrary String Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField String Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable String Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => String -> st -> st Source #

From AsciiString String
Instance details

Defined in Basement.From

From String ( UArray Word8 )
Instance details

Defined in Basement.From

Show ( ParseError String ) Source #
Instance details

Defined in Foundation.Parser

TryFrom ( UArray Word8 ) String
Instance details

Defined in Basement.From

IsProperty ( String , Bool ) Source #
Instance details

Defined in Foundation.Check.Property

type Item String
Instance details

Defined in Basement.UTF8.Base

type Element String Source #
Instance details

Defined in Foundation.Collection.Element

type Mutable String Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step String Source #
Instance details

Defined in Foundation.Collection.Buildable

type Chunk String Source #
Instance details

Defined in Foundation.Parser

Numeric functions

(^^) :: ( Fractional a, Integral b) => a -> b -> a infixr 8 Source #

raise a number to an integral power

fromIntegral :: ( Integral a, Num b) => a -> b Source #

general coercion from integral types

realToFrac :: ( Real a, Fractional b) => a -> b Source #

general coercion to fractional types

Monoids

class Semigroup a Source #

The class of semigroups (types with an associative binary operation).

Instances should satisfy the following:

Associativity
x <> (y <> z) = (x <> y) <> z

Since: base-4.9.0.0

Minimal complete definition

(<>)

Instances

Instances details
Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup ()

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Semigroup Builder
Instance details

Defined in Basement.String.Builder

Semigroup Builder
Instance details

Defined in Basement.Block.Builder

Semigroup String
Instance details

Defined in Basement.UTF8.Base

Semigroup AsciiString
Instance details

Defined in Basement.Types.AsciiString

Semigroup Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Semigroup CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Semigroup Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Semigroup FileName Source #
Instance details

Defined in Foundation.VFS.FilePath

Semigroup [a]

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: [a] -> [a] -> [a] Source #

sconcat :: NonEmpty [a] -> [a] Source #

stimes :: Integral b => b -> [a] -> [a] Source #

Semigroup a => Semigroup ( Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup a => Semigroup ( IO a)

Since: base-4.10.0.0

Instance details

Defined in GHC.Base

Semigroup p => Semigroup ( Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Ord a => Semigroup ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Ord a => Semigroup ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid m => Semigroup ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Semigroup ( Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Semigroup ( Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Semigroup ( First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Semigroup ( Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Semigroup a => Semigroup ( Dual a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Semigroup ( Endo a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Num a => Semigroup ( Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Num a => Semigroup ( Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Semigroup a => Semigroup ( Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Semigroup ( NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup ( Array a)
Instance details

Defined in Basement.BoxedArray

PrimType ty => Semigroup ( UArray ty)
Instance details

Defined in Basement.UArray.Base

PrimType ty => Semigroup ( Block ty)
Instance details

Defined in Basement.Block.Base

Semigroup ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Semigroup ( DList a) Source #
Instance details

Defined in Foundation.List.DList

Semigroup ( ChunkedUArray a) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Semigroup b => Semigroup (a -> b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a -> b) -> (a -> b) -> a -> b Source #

sconcat :: NonEmpty (a -> b) -> a -> b Source #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b Source #

Semigroup ( Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Semigroup ( V1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Semigroup ( U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Semigroup a, Semigroup b) => Semigroup (a, b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) Source #

sconcat :: NonEmpty (a, b) -> (a, b) Source #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) Source #

Semigroup ( Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Semigroup a => Semigroup ( ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Semigroup (f p) => Semigroup ( Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) Source #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) Source #

Semigroup a => Semigroup ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

( Applicative f, Semigroup a) => Semigroup ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Alternative f => Semigroup ( Alt f a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Semigroup c => Semigroup ( K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p Source #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p Source #

( Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) Source #

Semigroup (f p) => Semigroup ( M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

sconcat :: NonEmpty ( M1 i c f p) -> M1 i c f p Source #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p Source #

Semigroup (f (g p)) => Semigroup ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

sconcat :: NonEmpty ((f :.: g) p) -> (f :.: g) p Source #

stimes :: Integral b => b -> (f :.: g) p -> (f :.: g) p Source #

( Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) Source #

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

class Semigroup a => Monoid a where Source #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z ( Semigroup law)
Concatenation
mconcat = foldr ( <> ) mempty

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 newtype s and make those instances of Monoid , e.g. Sum and Product .

NOTE : Semigroup is a superclass of Monoid since base-4.11.0.0 .

Minimal complete definition

mempty

Methods

mempty :: a Source #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a Source #

An associative operation

NOTE : This method is redundant and has the default implementation mappend = ( <> ) since base-4.11.0.0 . Should it be implemented manually, since mappend is a synonym for ( <> ), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid .

mconcat :: [a] -> a Source #

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 ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Monoid Builder
Instance details

Defined in Basement.String.Builder

Monoid Builder
Instance details

Defined in Basement.Block.Builder

Monoid String
Instance details

Defined in Basement.UTF8.Base

Monoid AsciiString
Instance details

Defined in Basement.Types.AsciiString

Monoid Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Monoid CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Monoid Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Monoid FileName Source #
Instance details

Defined in Foundation.VFS.FilePath

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] Source #

mappend :: [a] -> [a] -> [a] Source #

mconcat :: [[a]] -> [a] Source #

Semigroup a => Monoid ( Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid : "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S ."

Since 4.11.0 : constraint on inner a value generalised from Monoid to Semigroup .

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid a => Monoid ( IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Monoid p => Monoid ( Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Ord a, Bounded a) => Monoid ( Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

( Ord a, Bounded a) => Monoid ( Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid m => Monoid ( WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid ( Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid a => Monoid ( Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Monoid ( First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Monoid ( Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Monoid a => Monoid ( Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Monoid ( Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Num a => Monoid ( Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Num a => Monoid ( Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Monoid a => Monoid ( Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Monoid ( Array a)
Instance details

Defined in Basement.BoxedArray

PrimType ty => Monoid ( UArray ty)
Instance details

Defined in Basement.UArray.Base

PrimType ty => Monoid ( Block ty)
Instance details

Defined in Basement.Block.Base

Monoid ( CountOf ty)
Instance details

Defined in Basement.Types.OffsetSize

Monoid ( DList a) Source #
Instance details

Defined in Foundation.List.DList

Monoid ( ChunkedUArray a) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b Source #

mappend :: (a -> b) -> (a -> b) -> a -> b Source #

mconcat :: [a -> b] -> a -> b Source #

Monoid ( U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) Source #

mappend :: (a, b) -> (a, b) -> (a, b) Source #

mconcat :: [(a, b)] -> (a, b) Source #

Monoid ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Monoid a => Monoid ( ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Monoid (f p) => Monoid ( Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) Source #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) Source #

mconcat :: [(a, b, c)] -> (a, b, c) Source #

Monoid a => Monoid ( Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

( Applicative f, Monoid a) => Monoid ( Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Alternative f => Monoid ( Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Monoid c => Monoid ( K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

( Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p Source #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p Source #

mconcat :: [(f :*: g) p] -> (f :*: g) p Source #

( Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) Source #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) Source #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) Source #

Monoid (f p) => Monoid ( M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p Source #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p Source #

mconcat :: [ M1 i c f p] -> M1 i c f p Source #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p Source #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p Source #

mconcat :: [(f :.: g) p] -> (f :.: g) p Source #

( Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) Source #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) Source #

(<>) :: Semigroup a => a -> a -> a infixr 6 Source #

An associative operation.

>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]

Collection

class ( IsList c, Item c ~ Element c) => Collection c where Source #

A set of methods for ordered colection

Minimal complete definition

null , length , ( elem | notElem ), minimum , maximum , all , any

Methods

null :: c -> Bool Source #

Check if a collection is empty

length :: c -> CountOf ( Element c) Source #

Length of a collection (number of Element c)

elem :: forall a. ( Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection contains a specific element

This is the inverse of notElem .

notElem :: forall a. ( Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection does *not* contain a specific element

This is the inverse of elem .

maximum :: forall a. ( Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the maximum element of a collection

minimum :: forall a. ( Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the minimum element of a collection

any :: ( Element c -> Bool ) -> c -> Bool Source #

Determine is any elements of the collection satisfy the predicate

all :: ( Element c -> Bool ) -> c -> Bool Source #

Determine is all elements of the collection satisfy the predicate

Instances

Instances details
Collection String Source #
Instance details

Defined in Foundation.Collection.Collection

Collection AsciiString Source #
Instance details

Defined in Foundation.Collection.Collection

Collection Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Collection CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Collection Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Collection [a] Source #
Instance details

Defined in Foundation.Collection.Collection

Collection ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Collection

PrimType ty => Collection ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Collection

PrimType ty => Collection ( Block ty) Source #
Instance details

Defined in Foundation.Collection.Collection

Collection c => Collection ( NonEmpty c) Source #
Instance details

Defined in Foundation.Collection.Collection

Collection ( DList a) Source #
Instance details

Defined in Foundation.List.DList

PrimType ty => Collection ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

and :: ( Collection col, Element col ~ Bool ) => col -> Bool Source #

Return True if all the elements in the collection are True

or :: ( Collection col, Element col ~ Bool ) => col -> Bool Source #

Return True if at least one element in the collection is True

class ( IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where Source #

A set of methods for ordered colection

Methods

take :: CountOf ( Element c) -> c -> c Source #

Take the first @n elements of a collection

revTake :: CountOf ( Element c) -> c -> c Source #

Take the last @n elements of a collection

drop :: CountOf ( Element c) -> c -> c Source #

Drop the first @n elements of a collection

revDrop :: CountOf ( Element c) -> c -> c Source #

Drop the last @n elements of a collection

splitAt :: CountOf ( Element c) -> c -> (c, c) Source #

Split the collection at the @n'th elements

revSplitAt :: CountOf ( Element c) -> c -> (c, c) Source #

Split the collection at the @n'th elements from the end

splitOn :: ( Element c -> Bool ) -> c -> [c] Source #

Split on a specific elements returning a list of colletion

break :: ( Element c -> Bool ) -> c -> (c, c) Source #

Split a collection when the predicate return true

breakEnd :: ( Element c -> Bool ) -> c -> (c, c) Source #

Split a collection when the predicate return true starting from the end of the collection

breakElem :: Eq ( Element c) => Element c -> c -> (c, c) Source #

Split a collection at the given element

takeWhile :: ( Element c -> Bool ) -> c -> c Source #

Return the longest prefix in the collection that satisfy the predicate

dropWhile :: ( Element c -> Bool ) -> c -> c Source #

Return the longest prefix in the collection that satisfy the predicate

intersperse :: Element c -> c -> c Source #

The intersperse function takes an element and a list and `intersperses' that element between the elements of the list. For example,

intersperse ',' "abcde" == "a,b,c,d,e"

intercalate :: Monoid ( Item c) => Element c -> c -> Element c Source #

intercalate xs xss is equivalent to ( mconcat ( intersperse xs xss)) . It inserts the list xs in between the lists in xss and concatenates the result.

span :: ( Element c -> Bool ) -> c -> (c, c) Source #

Split a collection while the predicate return true

spanEnd :: ( Element c -> Bool ) -> c -> (c, c) Source #

Split a collection while the predicate return true starting from the end of the collection

filter :: ( Element c -> Bool ) -> c -> c Source #

Filter all the elements that satisfy the predicate

partition :: ( Element c -> Bool ) -> c -> (c, c) Source #

Partition the elements that satisfy the predicate and those that don't

reverse :: c -> c Source #

Reverse a collection

uncons :: c -> Maybe ( Element c, c) Source #

Decompose a collection into its first element and the remaining collection. If the collection is empty, returns Nothing.

unsnoc :: c -> Maybe (c, Element c) Source #

Decompose a collection into a collection without its last element, and the last element If the collection is empty, returns Nothing.

snoc :: c -> Element c -> c Source #

Prepend an element to an ordered collection

cons :: Element c -> c -> c Source #

Append an element to an ordered collection

find :: ( Element c -> Bool ) -> c -> Maybe ( Element c) Source #

Find an element in an ordered collection

sortBy :: ( Element c -> Element c -> Ordering ) -> c -> c Source #

Sort an ordered collection using the specified order function

singleton :: Element c -> c Source #

Create a collection with a single element

head :: NonEmpty c -> Element c Source #

get the first element of a non-empty collection

last :: NonEmpty c -> Element c Source #

get the last element of a non-empty collection

tail :: NonEmpty c -> c Source #

Extract the elements after the first element of a non-empty collection.

init :: NonEmpty c -> c Source #

Extract the elements before the last element of a non-empty collection.

replicate :: CountOf ( Element c) -> Element c -> c Source #

Create a collection where the element in parameter is repeated N time

isPrefixOf :: Eq ( Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a prefix of the second.

default isPrefixOf :: Eq c => c -> c -> Bool Source #

isSuffixOf :: Eq ( Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a suffix of the second.

default isSuffixOf :: Eq c => c -> c -> Bool Source #

isInfixOf :: Eq ( Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is an infix of the second.

default isInfixOf :: Eq c => c -> c -> Bool Source #

stripPrefix :: Eq ( Element c) => c -> c -> Maybe c Source #

Try to strip a prefix from a collection

stripSuffix :: Eq ( Element c) => c -> c -> Maybe c Source #

Try to strip a suffix from a collection

Instances

Instances details
Sequential String Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element String ) -> String -> String Source #

revTake :: CountOf ( Element String ) -> String -> String Source #

drop :: CountOf ( Element String ) -> String -> String Source #

revDrop :: CountOf ( Element String ) -> String -> String Source #

splitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

revSplitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

splitOn :: ( Element String -> Bool ) -> String -> [ String ] Source #

break :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakElem :: Element String -> String -> ( String , String ) Source #

takeWhile :: ( Element String -> Bool ) -> String -> String Source #

dropWhile :: ( Element String -> Bool ) -> String -> String Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

spanEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

filter :: ( Element String -> Bool ) -> String -> String Source #

partition :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe ( Element String , String ) Source #

unsnoc :: String -> Maybe ( String , Element String ) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: ( Element String -> Bool ) -> String -> Maybe ( Element String ) Source #

sortBy :: ( Element String -> Element String -> Ordering ) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

replicate :: CountOf ( Element String ) -> Element String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Sequential AsciiString Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element AsciiString ) -> AsciiString -> AsciiString Source #

revTake :: CountOf ( Element AsciiString ) -> AsciiString -> AsciiString Source #

drop :: CountOf ( Element AsciiString ) -> AsciiString -> AsciiString Source #

revDrop :: CountOf ( Element AsciiString ) -> AsciiString -> AsciiString Source #

splitAt :: CountOf ( Element AsciiString ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

revSplitAt :: CountOf ( Element AsciiString ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

splitOn :: ( Element AsciiString -> Bool ) -> AsciiString -> [ AsciiString ] Source #

break :: ( Element AsciiString -> Bool ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

breakEnd :: ( Element AsciiString -> Bool ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

breakElem :: Element AsciiString -> AsciiString -> ( AsciiString , AsciiString ) Source #

takeWhile :: ( Element AsciiString -> Bool ) -> AsciiString -> AsciiString Source #

dropWhile :: ( Element AsciiString -> Bool ) -> AsciiString -> AsciiString Source #

intersperse :: Element AsciiString -> AsciiString -> AsciiString Source #

intercalate :: Element AsciiString -> AsciiString -> Element AsciiString Source #

span :: ( Element AsciiString -> Bool ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

spanEnd :: ( Element AsciiString -> Bool ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

filter :: ( Element AsciiString -> Bool ) -> AsciiString -> AsciiString Source #

partition :: ( Element AsciiString -> Bool ) -> AsciiString -> ( AsciiString , AsciiString ) Source #

reverse :: AsciiString -> AsciiString Source #

uncons :: AsciiString -> Maybe ( Element AsciiString , AsciiString ) Source #

unsnoc :: AsciiString -> Maybe ( AsciiString , Element AsciiString ) Source #

snoc :: AsciiString -> Element AsciiString -> AsciiString Source #

cons :: Element AsciiString -> AsciiString -> AsciiString Source #

find :: ( Element AsciiString -> Bool ) -> AsciiString -> Maybe ( Element AsciiString ) Source #

sortBy :: ( Element AsciiString -> Element AsciiString -> Ordering ) -> AsciiString -> AsciiString Source #

singleton :: Element AsciiString -> AsciiString Source #

head :: NonEmpty AsciiString -> Element AsciiString Source #

last :: NonEmpty AsciiString -> Element AsciiString Source #

tail :: NonEmpty AsciiString -> AsciiString Source #

init :: NonEmpty AsciiString -> AsciiString Source #

replicate :: CountOf ( Element AsciiString ) -> Element AsciiString -> AsciiString Source #

isPrefixOf :: AsciiString -> AsciiString -> Bool Source #

isSuffixOf :: AsciiString -> AsciiString -> Bool Source #

isInfixOf :: AsciiString -> AsciiString -> Bool Source #

stripPrefix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

stripSuffix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

Sequential Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Methods

take :: CountOf ( Element Bitmap ) -> Bitmap -> Bitmap Source #

revTake :: CountOf ( Element Bitmap ) -> Bitmap -> Bitmap Source #

drop :: CountOf ( Element Bitmap ) -> Bitmap -> Bitmap Source #

revDrop :: CountOf ( Element Bitmap ) -> Bitmap -> Bitmap Source #

splitAt :: CountOf ( Element Bitmap ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

revSplitAt :: CountOf ( Element Bitmap ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

splitOn :: ( Element Bitmap -> Bool ) -> Bitmap -> [ Bitmap ] Source #

break :: ( Element Bitmap -> Bool ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

breakEnd :: ( Element Bitmap -> Bool ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

breakElem :: Element Bitmap -> Bitmap -> ( Bitmap , Bitmap ) Source #

takeWhile :: ( Element Bitmap -> Bool ) -> Bitmap -> Bitmap Source #

dropWhile :: ( Element Bitmap -> Bool ) -> Bitmap -> Bitmap Source #

intersperse :: Element Bitmap -> Bitmap -> Bitmap Source #

intercalate :: Element Bitmap -> Bitmap -> Element Bitmap Source #

span :: ( Element Bitmap -> Bool ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

spanEnd :: ( Element Bitmap -> Bool ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

filter :: ( Element Bitmap -> Bool ) -> Bitmap -> Bitmap Source #

partition :: ( Element Bitmap -> Bool ) -> Bitmap -> ( Bitmap , Bitmap ) Source #

reverse :: Bitmap -> Bitmap Source #

uncons :: Bitmap -> Maybe ( Element Bitmap , Bitmap ) Source #

unsnoc :: Bitmap -> Maybe ( Bitmap , Element Bitmap ) Source #

snoc :: Bitmap -> Element Bitmap -> Bitmap Source #

cons :: Element Bitmap -> Bitmap -> Bitmap Source #

find :: ( Element Bitmap -> Bool ) -> Bitmap -> Maybe ( Element Bitmap ) Source #

sortBy :: ( Element Bitmap -> Element Bitmap -> Ordering ) -> Bitmap -> Bitmap Source #

singleton :: Element Bitmap -> Bitmap Source #

head :: NonEmpty Bitmap -> Element Bitmap Source #

last :: NonEmpty Bitmap -> Element Bitmap Source #

tail :: NonEmpty Bitmap -> Bitmap Source #

init :: NonEmpty Bitmap -> Bitmap Source #

replicate :: CountOf ( Element Bitmap ) -> Element Bitmap -> Bitmap Source #

isPrefixOf :: Bitmap -> Bitmap -> Bool Source #

isSuffixOf :: Bitmap -> Bitmap -> Bool Source #

isInfixOf :: Bitmap -> Bitmap -> Bool Source #

stripPrefix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

stripSuffix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

Sequential CSV Source #
Instance details

Defined in Foundation.Format.CSV.Types

Methods

take :: CountOf ( Element CSV ) -> CSV -> CSV Source #

revTake :: CountOf ( Element CSV ) -> CSV -> CSV Source #

drop :: CountOf ( Element CSV ) -> CSV -> CSV Source #

revDrop :: CountOf ( Element CSV ) -> CSV -> CSV Source #

splitAt :: CountOf ( Element CSV ) -> CSV -> ( CSV , CSV ) Source #

revSplitAt :: CountOf ( Element CSV ) -> CSV -> ( CSV , CSV ) Source #

splitOn :: ( Element CSV -> Bool ) -> CSV -> [ CSV ] Source #

break :: ( Element CSV -> Bool ) -> CSV -> ( CSV , CSV ) Source #

breakEnd :: ( Element CSV -> Bool ) -> CSV -> ( CSV , CSV ) Source #

breakElem :: Element CSV -> CSV -> ( CSV , CSV ) Source #

takeWhile :: ( Element CSV -> Bool ) -> CSV -> CSV Source #

dropWhile :: ( Element CSV -> Bool ) -> CSV -> CSV Source #

intersperse :: Element CSV -> CSV -> CSV Source #

intercalate :: Element CSV -> CSV -> Element CSV Source #

span :: ( Element CSV -> Bool ) -> CSV -> ( CSV , CSV ) Source #

spanEnd :: ( Element CSV -> Bool ) -> CSV -> ( CSV , CSV ) Source #

filter :: ( Element CSV -> Bool ) -> CSV -> CSV Source #

partition :: ( Element CSV -> Bool ) -> CSV -> ( CSV , CSV ) Source #

reverse :: CSV -> CSV Source #

uncons :: CSV -> Maybe ( Element CSV , CSV ) Source #

unsnoc :: CSV -> Maybe ( CSV , Element CSV ) Source #

snoc :: CSV -> Element CSV -> CSV Source #

cons :: Element CSV -> CSV -> CSV Source #

find :: ( Element CSV -> Bool ) -> CSV -> Maybe ( Element CSV ) Source #

sortBy :: ( Element CSV -> Element CSV -> Ordering ) -> CSV -> CSV Source #

singleton :: Element CSV -> CSV Source #

head :: NonEmpty CSV -> Element CSV Source #

last :: NonEmpty CSV -> Element CSV Source #

tail :: NonEmpty CSV -> CSV Source #

init :: NonEmpty CSV -> CSV Source #

replicate :: CountOf ( Element CSV ) -> Element CSV -> CSV Source #

isPrefixOf :: CSV -> CSV -> Bool Source #

isSuffixOf :: CSV -> CSV -> Bool Source #

isInfixOf :: CSV -> CSV -> Bool Source #

stripPrefix :: CSV -> CSV -> Maybe CSV Source #

stripSuffix :: CSV -> CSV -> Maybe CSV Source #

Sequential Row Source #
Instance details

Defined in Foundation.Format.CSV.Types

Methods

take :: CountOf ( Element Row ) -> Row -> Row Source #

revTake :: CountOf ( Element Row ) -> Row -> Row Source #

drop :: CountOf ( Element Row ) -> Row -> Row Source #

revDrop :: CountOf ( Element Row ) -> Row -> Row Source #

splitAt :: CountOf ( Element Row ) -> Row -> ( Row , Row ) Source #

revSplitAt :: CountOf ( Element Row ) -> Row -> ( Row , Row ) Source #

splitOn :: ( Element Row -> Bool ) -> Row -> [ Row ] Source #

break :: ( Element Row -> Bool ) -> Row -> ( Row , Row ) Source #

breakEnd :: ( Element Row -> Bool ) -> Row -> ( Row , Row ) Source #

breakElem :: Element Row -> Row -> ( Row , Row ) Source #

takeWhile :: ( Element Row -> Bool ) -> Row -> Row Source #

dropWhile :: ( Element Row -> Bool ) -> Row -> Row Source #

intersperse :: Element Row -> Row -> Row Source #

intercalate :: Element Row -> Row -> Element Row Source #

span :: ( Element Row -> Bool ) -> Row -> ( Row , Row ) Source #

spanEnd :: ( Element Row -> Bool ) -> Row -> ( Row , Row ) Source #

filter :: ( Element Row -> Bool ) -> Row -> Row Source #

partition :: ( Element Row -> Bool ) -> Row -> ( Row , Row ) Source #

reverse :: Row -> Row Source #

uncons :: Row -> Maybe ( Element Row , Row ) Source #

unsnoc :: Row -> Maybe ( Row , Element Row ) Source #

snoc :: Row -> Element Row -> Row Source #

cons :: Element Row -> Row -> Row Source #

find :: ( Element Row -> Bool ) -> Row -> Maybe ( Element Row ) Source #

sortBy :: ( Element Row -> Element Row -> Ordering ) -> Row -> Row Source #

singleton :: Element Row -> Row Source #

head :: NonEmpty Row -> Element Row Source #

last :: NonEmpty Row -> Element Row Source #

tail :: NonEmpty Row -> Row Source #

init :: NonEmpty Row -> Row Source #

replicate :: CountOf ( Element Row ) -> Element Row -> Row Source #

isPrefixOf :: Row -> Row -> Bool Source #

isSuffixOf :: Row -> Row -> Bool Source #

isInfixOf :: Row -> Row -> Bool Source #

stripPrefix :: Row -> Row -> Maybe Row Source #

stripSuffix :: Row -> Row -> Maybe Row Source #

Sequential [a] Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element [a]) -> [a] -> [a] Source #

revTake :: CountOf ( Element [a]) -> [a] -> [a] Source #

drop :: CountOf ( Element [a]) -> [a] -> [a] Source #

revDrop :: CountOf ( Element [a]) -> [a] -> [a] Source #

splitAt :: CountOf ( Element [a]) -> [a] -> ([a], [a]) Source #

revSplitAt :: CountOf ( Element [a]) -> [a] -> ([a], [a]) Source #

splitOn :: ( Element [a] -> Bool ) -> [a] -> [[a]] Source #

break :: ( Element [a] -> Bool ) -> [a] -> ([a], [a]) Source #

breakEnd :: ( Element [a] -> Bool ) -> [a] -> ([a], [a]) Source #

breakElem :: Element [a] -> [a] -> ([a], [a]) Source #

takeWhile :: ( Element [a] -> Bool ) -> [a] -> [a] Source #

dropWhile :: ( Element [a] -> Bool ) -> [a] -> [a] Source #

intersperse :: Element [a] -> [a] -> [a] Source #

intercalate :: Element [a] -> [a] -> Element [a] Source #

span :: ( Element [a] -> Bool ) -> [a] -> ([a], [a]) Source #

spanEnd :: ( Element [a] -> Bool ) -> [a] -> ([a], [a]) Source #

filter :: ( Element [a] -> Bool ) -> [a] -> [a] Source #

partition :: ( Element [a] -> Bool ) -> [a] -> ([a], [a]) Source #

reverse :: [a] -> [a] Source #

uncons :: [a] -> Maybe ( Element [a], [a]) Source #

unsnoc :: [a] -> Maybe ([a], Element [a]) Source #

snoc :: [a] -> Element [a] -> [a] Source #

cons :: Element [a] -> [a] -> [a] Source #

find :: ( Element [a] -> Bool ) -> [a] -> Maybe ( Element [a]) Source #

sortBy :: ( Element [a] -> Element [a] -> Ordering ) -> [a] -> [a] Source #

singleton :: Element [a] -> [a] Source #

head :: NonEmpty [a] -> Element [a] Source #

last :: NonEmpty [a] -> Element [a] Source #

tail :: NonEmpty [a] -> [a] Source #

init :: NonEmpty [a] -> [a] Source #

replicate :: CountOf ( Element [a]) -> Element [a] -> [a] Source #

isPrefixOf :: [a] -> [a] -> Bool Source #

isSuffixOf :: [a] -> [a] -> Bool Source #

isInfixOf :: [a] -> [a] -> Bool Source #

stripPrefix :: [a] -> [a] -> Maybe [a] Source #

stripSuffix :: [a] -> [a] -> Maybe [a] Source #

Sequential ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf ( Element ( Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf ( Element ( Array ty)) -> Array ty -> ( Array ty, Array ty) Source #

revSplitAt :: CountOf ( Element ( Array ty)) -> Array ty -> ( Array ty, Array ty) Source #

splitOn :: ( Element ( Array ty) -> Bool ) -> Array ty -> [ Array ty] Source #

break :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

breakEnd :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

breakElem :: Element ( Array ty) -> Array ty -> ( Array ty, Array ty) Source #

takeWhile :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

dropWhile :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

intersperse :: Element ( Array ty) -> Array ty -> Array ty Source #

intercalate :: Element ( Array ty) -> Array ty -> Element ( Array ty) Source #

span :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

spanEnd :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

filter :: ( Element ( Array ty) -> Bool ) -> Array ty -> Array ty Source #

partition :: ( Element ( Array ty) -> Bool ) -> Array ty -> ( Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe ( Element ( Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe ( Array ty, Element ( Array ty)) Source #

snoc :: Array ty -> Element ( Array ty) -> Array ty Source #

cons :: Element ( Array ty) -> Array ty -> Array ty Source #

find :: ( Element ( Array ty) -> Bool ) -> Array ty -> Maybe ( Element ( Array ty)) Source #

sortBy :: ( Element ( Array ty) -> Element ( Array ty) -> Ordering ) -> Array ty -> Array ty Source #

singleton :: Element ( Array ty) -> Array ty Source #

head :: NonEmpty ( Array ty) -> Element ( Array ty) Source #

last :: NonEmpty ( Array ty) -> Element ( Array ty) Source #

tail :: NonEmpty ( Array ty) -> Array ty Source #

init :: NonEmpty ( Array ty) -> Array ty Source #

replicate :: CountOf ( Element ( Array ty)) -> Element ( Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

isInfixOf :: Array ty -> Array ty -> Bool Source #

stripPrefix :: Array ty -> Array ty -> Maybe ( Array ty) Source #

stripSuffix :: Array ty -> Array ty -> Maybe ( Array ty) Source #

PrimType ty => Sequential ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf ( Element ( UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf ( Element ( UArray ty)) -> UArray ty -> ( UArray ty, UArray ty) Source #

revSplitAt :: CountOf ( Element ( UArray ty)) -> UArray ty -> ( UArray ty, UArray ty) Source #

splitOn :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> [ UArray ty] Source #

break :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

breakEnd :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

breakElem :: Element ( UArray ty) -> UArray ty -> ( UArray ty, UArray ty) Source #

takeWhile :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

dropWhile :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

intersperse :: Element ( UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element ( UArray ty) -> UArray ty -> Element ( UArray ty) Source #

span :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

spanEnd :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

filter :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> UArray ty Source #

partition :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> ( UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe ( Element ( UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe ( UArray ty, Element ( UArray ty)) Source #

snoc :: UArray ty -> Element ( UArray ty) -> UArray ty Source #

cons :: Element ( UArray ty) -> UArray ty -> UArray ty Source #

find :: ( Element ( UArray ty) -> Bool ) -> UArray ty -> Maybe ( Element ( UArray ty)) Source #

sortBy :: ( Element ( UArray ty) -> Element ( UArray ty) -> Ordering ) -> UArray ty -> UArray ty Source #

singleton :: Element ( UArray ty) -> UArray ty Source #

head :: NonEmpty ( UArray ty) -> Element ( UArray ty) Source #

last :: NonEmpty ( UArray ty) -> Element ( UArray ty) Source #

tail :: NonEmpty ( UArray ty) -> UArray ty Source #

init :: NonEmpty ( UArray ty) -> UArray ty Source #

replicate :: CountOf ( Element ( UArray ty)) -> Element ( UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

isInfixOf :: UArray ty -> UArray ty -> Bool Source #

stripPrefix :: UArray ty -> UArray ty -> Maybe ( UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe ( UArray ty) Source #

PrimType ty => Sequential ( Block ty) Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element ( Block ty)) -> Block ty -> Block ty Source #

revTake :: CountOf ( Element ( Block ty)) -> Block ty -> Block ty Source #

drop :: CountOf ( Element ( Block ty)) -> Block ty -> Block ty Source #

revDrop :: CountOf ( Element ( Block ty)) -> Block ty -> Block ty Source #

splitAt :: CountOf ( Element ( Block ty)) -> Block ty -> ( Block ty, Block ty) Source #

revSplitAt :: CountOf ( Element ( Block ty)) -> Block ty -> ( Block ty, Block ty) Source #

splitOn :: ( Element ( Block ty) -> Bool ) -> Block ty -> [ Block ty] Source #

break :: ( Element ( Block ty) -> Bool ) -> Block ty -> ( Block ty, Block ty) Source #

breakEnd :: ( Element ( Block ty) -> Bool ) -> Block ty -> ( Block ty, Block ty) Source #

breakElem :: Element ( Block ty) -> Block ty -> ( Block ty, Block ty) Source #

takeWhile :: ( Element ( Block ty) -> Bool ) -> Block ty -> Block ty Source #

dropWhile :: ( Element ( Block ty) -> Bool ) -> Block ty -> Block ty Source #

intersperse :: Element ( Block ty) -> Block ty -> Block ty Source #

intercalate :: Element ( Block ty) -> Block ty -> Element ( Block ty) Source #

span :: ( Element ( Block ty) -> Bool ) -> Block ty -> ( Block ty, Block ty) Source #

spanEnd :: ( Element ( Block ty) -> Bool ) -> Block ty -> ( Block ty, Block ty) Source #

filter :: ( Element ( Block ty) -> Bool ) -> Block ty -> Block ty Source #

partition :: ( Element ( Block ty) -> Bool ) -> Block ty -> ( Block ty, Block ty) Source #

reverse :: Block ty -> Block ty Source #

uncons :: Block ty -> Maybe ( Element ( Block ty), Block ty) Source #

unsnoc :: Block ty -> Maybe ( Block ty, Element ( Block ty)) Source #

snoc :: Block ty -> Element ( Block ty) -> Block ty Source #

cons :: Element ( Block ty) -> Block ty -> Block ty Source #

find :: ( Element ( Block ty) -> Bool ) -> Block ty -> Maybe ( Element ( Block ty)) Source #

sortBy :: ( Element ( Block ty) -> Element ( Block ty) -> Ordering ) -> Block ty -> Block ty Source #

singleton :: Element ( Block ty) -> Block ty Source #

head :: NonEmpty ( Block ty) -> Element ( Block ty) Source #

last :: NonEmpty ( Block ty) -> Element ( Block ty) Source #

tail :: NonEmpty ( Block ty) -> Block ty Source #

init :: NonEmpty ( Block ty) -> Block ty Source #

replicate :: CountOf ( Element ( Block ty)) -> Element ( Block ty) -> Block ty Source #

isPrefixOf :: Block ty -> Block ty -> Bool Source #

isSuffixOf :: Block ty -> Block ty -> Bool Source #

isInfixOf :: Block ty -> Block ty -> Bool Source #

stripPrefix :: Block ty -> Block ty -> Maybe ( Block ty) Source #

stripSuffix :: Block ty -> Block ty -> Maybe ( Block ty) Source #

Sequential ( DList a) Source #
Instance details

Defined in Foundation.List.DList

Methods

take :: CountOf ( Element ( DList a)) -> DList a -> DList a Source #

revTake :: CountOf ( Element ( DList a)) -> DList a -> DList a Source #

drop :: CountOf ( Element ( DList a)) -> DList a -> DList a Source #

revDrop :: CountOf ( Element ( DList a)) -> DList a -> DList a Source #

splitAt :: CountOf ( Element ( DList a)) -> DList a -> ( DList a, DList a) Source #

revSplitAt :: CountOf ( Element ( DList a)) -> DList a -> ( DList a, DList a) Source #

splitOn :: ( Element ( DList a) -> Bool ) -> DList a -> [ DList a] Source #

break :: ( Element ( DList a) -> Bool ) -> DList a -> ( DList a, DList a) Source #

breakEnd :: ( Element ( DList a) -> Bool ) -> DList a -> ( DList a, DList a) Source #

breakElem :: Element ( DList a) -> DList a -> ( DList a, DList a) Source #

takeWhile :: ( Element ( DList a) -> Bool ) -> DList a -> DList a Source #

dropWhile :: ( Element ( DList a) -> Bool ) -> DList a -> DList a Source #

intersperse :: Element ( DList a) -> DList a -> DList a Source #

intercalate :: Element ( DList a) -> DList a -> Element ( DList a) Source #

span :: ( Element ( DList a) -> Bool ) -> DList a -> ( DList a, DList a) Source #

spanEnd :: ( Element ( DList a) -> Bool ) -> DList a -> ( DList a, DList a) Source #

filter :: ( Element ( DList a) -> Bool ) -> DList a -> DList a Source #

partition :: ( Element ( DList a) -> Bool ) -> DList a -> ( DList a, DList a) Source #

reverse :: DList a -> DList a Source #

uncons :: DList a -> Maybe ( Element ( DList a), DList a) Source #

unsnoc :: DList a -> Maybe ( DList a, Element ( DList a)) Source #

snoc :: DList a -> Element ( DList a) -> DList a Source #

cons :: Element ( DList a) -> DList a -> DList a Source #

find :: ( Element ( DList a) -> Bool ) -> DList a -> Maybe ( Element ( DList a)) Source #

sortBy :: ( Element ( DList a) -> Element ( DList a) -> Ordering ) -> DList a -> DList a Source #

singleton :: Element ( DList a) -> DList a Source #

head :: NonEmpty ( DList a) -> Element ( DList a) Source #

last :: NonEmpty ( DList a) -> Element ( DList a) Source #

tail :: NonEmpty ( DList a) -> DList a Source #

init :: NonEmpty ( DList a) -> DList a Source #

replicate :: CountOf ( Element ( DList a)) -> Element ( DList a) -> DList a Source #

isPrefixOf :: DList a -> DList a -> Bool Source #

isSuffixOf :: DList a -> DList a -> Bool Source #

isInfixOf :: DList a -> DList a -> Bool Source #

stripPrefix :: DList a -> DList a -> Maybe ( DList a) Source #

stripSuffix :: DList a -> DList a -> Maybe ( DList a) Source #

PrimType ty => Sequential ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Methods

take :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revTake :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

drop :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revDrop :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

splitAt :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

revSplitAt :: CountOf ( Element ( ChunkedUArray ty)) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

splitOn :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> [ ChunkedUArray ty] Source #

break :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

breakEnd :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

breakElem :: Element ( ChunkedUArray ty) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

takeWhile :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ChunkedUArray ty Source #

dropWhile :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intersperse :: Element ( ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intercalate :: Element ( ChunkedUArray ty) -> ChunkedUArray ty -> Element ( ChunkedUArray ty) Source #

span :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

spanEnd :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

filter :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ChunkedUArray ty Source #

partition :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> ( ChunkedUArray ty, ChunkedUArray ty) Source #

reverse :: ChunkedUArray ty -> ChunkedUArray ty Source #

uncons :: ChunkedUArray ty -> Maybe ( Element ( ChunkedUArray ty), ChunkedUArray ty) Source #

unsnoc :: ChunkedUArray ty -> Maybe ( ChunkedUArray ty, Element ( ChunkedUArray ty)) Source #

snoc :: ChunkedUArray ty -> Element ( ChunkedUArray ty) -> ChunkedUArray ty Source #

cons :: Element ( ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

find :: ( Element ( ChunkedUArray ty) -> Bool ) -> ChunkedUArray ty -> Maybe ( Element ( ChunkedUArray ty)) Source #

sortBy :: ( Element ( ChunkedUArray ty) -> Element ( ChunkedUArray ty) -> Ordering ) -> ChunkedUArray ty -> ChunkedUArray ty Source #

singleton :: Element ( ChunkedUArray ty) -> ChunkedUArray ty Source #

head :: NonEmpty ( ChunkedUArray ty) -> Element ( ChunkedUArray ty) Source #

last :: NonEmpty ( ChunkedUArray ty) -> Element ( ChunkedUArray ty) Source #

tail :: NonEmpty ( ChunkedUArray ty) -> ChunkedUArray ty Source #

init :: NonEmpty ( ChunkedUArray ty) -> ChunkedUArray ty Source #

replicate :: CountOf ( Element ( ChunkedUArray ty)) -> Element ( ChunkedUArray ty) -> ChunkedUArray ty Source #

isPrefixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isSuffixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isInfixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

stripPrefix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe ( ChunkedUArray ty) Source #

stripSuffix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe ( ChunkedUArray ty) Source #

data NonEmpty a Source #

NonEmpty property for any Collection

Instances

Instances details
IsList c => IsList ( NonEmpty c)
Instance details

Defined in Basement.NonEmpty

Associated Types

type Item ( NonEmpty c) Source #

Eq a => Eq ( NonEmpty a)
Instance details

Defined in Basement.NonEmpty

Show a => Show ( NonEmpty a)
Instance details

Defined in Basement.NonEmpty

Collection c => Collection ( NonEmpty c) Source #
Instance details

Defined in Foundation.Collection.Collection

type Item ( NonEmpty c)
Instance details

Defined in Basement.NonEmpty

type Element ( NonEmpty a) Source #
Instance details

Defined in Foundation.Collection.Element

nonEmpty :: Collection c => c -> Maybe ( NonEmpty c) Source #

Smart constructor to create a NonEmpty collection

If the collection is empty, then Nothing is returned Otherwise, the collection is wrapped in the NonEmpty property

Folds

class Foldable collection where Source #

Give the ability to fold a collection on itself

Minimal complete definition

foldl' , foldr

Methods

foldl' :: (a -> Element collection -> a) -> a -> collection -> a Source #

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.

Note that Foundation only provides foldl `, a strict version of foldl because the lazy version is seldom useful.

Left-associative fold of a structure with strict application of the operator.

foldr :: ( Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure.

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldr' :: ( Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure, but with strict application of the operator.

Instances

Instances details
Foldable Bitmap Source #
Instance details

Defined in Foundation.Array.Bitmap

Foldable [a] Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a0 -> Element [a] -> a0) -> a0 -> [a] -> a0 Source #

foldr :: ( Element [a] -> a0 -> a0) -> a0 -> [a] -> a0 Source #

foldr' :: ( Element [a] -> a0 -> a0) -> a0 -> [a] -> a0 Source #

Foldable ( Array ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: ( Element ( Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: ( Element ( Array ty) -> a -> a) -> a -> Array ty -> a Source #

PrimType ty => Foldable ( UArray ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: ( Element ( UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: ( Element ( UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

PrimType ty => Foldable ( Block ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( Block ty) -> a) -> a -> Block ty -> a Source #

foldr :: ( Element ( Block ty) -> a -> a) -> a -> Block ty -> a Source #

foldr' :: ( Element ( Block ty) -> a -> a) -> a -> Block ty -> a Source #

Foldable ( DList a) Source #
Instance details

Defined in Foundation.List.DList

Methods

foldl' :: (a0 -> Element ( DList a) -> a0) -> a0 -> DList a -> a0 Source #

foldr :: ( Element ( DList a) -> a0 -> a0) -> a0 -> DList a -> a0 Source #

foldr' :: ( Element ( DList a) -> a0 -> a0) -> a0 -> DList a -> a0 Source #

PrimType ty => Foldable ( ChunkedUArray ty) Source #
Instance details

Defined in Foundation.Array.Chunked.Unboxed

PrimType ty => Foldable ( BlockN n ty) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a -> Element ( BlockN n ty) -> a) -> a -> BlockN n ty -> a Source #

foldr :: ( Element ( BlockN n ty) -> a -> a) -> a -> BlockN n ty -> a Source #

foldr' :: ( Element ( BlockN n ty) -> a -> a) -> a -> BlockN n ty -> a Source #

Foldable ( ListN n a) Source #
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a0 -> Element ( ListN n a) -> a0) -> a0 -> ListN n a -> a0 Source #

foldr :: ( Element ( ListN n a) -> a0 -> a0) -> a0 -> ListN n a -> a0 Source #

foldr' :: ( Element ( ListN n a) -> a0 -> a0) -> a0 -> ListN n a -> a0 Source #

Maybe

mapMaybe :: (a -> Maybe b) -> [a] -> [b] Source #

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

Expand

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]

catMaybes :: [ Maybe a] -> [a] Source #

The catMaybes function takes a list of Maybe s and returns a list of all the Just values.

Examples

Expand

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]

fromMaybe :: a -> Maybe a -> a Source #

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

Expand

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

isJust :: Maybe a -> Bool Source #

The isJust function returns True iff its argument is of the form Just _ .

Examples

Expand

Basic usage:

>>> isJust (Just 3)
True
>>> isJust (Just ())
True
>>> isJust Nothing
False

Only the outer constructor is taken into consideration:

>>> isJust (Just Nothing)
True

isNothing :: Maybe a -> Bool Source #

The isNothing function returns True iff its argument is Nothing .

Examples

Expand

Basic usage:

>>> isNothing (Just 3)
False
>>> isNothing (Just ())
False
>>> isNothing Nothing
True

Only the outer constructor is taken into consideration:

>>> isNothing (Just Nothing)
False

listToMaybe :: [a] -> Maybe a Source #

The listToMaybe function returns Nothing on an empty list or Just a where a is the first element of the list.

Examples

Expand

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]

maybeToList :: Maybe a -> [a] Source #

The maybeToList function returns an empty list when given Nothing or a singleton list when given Just .

Examples

Expand

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

Either

partitionEithers :: [ Either a b] -> ([a], [b]) Source #

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

Expand

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

lefts :: [ Either a b] -> [a] Source #

Extracts from a list of Either all the Left elements. All the Left elements are extracted in order.

Examples

Expand

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> lefts list
["foo","bar","baz"]

rights :: [ Either a b] -> [b] Source #

Extracts from a list of Either all the Right elements. All the Right elements are extracted in order.

Examples

Expand

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> rights list
[3,7]

Function

on :: (b -> b -> c) -> (a -> b) -> a -> a -> c infixl 0 Source #

on b u x y runs the binary function b on the results of applying unary function u to two arguments x and y . From the opposite perspective, it transforms two inputs and combines the outputs.

((+) `on` f) x y = f x + f y

Typical usage: sortBy ( compare `on` fst ) .

Algebraic properties:

  • (*) `on` id = (*) -- (if (*) ∉ {⊥, const ⊥})
  • ((*) `on` f) `on` g = (*) `on` (f . g)
  • flip on f . flip on g = flip on (g . f)

Applicative

(<$>) :: Functor f => (a -> b) -> f a -> f b infixl 4 Source #

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

Expand

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)

(<|>) :: Alternative f => f a -> f a -> f a infixl 3 Source #

An associative binary operation

Monad

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 Source #

Left-to-right composition of Kleisli arrows.

' (bs >=> cs) a ' can be understood as the do expression

do b <- bs a
   cs b

Exceptions

class ( Typeable e, Show e) => Exception e where Source #

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

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

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

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

Minimal complete definition

Nothing

Methods

toException :: e -> SomeException Source #

fromException :: SomeException -> Maybe e Source #

displayException :: e -> String Source #

Render this exception value in a human-friendly manner.

Default implementation: show .

Since: base-4.8.0.0

Instances

Instances details
Exception PatternMatchFail

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecSelError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecConError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception RecUpdError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NoMethodError

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception TypeError

Since: base-4.9.0.0

Instance details

Defined in Control.Exception.Base

Exception NonTermination

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception NestedAtomically

Since: base-4.0

Instance details

Defined in Control.Exception.Base

Exception BlockedIndefinitelyOnMVar

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception BlockedIndefinitelyOnSTM

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception Deadlock

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception AllocationLimitExceeded

Since: base-4.8.0.0

Instance details

Defined in GHC.IO.Exception

Exception CompactionFailed

Since: base-4.10.0.0

Instance details

Defined in GHC.IO.Exception

Exception AssertionFailed

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception SomeAsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception AsyncException

Since: base-4.7.0.0

Instance details

Defined in GHC.IO.Exception

Exception ArrayException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception FixIOException

Since: base-4.11.0.0

Instance details

Defined in GHC.IO.Exception

Exception ExitCode

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception IOException

Since: base-4.1.0.0

Instance details

Defined in GHC.IO.Exception

Exception ErrorCall

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception

Exception ArithException

Since: base-4.0.0.0

Instance details

Defined in GHC.Exception.Type

Exception SomeException

Since: base-3.0

Instance details

Defined in GHC.Exception.Type

Exception ASCII7_Invalid
Instance details

Defined in Basement.String.Encoding.ASCII7

Exception ISO_8859_1_Invalid
Instance details

Defined in Basement.String.Encoding.ISO_8859_1

Exception UTF16_Invalid
Instance details

Defined in Basement.String.Encoding.UTF16

Exception UTF32_Invalid
Instance details

Defined in Basement.String.Encoding.UTF32

Exception ValidationFailure
Instance details

Defined in Basement.UTF8.Types

Exception OutOfBound
Instance details

Defined in Basement.Exception

Exception InvalidRecast
Instance details

Defined in Basement.Exception

Exception NonEmptyCollectionIsEmpty
Instance details

Defined in Basement.Exception

Exception PartialError Source #
Instance details

Defined in Foundation.Partial

( Typeable input, Show input) => Exception ( ParseError input) Source #
Instance details

Defined in Foundation.Parser

class Typeable (a :: k) Source #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

data SomeException Source #

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 IOException Source #

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.

Proxy

data Proxy (t :: k) Source #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy

Instances

Instances details
Generic1 ( Proxy :: k -> Type )

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type Source #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a Source #

to1 :: forall (a :: k0). Rep1 Proxy a -> Proxy a Source #

Monad ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Functor ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Applicative ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Foldable ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Traversable ( Proxy :: Type -> Type )

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Alternative ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

MonadPlus ( Proxy :: Type -> Type )

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Bounded ( Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Enum ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Eq ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Data t => Data ( Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Proxy t -> c ( Proxy t) Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c ( Proxy t) Source #

toConstr :: Proxy t -> Constr Source #

dataTypeOf :: Proxy t -> DataType Source #

dataCast1 :: Typeable t0 => ( forall d. Data d => c (t0 d)) -> Maybe (c ( Proxy t)) Source #

dataCast2 :: Typeable t0 => ( forall d e. ( Data d, Data e) => c (t0 d e)) -> Maybe (c ( Proxy t)) Source #

gmapT :: ( forall b. Data b => b -> b) -> Proxy t -> Proxy t Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Proxy t -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Proxy t -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Proxy t -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Proxy t -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Proxy t -> m ( Proxy t) Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Proxy t -> m ( Proxy t) Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Proxy t -> m ( Proxy t) Source #

Ord ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Read ( Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Ix ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Generic ( Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ( Proxy t) :: Type -> Type Source #

Semigroup ( Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Monoid ( Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

type Rep1 ( Proxy :: k -> Type )
Instance details

Defined in GHC.Generics

type Rep1 ( Proxy :: k -> Type ) = D1 (' MetaData "Proxy" "Data.Proxy" "base" ' False ) ( C1 (' MetaCons "Proxy" ' PrefixI ' False ) ( U1 :: k -> Type ))
type Rep ( Proxy t)
Instance details

Defined in GHC.Generics

type Rep ( Proxy t) = D1 (' MetaData "Proxy" "Data.Proxy" "base" ' False ) ( C1 (' MetaCons "Proxy" ' PrefixI ' False ) ( U1 :: Type -> Type ))

asProxyTypeOf :: a -> proxy a -> a Source #

asProxyTypeOf is a type-restricted version of const . It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

>>> import Data.Word
>>> :type asProxyTypeOf 123 (Proxy :: Proxy Word8)
asProxyTypeOf 123 (Proxy :: Proxy Word8) :: Word8

Note the lower-case proxy in the definition. This allows any type constructor with just one argument to be passed to the function, for example we could also write

>>> import Data.Word
>>> :type asProxyTypeOf 123 (Just (undefined :: Word8))
asProxyTypeOf 123 (Just (undefined :: Word8)) :: Word8

Partial

partial :: a -> Partial a Source #

Create a value that is partial. this can only be unwrap using the fromPartial function

fromPartial :: Partial a -> a Source #

Dewrap a possible partial value

ifThenElse :: Bool -> a -> a -> a Source #

for support of if .. then .. else

Old Prelude Strings as [Char] with bridge back and forth

type LString = String Source #

Alias to Prelude String ([Char]) for compatibility purpose