License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Foundation
Contents
Description
I tried to picture clusters of information As they moved through the computer What do they look like?
Alternative Prelude
Synopsis
- ($) :: (a -> b) -> a -> b
- ($!) :: (a -> b) -> a -> b
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- (.) :: Category cat => cat b c -> cat a b -> cat a c
- not :: Bool -> Bool
- otherwise :: Bool
- data Tuple2 a b = Tuple2 !a !b
- data Tuple3 a b c = Tuple3 !a !b !c
- data Tuple4 a b c d = Tuple4 !a !b !c !d
- class Fstable a where
- type ProductFirst a
- fst :: a -> ProductFirst a
- class Sndable a where
- type ProductSecond a
- snd :: a -> ProductSecond a
- class Thdable a where
- type ProductThird a
- thd :: a -> ProductThird a
- id :: Category cat => cat a a
- maybe :: b -> (a -> b) -> Maybe a -> b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- flip :: (a -> b -> c) -> b -> a -> c
- const :: a -> b -> a
- error :: HasCallStack => String -> a
- putStr :: String -> IO ()
- putStrLn :: String -> IO ()
- getArgs :: IO [String]
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- swap :: (a, b) -> (b, a)
- until :: (a -> Bool) -> (a -> a) -> a -> a
- asTypeOf :: a -> a -> a
- undefined :: HasCallStack => a
- seq :: a -> b -> b
- class NormalForm a
- deepseq :: NormalForm a => a -> b -> b
- force :: NormalForm a => a -> a
- class Show a
- show :: Show a => a -> String
- class Eq a => Ord a where
- class Eq a where
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Functor (f :: Type -> Type) where
- class Integral a where
- fromInteger :: Integer -> a
- class Fractional a where
- fromRational :: Rational -> a
- class HasNegation a where
- negate :: a -> a
- class Bifunctor (p :: Type -> Type -> Type) where
- class Functor f => Applicative (f :: Type -> Type) where
- class Applicative m => Monad (m :: Type -> Type) where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- class IsString a where
- fromString :: String -> a
- class IsList l where
- class (Integral a, Eq a, Ord a) => IsIntegral a where
- class IsIntegral a => IsNatural a where
- class Signed a where
- class Additive a where
- class Subtractive a where
- type Difference a :: Type
- (-) :: a -> a -> Difference a
- class Multiplicative a where
- class (Additive a, Multiplicative a) => IDivisible a where
- class Multiplicative a => Divisible a where
- (/) :: a -> a -> a
- data Maybe a
- data Ordering
- data Bool
- data Char
- data Char7
- data IO a
- data Either a b
- data Int8
- data Int16
- data Int32
- data Int64
- data Word8
- data Word16
- data Word32
- data Word64
- data Word
- data Word128
- data Word256
- data Int
- data Integer
- data Natural
- type Rational = Ratio Integer
- data Float
- data Double
- newtype CountOf ty = CountOf Int
- newtype Offset ty = Offset Int
- toCount :: Int -> CountOf ty
- fromCount :: CountOf ty -> Int
- data UArray ty
- class Eq ty => PrimType ty
- data Array a
- data String
- (^^) :: (Fractional a, Integral b) => a -> b -> a
- fromIntegral :: (Integral a, Num b) => a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Semigroup a
- class Semigroup a => Monoid a where
- (<>) :: Semigroup a => a -> a -> a
- class (IsList c, Item c ~ Element c) => Collection c where
- null :: c -> Bool
- length :: c -> CountOf (Element c)
- elem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
- notElem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool
- maximum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
- minimum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c
- any :: (Element c -> Bool) -> c -> Bool
- all :: (Element c -> Bool) -> c -> Bool
- and :: (Collection col, Element col ~ Bool) => col -> Bool
- or :: (Collection col, Element col ~ Bool) => col -> Bool
- class (IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where
- take :: CountOf (Element c) -> c -> c
- revTake :: CountOf (Element c) -> c -> c
- drop :: CountOf (Element c) -> c -> c
- revDrop :: CountOf (Element c) -> c -> c
- splitAt :: CountOf (Element c) -> c -> (c, c)
- revSplitAt :: CountOf (Element c) -> c -> (c, c)
- splitOn :: (Element c -> Bool) -> c -> [c]
- break :: (Element c -> Bool) -> c -> (c, c)
- breakEnd :: (Element c -> Bool) -> c -> (c, c)
- breakElem :: Eq (Element c) => Element c -> c -> (c, c)
- takeWhile :: (Element c -> Bool) -> c -> c
- dropWhile :: (Element c -> Bool) -> c -> c
- intersperse :: Element c -> c -> c
- intercalate :: Monoid (Item c) => Element c -> c -> Element c
- span :: (Element c -> Bool) -> c -> (c, c)
- spanEnd :: (Element c -> Bool) -> c -> (c, c)
- filter :: (Element c -> Bool) -> c -> c
- partition :: (Element c -> Bool) -> c -> (c, c)
- reverse :: c -> c
- uncons :: c -> Maybe (Element c, c)
- unsnoc :: c -> Maybe (c, Element c)
- snoc :: c -> Element c -> c
- cons :: Element c -> c -> c
- find :: (Element c -> Bool) -> c -> Maybe (Element c)
- sortBy :: (Element c -> Element c -> Ordering) -> c -> c
- singleton :: Element c -> c
- head :: NonEmpty c -> Element c
- last :: NonEmpty c -> Element c
- tail :: NonEmpty c -> c
- init :: NonEmpty c -> c
- replicate :: CountOf (Element c) -> Element c -> c
- isPrefixOf :: Eq (Element c) => c -> c -> Bool
- isSuffixOf :: Eq (Element c) => c -> c -> Bool
- isInfixOf :: Eq (Element c) => c -> c -> Bool
- stripPrefix :: Eq (Element c) => c -> c -> Maybe c
- stripSuffix :: Eq (Element c) => c -> c -> Maybe c
- data NonEmpty a
- nonEmpty :: Collection c => c -> Maybe (NonEmpty c)
- class Foldable collection where
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- catMaybes :: [Maybe a] -> [a]
- fromMaybe :: a -> Maybe a -> a
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- listToMaybe :: [a] -> Maybe a
- maybeToList :: Maybe a -> [a]
- partitionEithers :: [Either a b] -> ([a], [b])
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- on :: (b -> b -> c) -> (a -> b) -> a -> a -> c
- (<$>) :: Functor f => (a -> b) -> f a -> f b
- (<|>) :: Alternative f => f a -> f a -> f a
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
- displayException :: e -> String
- class Typeable (a :: k)
- data SomeException
- data IOException
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
- asProxyTypeOf :: a -> proxy a -> a
- data Partial a
- partial :: a -> Partial a
- data PartialError
- fromPartial :: Partial a -> a
- ifThenElse :: Bool -> a -> a -> a
- type LString = String
Standard
Operators
Functions
Strict tuple (a,b)
Constructors
Tuple2 !a !b |
Instances
Bifunctor Tuple2 Source # | |
Nthable 1 (Tuple2 a b) Source # | |
Nthable 2 (Tuple2 a b) Source # | |
(Eq a, Eq b) => Eq (Tuple2 a b) Source # | |
(Data a, Data b) => Data (Tuple2 a b) Source # | |
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) gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tuple2 a b) toConstr :: Tuple2 a b -> Constr dataTypeOf :: Tuple2 a b -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Tuple2 a b)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Tuple2 a b)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tuple2 a b -> Tuple2 a b gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tuple2 a b -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tuple2 a b -> r gmapQ :: (forall d. Data d => d -> u) -> Tuple2 a b -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Tuple2 a b -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple2 a b -> m (Tuple2 a b) | |
(Ord a, Ord b) => Ord (Tuple2 a b) Source # | |
(Show a, Show b) => Show (Tuple2 a b) Source # | |
Generic (Tuple2 a b) Source # | |
(NormalForm a, NormalForm b) => NormalForm (Tuple2 a b) Source # | |
Defined in Foundation.Tuple Methods toNormalForm :: Tuple2 a b -> () # | |
Sndable (Tuple2 a b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple2 a b) :: Type Source # | |
Fstable (Tuple2 a b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple2 a b) :: Type Source # | |
(Hashable a, Hashable b) => Hashable (Tuple2 a b) Source # | |
type NthTy 1 (Tuple2 a b) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 2 (Tuple2 a b) Source # | |
Defined in Foundation.Tuple.Nth | |
type Rep (Tuple2 a b) Source # | |
Defined in Foundation.Tuple type Rep (Tuple2 a b) = D1 (MetaData "Tuple2" "Foundation.Tuple" "foundation-0.0.25-3BrSZNf3UlK9iHqaZVzvLG" False) (C1 (MetaCons "Tuple2" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b))) | |
type ProductSecond (Tuple2 a b) Source # | |
Defined in Foundation.Tuple | |
type ProductFirst (Tuple2 a b) Source # | |
Defined in Foundation.Tuple |
Strict tuple (a,b,c)
Constructors
Tuple3 !a !b !c |
Instances
Nthable 1 (Tuple3 a b c) Source # | |
Nthable 2 (Tuple3 a b c) Source # | |
Nthable 3 (Tuple3 a b c) Source # | |
(Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) Source # | |
(Data a, Data b, Data c) => Data (Tuple3 a b c) Source # | |
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) gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Tuple3 a b c) toConstr :: Tuple3 a b c -> Constr dataTypeOf :: Tuple3 a b c -> DataType dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Tuple3 a b c)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Tuple3 a b c)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tuple3 a b c -> Tuple3 a b c gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tuple3 a b c -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tuple3 a b c -> r gmapQ :: (forall d. Data d => d -> u) -> Tuple3 a b c -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Tuple3 a b c -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tuple3 a b c -> m (Tuple3 a b c) | |
(Ord a, Ord b, Ord c) => Ord (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple | |
(Show a, Show b, Show c) => Show (Tuple3 a b c) Source # | |
Generic (Tuple3 a b c) Source # | |
(NormalForm a, NormalForm b, NormalForm c) => NormalForm (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Methods toNormalForm :: Tuple3 a b c -> () # | |
Thdable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (Tuple3 a b c) :: Type Source # | |
Sndable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple3 a b c) :: Type Source # | |
Fstable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple3 a b c) :: Type Source # | |
(Hashable a, Hashable b, Hashable c) => Hashable (Tuple3 a b c) Source # | |
type NthTy 1 (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 2 (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 3 (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple.Nth | |
type Rep (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple type Rep (Tuple3 a b c) = D1 (MetaData "Tuple3" "Foundation.Tuple" "foundation-0.0.25-3BrSZNf3UlK9iHqaZVzvLG" False) (C1 (MetaCons "Tuple3" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 c)))) | |
type ProductThird (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple | |
type ProductSecond (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple | |
type ProductFirst (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple |
Strict tuple (a,b,c,d)
Constructors
Tuple4 !a !b !c !d |
Instances
Nthable 1 (Tuple4 a b c d) Source # | |
Nthable 2 (Tuple4 a b c d) Source # | |
Nthable 3 (Tuple4 a b c d) Source # | |
Nthable 4 (Tuple4 a b c d) Source # | |
(Eq a, Eq b, Eq c, Eq d) => Eq (Tuple4 a b c d) Source # | |
(Data a, Data b, Data c, Data d) => Data (Tuple4 a b c d) Source # | |
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) gunfold :: (forall b0 r. Data b0 => c0 (b0 -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Tuple4 a b c d) toConstr :: Tuple4 a b c d -> Constr dataTypeOf :: Tuple4 a b c d -> DataType dataCast1 :: Typeable t => (forall d0. Data d0 => c0 (t d0)) -> Maybe (c0 (Tuple4 a b c d)) dataCast2 :: Typeable t => (forall d0 e. (Data d0, Data e) => c0 (t d0 e)) -> Maybe (c0 (Tuple4 a b c d)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> Tuple4 a b c d -> Tuple4 a b c d gmapQl :: (r -> r' -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Tuple4 a b c d -> r gmapQr :: (r' -> r -> r) -> r -> (forall d0. Data d0 => d0 -> r') -> Tuple4 a b c d -> r gmapQ :: (forall d0. Data d0 => d0 -> u) -> Tuple4 a b c d -> [u] gmapQi :: Int -> (forall d0. Data d0 => d0 -> u) -> Tuple4 a b c d -> u gmapM :: Monad m => (forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m (Tuple4 a b c d) gmapMp :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m (Tuple4 a b c d) gmapMo :: MonadPlus m => (forall d0. Data d0 => d0 -> m d0) -> Tuple4 a b c d -> m (Tuple4 a b c d) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Methods compare :: Tuple4 a b c d -> Tuple4 a b c d -> Ordering # (<) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (<=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (>) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (>=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # | |
(Show a, Show b, Show c, Show d) => Show (Tuple4 a b c d) Source # | |
Generic (Tuple4 a b c d) Source # | |
(NormalForm a, NormalForm b, NormalForm c, NormalForm d) => NormalForm (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Methods toNormalForm :: Tuple4 a b c d -> () # | |
Thdable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (Tuple4 a b c d) :: Type Source # | |
Sndable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple4 a b c d) :: Type Source # | |
Fstable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple4 a b c d) :: Type Source # | |
(Hashable a, Hashable b, Hashable c, Hashable d) => Hashable (Tuple4 a b c d) Source # | |
type NthTy 1 (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 2 (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 3 (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple.Nth | |
type NthTy 4 (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple.Nth | |
type Rep (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple type Rep (Tuple4 a b c d) = D1 (MetaData "Tuple4" "Foundation.Tuple" "foundation-0.0.25-3BrSZNf3UlK9iHqaZVzvLG" False) (C1 (MetaCons "Tuple4" PrefixI False) ((S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 b)) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 c) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 d)))) | |
type ProductThird (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple | |
type ProductSecond (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple | |
type ProductFirst (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple |
class Fstable a where Source #
Class of product types that have a first element
Associated Types
type ProductFirst a Source #
Methods
fst :: a -> ProductFirst a Source #
Instances
Fstable (a, b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (a, b) :: Type Source # Methods fst :: (a, b) -> ProductFirst (a, b) Source # | |
Fstable (Tuple2 a b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple2 a b) :: Type Source # | |
Fstable (a, b, c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (a, b, c) :: Type Source # Methods fst :: (a, b, c) -> ProductFirst (a, b, c) Source # | |
Fstable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple3 a b c) :: Type Source # | |
Fstable (a, b, c, d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (a, b, c, d) :: Type Source # Methods fst :: (a, b, c, d) -> ProductFirst (a, b, c, d) Source # | |
Fstable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductFirst (Tuple4 a b c d) :: Type Source # |
class Sndable a where Source #
Class of product types that have a second element
Associated Types
type ProductSecond a Source #
Methods
snd :: a -> ProductSecond a Source #
Instances
Sndable (a, b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (a, b) :: Type Source # Methods snd :: (a, b) -> ProductSecond (a, b) Source # | |
Sndable (Tuple2 a b) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple2 a b) :: Type Source # | |
Sndable (a, b, c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (a, b, c) :: Type Source # Methods snd :: (a, b, c) -> ProductSecond (a, b, c) Source # | |
Sndable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple3 a b c) :: Type Source # | |
Sndable (a, b, c, d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (a, b, c, d) :: Type Source # Methods snd :: (a, b, c, d) -> ProductSecond (a, b, c, d) Source # | |
Sndable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductSecond (Tuple4 a b c d) :: Type Source # |
class Thdable a where Source #
Class of product types that have a third element
Associated Types
type ProductThird a Source #
Methods
thd :: a -> ProductThird a Source #
Instances
Thdable (a, b, c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (a, b, c) :: Type Source # Methods thd :: (a, b, c) -> ProductThird (a, b, c) Source # | |
Thdable (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (Tuple3 a b c) :: Type Source # | |
Thdable (a, b, c, d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (a, b, c, d) :: Type Source # Methods thd :: (a, b, c, d) -> ProductThird (a, b, c, d) Source # | |
Thdable (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Associated Types type ProductThird (Tuple4 a b c d) :: Type Source # |
class NormalForm a #
Minimal complete definition
Instances
deepseq :: NormalForm a => a -> b -> b #
force :: NormalForm a => a -> a #
Type classes
Minimal complete definition
showsPrec | show
Instances
Show Bool | |
Show Char | |
Show Int | |
Show Int8 | |
Show Int16 | |
Show Int32 | |
Show Int64 | |
Show Integer | |
Show Natural | |
Show Ordering | |
Show Word | |
Show Word8 | |
Show Word16 | |
Show Word32 | |
Show Word64 | |
Show RuntimeRep | |
Show VecCount | |
Show VecElem | |
Show CallStack | |
Show SomeTypeRep | |
Defined in Data.Typeable.Internal | |
Show () | |
Show TyCon | |
Show Module | |
Show TrName | |
Show KindRep | |
Show TypeLitSort | |
Show OutOfBound | |
Defined in Basement.Exception Methods showsPrec :: Int -> OutOfBound -> ShowS show :: OutOfBound -> String showList :: [OutOfBound] -> ShowS | |
Show Constr | |
Show SrcLoc | |
Show CInt | |
Defined in Foreign.C.Types | |
Show DataType | |
Show FileSize | |
Defined in Basement.Types.OffsetSize | |
Show CSize | |
Defined in Foreign.C.Types | |
Show CSsize | |
Defined in System.Posix.Types | |
Show CChar | |
Defined in Foreign.C.Types | |
Show CUChar | |
Defined in Foreign.C.Types | |
Show Word128 | |
Show Word256 | |
Show Char7 | |
Show Encoding | |
Show String | |
Show ValidationFailure | |
Defined in Basement.UTF8.Types Methods showsPrec :: Int -> ValidationFailure -> ShowS show :: ValidationFailure -> String showList :: [ValidationFailure] -> ShowS | |
Show ConstrRep | |
Show DataRep | |
Show Version | |
Show Associativity | |
Defined in GHC.Generics | |
Show DecidedStrictness | |
Defined in GHC.Generics | |
Show Fixity | |
Defined in GHC.Generics | |
Show SourceStrictness | |
Defined in GHC.Generics | |
Show SourceUnpackedness | |
Defined in GHC.Generics | |
Show ASCII7_Invalid | |
Defined in Basement.String.Encoding.ASCII7 | |
Show SomeException | |
Defined in GHC.Exception.Type Methods showsPrec :: Int -> SomeException -> ShowS show :: SomeException -> String showList :: [SomeException] -> ShowS | |
Show ISO_8859_1_Invalid | |
Defined in Basement.String.Encoding.ISO_8859_1 | |
Show UTF16_Invalid | |
Defined in Basement.String.Encoding.UTF16 | |
Show UTF32_Invalid | |
Defined in Basement.String.Encoding.UTF32 | |
Show SomeNat | |
Defined in GHC.TypeNats | |
Show SomeSymbol | |
Defined in GHC.TypeLits | |
Show AsciiString | |
Defined in Basement.Types.AsciiString Methods showsPrec :: Int -> AsciiString -> ShowS show :: AsciiString -> String showList :: [AsciiString] -> ShowS | |
Show InvalidRecast | |
Defined in Basement.Exception | |
Show NonEmptyCollectionIsEmpty | |
Defined in Basement.Exception | |
Show OutOfBoundOperation | |
Defined in Basement.Exception | |
Show RecastDestinationSize | |
Defined in Basement.Exception | |
Show RecastSourceSize | |
Defined in Basement.Exception | |
Show Any | |
Defined in Data.Semigroup.Internal | |
Show All | |
Defined in Data.Semigroup.Internal | |
Show CDouble | |
Defined in Foreign.C.Types | |
Show CFloat | |
Defined in Foreign.C.Types | |
Show CIntMax | |
Defined in Foreign.C.Types | |
Show CLLong | |
Defined in Foreign.C.Types | |
Show CLong | |
Defined in Foreign.C.Types | |
Show CPtrdiff | |
Defined in Foreign.C.Types | |
Show CSChar | |
Defined in Foreign.C.Types | |
Show CShort | |
Defined in Foreign.C.Types | |
Show CWchar | |
Defined in Foreign.C.Types | |
Show CBool | |
Defined in Foreign.C.Types | |
Show CClock | |
Defined in Foreign.C.Types | |
Show CIntPtr | |
Defined in Foreign.C.Types | |
Show COff | |
Defined in System.Posix.Types | |
Show CSUSeconds | |
Defined in Foreign.C.Types | |
Show CSigAtomic | |
Defined in Foreign.C.Types | |
Show CTime | |
Defined in Foreign.C.Types | |
Show CUInt | |
Defined in Foreign.C.Types | |
Show CUIntMax | |
Defined in Foreign.C.Types | |
Show CUIntPtr | |
Defined in Foreign.C.Types | |
Show CULLong | |
Defined in Foreign.C.Types | |
Show CULong | |
Defined in Foreign.C.Types | |
Show CUSeconds | |
Defined in Foreign.C.Types | |
Show CUShort | |
Defined in Foreign.C.Types | |
Show IntPtr | |
Defined in Foreign.Ptr | |
Show ErrorCall | |
Defined in GHC.Exception | |
Show ArithException | |
Defined in GHC.Exception.Type | |
Show CMode | |
Defined in System.Posix.Types | |
Show IOException | |
Defined in GHC.IO.Exception Methods showsPrec :: Int -> IOException -> ShowS show :: IOException -> String showList :: [IOException] -> ShowS | |
Show Handle | |
Defined in GHC.IO.Handle.Types | |
Show SeekMode | |
Defined in GHC.IO.Device | |
Show TextEncoding | |
Defined in GHC.IO.Encoding.Types | |
Show HandlePosn | |
Defined in GHC.IO.Handle | |
Show BufferMode | |
Defined in GHC.IO.Handle.Types | |
Show Newline | |
Defined in GHC.IO.Handle.Types | |
Show NewlineMode | |
Defined in GHC.IO.Handle.Types | |
Show IOMode | |
Show BlockedIndefinitelyOnMVar | |
Defined in GHC.IO.Exception | |
Show ExitCode | |
Defined in GHC.IO.Exception | |
Show CDev | |
Defined in System.Posix.Types | |
Show CIno | |
Defined in System.Posix.Types | |
Show FD | |
Show HandleType | |
Defined in GHC.IO.Handle.Types | |
Show NestedAtomically | |
Defined in Control.Exception.Base | |
Show NoMethodError | |
Defined in Control.Exception.Base | |
Show NonTermination | |
Defined in Control.Exception.Base | |
Show PatternMatchFail | |
Defined in Control.Exception.Base | |
Show RecConError | |
Defined in Control.Exception.Base | |
Show RecSelError | |
Defined in Control.Exception.Base | |
Show RecUpdError | |
Defined in Control.Exception.Base | |
Show TypeError | |
Defined in Control.Exception.Base | |
Show MaskingState | |
Show AllocationLimitExceeded | |
Defined in GHC.IO.Exception | |
Show ArrayException | |
Defined in GHC.IO.Exception | |
Show AssertionFailed | |
Defined in GHC.IO.Exception | |
Show AsyncException | |
Defined in GHC.IO.Exception | |
Show BlockedIndefinitelyOnSTM | |
Defined in GHC.IO.Exception | |
Show CompactionFailed | |
Defined in GHC.IO.Exception | |
Show Deadlock | |
Defined in GHC.IO.Exception | |
Show SomeAsyncException | |
Defined in GHC.IO.Exception | |
Show FixIOException | |
Defined in GHC.IO.Exception | |
Show IOErrorType | |
Defined in GHC.IO.Exception | |
Show CBlkCnt | |
Defined in System.Posix.Types | |
Show CBlkSize | |
Defined in System.Posix.Types | |
Show CCc | |
Defined in System.Posix.Types | |
Show CClockId | |
Defined in System.Posix.Types | |
Show CFsBlkCnt | |
Defined in System.Posix.Types | |
Show CFsFilCnt | |
Defined in System.Posix.Types | |
Show CGid | |
Defined in System.Posix.Types | |
Show CId | |
Defined in System.Posix.Types | |
Show CKey | |
Defined in System.Posix.Types | |
Show CNlink | |
Defined in System.Posix.Types | |
Show CPid | |
Defined in System.Posix.Types | |
Show CRLim | |
Defined in System.Posix.Types | |
Show CSpeed | |
Defined in System.Posix.Types | |
Show CTcflag | |
Defined in System.Posix.Types | |
Show CTimer | |
Defined in System.Posix.Types | |
Show CUid | |
Defined in System.Posix.Types | |
Show Fd | |
Defined in System.Posix.Types | |
Show Endianness | |
Defined in Basement.Endianness Methods showsPrec :: Int -> Endianness -> ShowS show :: Endianness -> String showList :: [Endianness] -> ShowS | |
Show WordPtr | |
Defined in Foreign.Ptr | |
Show Bitmap Source # | |
Show PartialError Source # | |
Defined in Foundation.Partial Methods showsPrec :: Int -> PartialError -> ShowS show :: PartialError -> String showList :: [PartialError] -> ShowS | |
Show And Source # | |
Show Condition Source # | |
Show GeneralCategory | |
Defined in GHC.Unicode | |
Show CSV Source # | |
Show Row Source # | |
Show Escaping Source # | |
Show Field Source # | |
Show Fixity | |
Show BlockReason | |
Defined in GHC.Conc.Sync | |
Show ThreadId | |
Defined in GHC.Conc.Sync | |
Show ThreadStatus | |
Defined in GHC.Conc.Sync | |
Show Arch Source # | |
Show OS Source # | |
Show Seconds Source # | |
Show NanoSeconds Source # | |
Defined in Foundation.Time.Types Methods showsPrec :: Int -> NanoSeconds -> ShowS show :: NanoSeconds -> String showList :: [NanoSeconds] -> ShowS | |
Show GCDetails | |
Show RTSStats | |
Show IPv6 Source # | |
Show IPv4 Source # | |
Show UUID Source # | |
Show FileName Source # | |
Show FilePath Source # | |
Show Relativity Source # | |
Defined in Foundation.VFS.FilePath Methods showsPrec :: Int -> Relativity -> ShowS show :: Relativity -> String showList :: [Relativity] -> ShowS | |
Show CodingProgress | |
Defined in GHC.IO.Encoding.Types | |
Show a => Show [a] | |
Show a => Show (Maybe a) | |
Show a => Show (Ratio a) | |
Show (Ptr a) | |
Show (FunPtr a) | |
Show p => Show (Par1 p) | |
Defined in GHC.Generics | |
(PrimType ty, Show ty) => Show (UArray ty) | |
Show (Offset ty) | |
(PrimType ty, Show ty) => Show (Block ty) | |
Show (CountOf ty) | |
Show (ForeignPtr a) | |
Defined in GHC.ForeignPtr | |
Show a => Show (NonEmpty a) | |
Show (FinalPtr a) | |
Defined in Basement.FinalPtr | |
Show a => Show (NonEmpty a) | |
Show a => Show (BE a) | |
Show a => Show (LE a) | |
Show a => Show (Array a) | |
Show a => Show (Down a) | |
Show a => Show (Dual a) | |
Defined in Data.Semigroup.Internal | |
Show a => Show (Product a) | |
Defined in Data.Semigroup.Internal | |
Show a => Show (Sum a) | |
Defined in Data.Semigroup.Internal | |
Show a => Show (First a) | |
Defined in Data.Monoid | |
Show a => Show (Last a) | |
Defined in Data.Monoid | |
Show (Zn n) | |
Defined in Basement.Bounded | |
Show (Zn64 n) | |
Defined in Basement.Bounded | |
Show a => Show (Identity a) | |
Show a => Show (ZipList a) | |
Defined in Control.Applicative | |
Show a => Show (First a) | |
Defined in Data.Semigroup | |
Show a => Show (Last a) | |
Defined in Data.Semigroup | |
Show a => Show (Max a) | |
Defined in Data.Semigroup | |
Show a => Show (Min a) | |
Defined in Data.Semigroup | |
Show a => Show (Option a) | |
Defined in Data.Semigroup | |
Show m => Show (WrappedMonoid m) | |
Defined in Data.Semigroup | |
Show a => Show (DList a) Source # | |
(PrimType ty, Show ty) => Show (ChunkedUArray ty) Source # | |
Defined in Foundation.Array.Chunked.Unboxed Methods showsPrec :: Int -> ChunkedUArray ty -> ShowS show :: ChunkedUArray ty -> String showList :: [ChunkedUArray ty] -> ShowS | |
Show input => Show (ParseError input) Source # | |
Defined in Foundation.Parser Methods showsPrec :: Int -> ParseError input -> ShowS show :: ParseError input -> String showList :: [ParseError input] -> ShowS | |
Show (ParseError String) Source # | |
Defined in Foundation.Parser Methods showsPrec :: Int -> ParseError String -> ShowS show :: ParseError String -> String0 showList :: [ParseError String] -> ShowS | |
Show (Bits n) | |
Defined in Basement.Bits | |
(Show a, Show b) => Show (Either a b) | |
Show (V1 p) | |
Defined in GHC.Generics | |
Show (U1 p) | |
Defined in GHC.Generics | |
Show (TypeRep a) | |
Defined in Data.Typeable.Internal | |
(Show a, Show b) => Show (a, b) | |
Show (ST s a) | |
Show (Proxy s) | |
(Ix a, Show a, Show b) => Show (Array a b) | |
(PrimType a, Show a) => Show (BlockN n a) | |
Defined in Basement.Sized.Block | |
Show a => Show (ListN n a) | |
Defined in Basement.Sized.List | |
(Show a, Show b) => Show (Arg a b) | |
Defined in Data.Semigroup | |
(Show a, Show b) => Show (These a b) | |
(Show k, Show input) => Show (Result input k) Source # | |
(Show a, Show b) => Show (Tuple2 a b) Source # | |
Show (f p) => Show (Rec1 f p) | |
Defined in GHC.Generics | |
Show (URec Char p) | |
Show (URec Double p) | |
Show (URec Float p) | |
Show (URec Int p) | |
Show (URec Word p) | |
(Show a, Show b, Show c) => Show (a, b, c) | |
Show a => Show (Const a b) | |
Defined in Data.Functor.Const | |
Show (a :~: b) | |
Defined in Data.Type.Equality | |
Show (Coercion a b) | |
Defined in Data.Type.Coercion | |
Show (f a) => Show (Alt f a) | |
Defined in Data.Semigroup.Internal | |
Show (f a) => Show (Ap f a) | |
Defined in Data.Monoid | |
(Show a, Show b, Show c) => Show (Tuple3 a b c) Source # | |
Show c => Show (K1 i c p) | |
Defined in GHC.Generics | |
(Show (f p), Show (g p)) => Show ((f :+: g) p) | |
Defined in GHC.Generics | |
(Show (f p), Show (g p)) => Show ((f :*: g) p) | |
Defined in GHC.Generics | |
(Show a, Show b, Show c, Show d) => Show (a, b, c, d) | |
Show (a :~~: b) | |
Defined in Data.Type.Equality | |
(Show a, Show b, Show c, Show d) => Show (Tuple4 a b c d) Source # | |
Show (f p) => Show (M1 i c f p) | |
Defined in GHC.Generics | |
Show (f (g p)) => Show ((f :.: g) p) | |
Defined in GHC.Generics | |
(Show a, Show b, Show c, Show d, Show e) => Show (a, b, c, d, e) | |
(Show a, Show b, Show c, Show d, Show e, Show f) => Show (a, b, c, d, e, f) | |
(Show a, Show b, Show c, Show d, Show e, Show f, Show g) => Show (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
Instances
Ord Bool | |
Ord Char | |
Ord Double | |
Ord Float | |
Ord Int | |
Ord Int8 | |
Ord Int16 | |
Ord Int32 | |
Ord Int64 | |
Ord Integer | |
Ord Natural | |
Ord Ordering | |
Defined in GHC.Classes | |
Ord Word | |
Ord Word8 | |
Ord Word16 | |
Ord Word32 | |
Ord Word64 | |
Ord SomeTypeRep | |
Defined in Data.Typeable.Internal | |
Ord () | |
Ord TyCon | |
Ord CInt | |
Ord FileSize | |
Defined in Basement.Types.OffsetSize | |
Ord CSize | |
Ord CSsize | |
Ord CChar | |
Ord CUChar | |
Ord Word128 | |
Defined in Basement.Types.Word128 | |
Ord Word256 | |
Defined in Basement.Types.Word256 | |
Ord Char7 | |
Ord Encoding | |
Defined in Basement.String | |
Ord String | |
Ord Version | |
Ord Associativity | |
Defined in GHC.Generics Methods compare :: Associativity -> Associativity -> Ordering # (<) :: Associativity -> Associativity -> Bool # (<=) :: Associativity -> Associativity -> Bool # (>) :: Associativity -> Associativity -> Bool # (>=) :: Associativity -> Associativity -> Bool # | |
Ord DecidedStrictness | |
Defined in GHC.Generics Methods compare :: DecidedStrictness -> DecidedStrictness -> Ordering # (<) :: DecidedStrictness -> DecidedStrictness -> Bool # (<=) :: DecidedStrictness -> DecidedStrictness -> Bool # (>) :: DecidedStrictness -> DecidedStrictness -> Bool # (>=) :: DecidedStrictness -> DecidedStrictness -> Bool # max :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # min :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness # | |
Ord Fixity | |
Ord SourceStrictness | |
Defined in GHC.Generics Methods compare :: SourceStrictness -> SourceStrictness -> Ordering # (<) :: SourceStrictness -> SourceStrictness -> Bool # (<=) :: SourceStrictness -> SourceStrictness -> Bool # (>) :: SourceStrictness -> SourceStrictness -> Bool # (>=) :: SourceStrictness -> SourceStrictness -> Bool # max :: SourceStrictness -> SourceStrictness -> SourceStrictness # min :: SourceStrictness -> SourceStrictness -> SourceStrictness # | |
Ord SourceUnpackedness | |
Defined in GHC.Generics Methods compare :: SourceUnpackedness -> SourceUnpackedness -> Ordering # (<) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (<=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>) :: SourceUnpackedness -> SourceUnpackedness -> Bool # (>=) :: SourceUnpackedness -> SourceUnpackedness -> Bool # max :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # min :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness # | |
Ord UTF32_Invalid | |
Defined in Basement.String.Encoding.UTF32 Methods compare :: UTF32_Invalid -> UTF32_Invalid -> Ordering # (<) :: UTF32_Invalid -> UTF32_Invalid -> Bool # (<=) :: UTF32_Invalid -> UTF32_Invalid -> Bool # (>) :: UTF32_Invalid -> UTF32_Invalid -> Bool # (>=) :: UTF32_Invalid -> UTF32_Invalid -> Bool # | |
Ord SomeNat | |
Ord SomeSymbol | |
Ord BigNat | |
Ord AsciiString | |
Defined in Basement.Types.AsciiString Methods compare :: AsciiString -> AsciiString -> Ordering # (<) :: AsciiString -> AsciiString -> Bool # (<=) :: AsciiString -> AsciiString -> Bool # (>) :: AsciiString -> AsciiString -> Bool # (>=) :: AsciiString -> AsciiString -> Bool # max :: AsciiString -> AsciiString -> AsciiString # min :: AsciiString -> AsciiString -> AsciiString # | |
Ord Any | |
Ord All | |
Ord CDouble | |
Ord CFloat | |
Ord CIntMax | |
Ord CLLong | |
Ord CLong | |
Ord CPtrdiff | |
Defined in Foreign.C.Types | |
Ord CSChar | |
Ord CShort | |
Ord CWchar | |
Ord CBool | |
Ord CClock | |
Ord CIntPtr | |
Ord COff | |
Ord CSUSeconds | |
Ord CSigAtomic | |
Ord CTime | |
Ord CUInt | |
Ord CUIntMax | |
Defined in Foreign.C.Types | |
Ord CUIntPtr | |
Defined in Foreign.C.Types | |
Ord CULLong | |
Ord CULong | |
Ord CUSeconds | |
Ord CUShort | |
Ord IntPtr | |
Ord ErrorCall | |
Ord ArithException | |
Defined in GHC.Exception.Type Methods compare :: ArithException -> ArithException -> Ordering # (<) :: ArithException -> ArithException -> Bool # (<=) :: ArithException -> ArithException -> Bool # (>) :: ArithException -> ArithException -> Bool # (>=) :: ArithException -> ArithException -> Bool # | |
Ord CMode | |
Ord SeekMode | |
Defined in GHC.IO.Device | |
Ord BufferMode | |
Defined in GHC.IO.Handle.Types | |
Ord Newline | |
Ord NewlineMode | |
Defined in GHC.IO.Handle.Types | |
Ord IOMode | |
Ord ExitCode | |
Defined in GHC.IO.Exception | |
Ord CDev | |
Ord CIno | |
Ord ArrayException | |
Defined in GHC.IO.Exception Methods compare :: ArrayException -> ArrayException -> Ordering # (<) :: ArrayException -> ArrayException -> Bool # (<=) :: ArrayException -> ArrayException -> Bool # (>) :: ArrayException -> ArrayException -> Bool # (>=) :: ArrayException -> ArrayException -> Bool # | |
Ord AsyncException | |
Defined in GHC.IO.Exception Methods compare :: AsyncException -> AsyncException -> Ordering # (<) :: AsyncException -> AsyncException -> Bool # (<=) :: AsyncException -> AsyncException -> Bool # (>) :: AsyncException -> AsyncException -> Bool # (>=) :: AsyncException -> AsyncException -> Bool # | |
Ord CBlkCnt | |
Ord CBlkSize | |
Defined in System.Posix.Types | |
Ord CCc | |
Ord CClockId | |
Defined in System.Posix.Types | |
Ord CFsBlkCnt | |
Ord CFsFilCnt | |
Ord CGid | |
Ord CId | |
Ord CKey | |
Ord CNlink | |
Ord CPid | |
Ord CRLim | |
Ord CSpeed | |
Ord CTcflag | |
Ord CTimer | |
Ord CUid | |
Ord Fd | |
Ord WordPtr | |
Ord Bitmap Source # | |
Ord GeneralCategory | |
Defined in GHC.Unicode Methods compare :: GeneralCategory -> GeneralCategory -> Ordering # (<) :: GeneralCategory -> GeneralCategory -> Bool # (<=) :: GeneralCategory -> GeneralCategory -> Bool # (>) :: GeneralCategory -> GeneralCategory -> Bool # (>=) :: GeneralCategory -> GeneralCategory -> Bool # max :: GeneralCategory -> GeneralCategory -> GeneralCategory # min :: GeneralCategory -> GeneralCategory -> GeneralCategory # | |
Ord Escaping Source # | |
Defined in Foundation.Format.CSV.Types | |
Ord BlockReason | |
Defined in GHC.Conc.Sync | |
Ord ThreadId | |
Defined in GHC.Conc.Sync | |
Ord ThreadStatus | |
Defined in GHC.Conc.Sync | |
Ord Arch Source # | |
Ord OS Source # | |
Ord Seconds Source # | |
Defined in Foundation.Time.Types | |
Ord NanoSeconds Source # | |
Defined in Foundation.Time.Types Methods compare :: NanoSeconds -> NanoSeconds -> Ordering # (<) :: NanoSeconds -> NanoSeconds -> Bool # (<=) :: NanoSeconds -> NanoSeconds -> Bool # (>) :: NanoSeconds -> NanoSeconds -> Bool # (>=) :: NanoSeconds -> NanoSeconds -> Bool # max :: NanoSeconds -> NanoSeconds -> NanoSeconds # min :: NanoSeconds -> NanoSeconds -> NanoSeconds # | |
Ord Addr | |
Ord IPv6 Source # | |
Ord IPv4 Source # | |
Ord UUID Source # | |
Ord FilePath Source # | |
Defined in Foundation.VFS.FilePath | |
Ord a => Ord [a] | |
Ord a => Ord (Maybe a) | |
Integral a => Ord (Ratio a) | |
Ord (Ptr a) | |
Ord (FunPtr a) | |
Defined in GHC.Ptr | |
Ord p => Ord (Par1 p) | |
(PrimType ty, Ord ty) => Ord (UArray ty) | |
Ord (Offset ty) | |
(PrimType ty, Ord ty) => Ord (Block ty) | |
Defined in Basement.Block.Base | |
Ord (CountOf ty) | |
Defined in Basement.Types.OffsetSize | |
Ord (ForeignPtr a) | |
Defined in GHC.ForeignPtr | |
Ord (FinalPtr a) | |
Ord a => Ord (NonEmpty a) | |
(ByteSwap a, Ord a) => Ord (BE a) | |
(ByteSwap a, Ord a) => Ord (LE a) | |
Ord a => Ord (Array a) | |
Ord a => Ord (Down a) | |
Ord a => Ord (Dual a) | |
Ord a => Ord (Product a) | |
Ord a => Ord (Sum a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord (Zn n) | |
Ord (Zn64 n) | |
Ord a => Ord (Identity a) | |
Defined in Data.Functor.Identity | |
Ord a => Ord (ZipList a) | |
Ord a => Ord (First a) | |
Ord a => Ord (Last a) | |
Ord a => Ord (Max a) | |
Ord a => Ord (Min a) | |
Ord a => Ord (Option a) | |
Defined in Data.Semigroup | |
Ord m => Ord (WrappedMonoid m) | |
Defined in Data.Semigroup Methods compare :: WrappedMonoid m -> WrappedMonoid m -> Ordering # (<) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (<=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>) :: WrappedMonoid m -> WrappedMonoid m -> Bool # (>=) :: WrappedMonoid m -> WrappedMonoid m -> Bool # max :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # min :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # | |
Ord a => Ord (DList a) Source # | |
Defined in Foundation.List.DList | |
(PrimType ty, Ord ty) => Ord (ChunkedUArray ty) Source # | |
Defined in Foundation.Array.Chunked.Unboxed Methods compare :: ChunkedUArray ty -> ChunkedUArray ty -> Ordering # (<) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # (<=) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # (>) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # (>=) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # max :: ChunkedUArray ty -> ChunkedUArray ty -> ChunkedUArray ty # min :: ChunkedUArray ty -> ChunkedUArray ty -> ChunkedUArray ty # | |
Ord (Bits n) | |
(Ord a, Ord b) => Ord (Either a b) | |
Ord (V1 p) | |
Ord (U1 p) | |
Ord (TypeRep a) | |
(Ord a, Ord b) => Ord (a, b) | |
Ord (Proxy s) | |
(Ix i, Ord e) => Ord (Array i e) | |
(PrimType a, Ord a) => Ord (BlockN n a) | |
Defined in Basement.Sized.Block | |
Ord a => Ord (ListN n a) | |
Ord a => Ord (Arg a b) | |
(Ord a, Ord b) => Ord (These a b) | |
(Ord a, Ord b) => Ord (Tuple2 a b) Source # | |
Ord (f p) => Ord (Rec1 f p) | |
Defined in GHC.Generics | |
Ord (URec (Ptr ()) p) | |
Defined in GHC.Generics Methods compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering # (<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # (>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool # max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p # | |
Ord (URec Char p) | |
Defined in GHC.Generics | |
Ord (URec Double p) | |
Defined in GHC.Generics Methods compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Ord (URec Float p) | |
Defined in GHC.Generics | |
Ord (URec Int p) | |
Ord (URec Word p) | |
Defined in GHC.Generics | |
(Ord a, Ord b, Ord c) => Ord (a, b, c) | |
Ord a => Ord (Const a b) | |
Ord (a :~: b) | |
Defined in Data.Type.Equality | |
Ord (Coercion a b) | |
Defined in Data.Type.Coercion | |
Ord (f a) => Ord (Alt f a) | |
Defined in Data.Semigroup.Internal | |
Ord (f a) => Ord (Ap f a) | |
(Ord a, Ord b, Ord c) => Ord (Tuple3 a b c) Source # | |
Defined in Foundation.Tuple | |
Ord c => Ord (K1 i c p) | |
Defined in GHC.Generics | |
(Ord (f p), Ord (g p)) => Ord ((f :+: g) p) | |
Defined in GHC.Generics | |
(Ord (f p), Ord (g p)) => Ord ((f :*: g) p) | |
Defined in GHC.Generics | |
(Ord a, Ord b, Ord c, Ord d) => Ord (a, b, c, d) | |
Defined in GHC.Classes | |
Ord (a :~~: b) | |
(Ord a, Ord b, Ord c, Ord d) => Ord (Tuple4 a b c d) Source # | |
Defined in Foundation.Tuple Methods compare :: Tuple4 a b c d -> Tuple4 a b c d -> Ordering # (<) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (<=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (>) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # (>=) :: Tuple4 a b c d -> Tuple4 a b c d -> Bool # | |
Ord (f p) => Ord (M1 i c f p) | |
Ord (f (g p)) => Ord ((f :.: g) p) | |
Defined in GHC.Generics | |
(Ord a, Ord b, Ord c, Ord d, Ord e) => Ord (a, b, c, d, e) | |
Defined in GHC.Classes Methods compare :: (a, b, c, d, e) -> (a, b, c, d, e) -> Ordering # (<) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (<=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # (>=) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool # max :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # min :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f) => Ord (a, b, c, d, e, f) | |
Defined in GHC.Classes Methods compare :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Ordering # (<) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (<=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # (>=) :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> Bool # max :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # min :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> (a, b, c, d, e, f) # | |
(Ord a, Ord b, Ord c, Ord d, Ord e, Ord f, Ord g) => Ord (a, b, c, d, e, f, g) | |
Defined in GHC.Classes Methods compare :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Ordering # (<) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (<=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # (>=) :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> Bool # max :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # min :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) # | |
(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) | |
Defined in GHC.Classes Methods compare :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Ordering # (<) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (<=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # (>=) :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> Bool # 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) # 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) # | |
(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) | |
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 # (<) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> Bool # 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) # 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) # | |
(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) | |
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 # (<) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> Bool # 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) # 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) # | |
(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) | |
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 # (<) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (<=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # (>=) :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> Bool # 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) # 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) # | |
(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) | |
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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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) | |
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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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) | |
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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # | |
(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) | |
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 # (<) :: (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 # (<=) :: (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 # (>) :: (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 # (>=) :: (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 # 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) # 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) # |
Instances
Eq Bool | |
Eq Char | |
Eq Double | |
Eq Float | |
Eq Int | |
Eq Int8 | |
Eq Int16 | |
Eq Int32 | |
Eq Int64 | |
Eq Integer | |
Eq Natural | |
Eq Ordering | |
Eq Word | |
Eq Word8 | |
Eq Word16 | |
Eq Word32 | |
Eq Word64 | |
Eq SomeTypeRep | |
Eq () | |
Eq TyCon | |
Eq Module | |
Eq TrName | |
Eq Constr | |
Eq SrcLoc | |
Eq CInt | |
Eq FileSize | |
Eq CSize | |
Eq CSsize | |
Eq CChar | |
Eq CUChar | |
Eq Word128 | |
Eq Word256 | |
Eq Char7 | |
Eq Encoding | |
Eq String | |
Eq ValidationFailure | |
Defined in Basement.UTF8.Types Methods (==) :: ValidationFailure -> ValidationFailure -> Bool # (/=) :: ValidationFailure -> ValidationFailure -> Bool # | |
Eq ConstrRep | |
Eq CM | |
Eq DataRep | |
Eq SpecConstrAnnotation | |
Eq Version | |
Eq Associativity | |
Eq DecidedStrictness | |
Eq Fixity | |
Eq SourceStrictness | |
Eq SourceUnpackedness | |
Eq ASCII7_Invalid | |
Eq ISO_8859_1_Invalid | |
Eq UTF16_Invalid | |
Eq UTF32_Invalid | |
Eq SomeNat | |
Eq SomeSymbol | |
Eq BigNat | |
Eq AsciiString | |
Defined in Basement.Types.AsciiString | |
Eq OutOfBoundOperation | |
Eq RecastDestinationSize | |
Eq RecastSourceSize | |
Eq Any | |
Eq All | |
Eq CDouble | |
Eq CFloat | |
Eq CIntMax | |
Eq CLLong | |
Eq CLong | |
Eq CPtrdiff | |
Eq CSChar | |
Eq CShort | |
Eq CWchar | |
Eq CBool | |
Eq CClock | |
Eq CIntPtr | |
Eq COff | |
Eq CSUSeconds | |
Eq CSigAtomic | |
Eq CTime | |
Eq CUInt | |
Eq CUIntMax | |
Eq CUIntPtr | |
Eq CULLong | |
Eq CULong | |
Eq CUSeconds | |
Eq CUShort | |
Eq IntPtr | |
Eq ErrorCall | |
Eq ArithException | |
Eq CMode | |
Eq IOException | |
Defined in GHC.IO.Exception | |
Eq Handle | |
Eq SeekMode | |
Eq HandlePosn | |
Eq BufferMode | |
Eq Newline | |
Eq NewlineMode | |
Eq IOMode | |
Eq Errno | |
Eq ExitCode | |
Eq IODeviceType | |
Eq CDev | |
Eq CIno | |
Eq MaskingState | |
Eq ArrayException | |
Eq AsyncException | |
Eq IOErrorType | |
Eq Sign Source # | |
Eq CBlkCnt | |
Eq CBlkSize | |
Eq CCc | |
Eq CClockId | |
Eq CFsBlkCnt | |
Eq CFsFilCnt | |
Eq CGid | |
Eq CId | |
Eq CKey | |
Eq CNlink | |
Eq CPid | |
Eq CRLim | |
Eq CSpeed | |
Eq CTcflag | |
Eq CTimer | |
Eq CUid | |
Eq Fd | |
Eq Endianness | |
Defined in Basement.Endianness | |
Eq WordPtr | |
Eq Bitmap Source # | |
Eq PartialError Source # | |
Defined in Foundation.Partial | |
Eq And Source # | |
Eq Condition Source # | |
Eq GeneralCategory | |
Eq CSV Source # | |
Eq Row Source # | |
Eq Escaping Source # | |
Eq Field Source # | |
Eq Fixity | |
Eq BlockReason | |
Eq ThreadId | |
Eq ThreadStatus | |
Eq Arch Source # | |
Eq OS Source # | |
Eq Seconds Source # | |
Eq NanoSeconds Source # | |
Defined in Foundation.Time.Types | |
Eq Addr | |
Eq IPv6 Source # | |
Eq IPv4 Source # | |
Eq UUID Source # | |
Eq FileName Source # | |
Eq FilePath Source # | |
Eq Relativity Source # | |
Defined in Foundation.VFS.FilePath | |
Eq CodingProgress | |
Eq a => Eq [a] | |
Eq a => Eq (Maybe a) | |
Eq a => Eq (Ratio a) | |
Eq (Ptr a) | |
Eq (FunPtr a) | |
Eq p => Eq (Par1 p) | |
(PrimType ty, Eq ty) => Eq (UArray ty) | |
Eq (Offset ty) | |
(PrimType ty, Eq ty) => Eq (Block ty) | |
Eq (CountOf ty) | |
Eq (ForeignPtr a) | |
Eq a => Eq (NonEmpty a) | |
Eq (FinalPtr a) | |
Eq a => Eq (NonEmpty a) | |
Eq a => Eq (BE a) | |
Eq a => Eq (LE a) | |
Eq (IORef a) | |
Eq a => Eq (Array a) | |
Eq a => Eq (Down a) | |
Eq a => Eq (Dual a) | |
Eq a => Eq (Product a) | |
Eq a => Eq (Sum a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq (Zn n) | |
Eq (Zn64 n) | |
Eq a => Eq (Identity a) | |
Eq a => Eq (ZipList a) | |
Eq a => Eq (First a) | |
Eq a => Eq (Last a) | |
Eq a => Eq (Max a) | |
Eq a => Eq (Min a) | |
Eq a => Eq (Option a) | |
Eq m => Eq (WrappedMonoid m) | |
Eq a => Eq (DList a) Source # | |
PrimType ty => Eq (ChunkedUArray ty) Source # | |
Defined in Foundation.Array.Chunked.Unboxed Methods (==) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # (/=) :: ChunkedUArray ty -> ChunkedUArray ty -> Bool # | |
Eq (TVar a) | |
Eq (Bits n) | |
(Eq a, Eq b) => Eq (Either a b) | |
Eq (V1 p) | |
Eq (U1 p) | |
Eq (TypeRep a) | |
(Eq a, Eq b) => Eq (a, b) | |
Eq (Proxy s) | |
(Ix i, Eq e) => Eq (Array i e) | |
PrimType a => Eq (BlockN n a) | |
Eq a => Eq (ListN n a) | |
Eq a => Eq (Arg a b) | |
(Eq a, Eq b) => Eq (These a b) | |
(Eq a, Eq b) => Eq (Tuple2 a b) Source # | |
Eq (f p) => Eq (Rec1 f p) | |
Eq (URec (Ptr ()) p) | |
Eq (URec Char p) | |
Eq (URec Double p) | |
Eq (URec Float p) | |
Eq (URec Int p) | |
Eq (URec Word p) | |
(Eq a, Eq b, Eq c) => Eq (a, b, c) | |
Eq a => Eq (Const a b) | |
Eq (a :~: b) | |
Eq (Coercion a b) | |
Eq (f a) => Eq (Alt f a) | |
Eq (f a) => Eq (Ap f a) | |
(Eq a, Eq b, Eq c) => Eq (Tuple3 a b c) Source # | |
Eq (STArray s i e) | |
Eq c => Eq (K1 i c p) | |
(Eq (f p), Eq (g p)) => Eq ((f :+: g) p) | |
(Eq (f p), Eq (g p)) => Eq ((f :*: g) p) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (a, b, c, d) | |
Eq (a :~~: b) | |
(Eq a, Eq b, Eq c, Eq d) => Eq (Tuple4 a b c d) Source # | |
Eq (f p) => Eq (M1 i c f p) | |
Eq (f (g p)) => Eq ((f :.: g) p) | |
(Eq a, Eq b, Eq c, Eq d, Eq e) => Eq (a, b, c, d, e) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f) => Eq (a, b, c, d, e, f) | |
(Eq a, Eq b, Eq c, Eq d, Eq e, Eq f, Eq g) => Eq (a, b, c, d, e, f, g) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
(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) | |
Instances
Methods
enumFromThen :: a -> a -> [a] #
enumFromTo :: a -> a -> [a] #
enumFromThenTo :: a -> a -> a -> [a] #
Instances
Enum Bool | |
Enum Char | |
Enum Int | |
Enum Int8 | |
Enum Int16 | |
Enum Int32 | |
Enum Int64 | |
Enum Integer | |
Enum Natural | |
Enum Ordering | |
Enum Word | |
Enum Word8 | |
Enum Word16 | |
Defined in GHC.Word | |
Enum Word32 | |
Defined in GHC.Word | |
Enum Word64 | |
Defined in GHC.Word | |
Enum VecCount | |
Defined in GHC.Enum Methods succ :: VecCount -> VecCount # pred :: VecCount -> VecCount # enumFrom :: VecCount -> [VecCount] # enumFromThen :: VecCount -> VecCount -> [VecCount] # enumFromTo :: VecCount -> VecCount -> [VecCount] # enumFromThenTo :: VecCount -> VecCount -> VecCount -> [VecCount] # | |
Enum VecElem | |
Defined in GHC.Enum Methods enumFrom :: VecElem -> [VecElem] # enumFromThen :: VecElem -> VecElem -> [VecElem] # enumFromTo :: VecElem -> VecElem -> [VecElem] # enumFromThenTo :: VecElem -> VecElem -> VecElem -> [VecElem] # | |
Enum () | |
Enum CInt | |
Defined in Foreign.C.Types | |
Enum CSize | |
Defined in Foreign.C.Types | |
Enum CSsize | |
Defined in System.Posix.Types | |
Enum CChar | |
Defined in Foreign.C.Types | |
Enum CUChar | |
Defined in Foreign.C.Types | |
Enum Word128 | |
Enum Word256 | |
Enum Encoding | |
Enum Associativity | |
Defined in GHC.Generics Methods succ :: Associativity -> Associativity # pred :: Associativity -> Associativity # toEnum :: Int -> Associativity # fromEnum :: Associativity -> Int # enumFrom :: Associativity -> [Associativity] # enumFromThen :: Associativity -> Associativity -> [Associativity] # enumFromTo :: Associativity -> Associativity -> [Associativity] # enumFromThenTo :: Associativity -> Associativity -> Associativity -> [Associativity] # | |
Enum DecidedStrictness | |
Defined in GHC.Generics Methods succ :: DecidedStrictness -> DecidedStrictness # pred :: DecidedStrictness -> DecidedStrictness # toEnum :: Int -> DecidedStrictness # fromEnum :: DecidedStrictness -> Int # enumFrom :: DecidedStrictness -> [DecidedStrictness] # enumFromThen :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] # enumFromTo :: DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] # enumFromThenTo :: DecidedStrictness -> DecidedStrictness -> DecidedStrictness -> [DecidedStrictness] # | |
Enum SourceStrictness | |
Defined in GHC.Generics Methods succ :: SourceStrictness -> SourceStrictness # pred :: SourceStrictness -> SourceStrictness # toEnum :: Int -> SourceStrictness # fromEnum :: SourceStrictness -> Int # enumFrom :: SourceStrictness -> [SourceStrictness] # enumFromThen :: SourceStrictness -> SourceStrictness -> [SourceStrictness] # enumFromTo :: SourceStrictness -> SourceStrictness -> [SourceStrictness] # enumFromThenTo :: SourceStrictness -> SourceStrictness -> SourceStrictness -> [SourceStrictness] # | |
Enum SourceUnpackedness | |
Defined in GHC.Generics Methods succ :: SourceUnpackedness -> SourceUnpackedness # pred :: SourceUnpackedness -> SourceUnpackedness # toEnum :: Int -> SourceUnpackedness # fromEnum :: SourceUnpackedness -> Int # enumFrom :: SourceUnpackedness -> [SourceUnpackedness] # enumFromThen :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] # enumFromTo :: SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] # enumFromThenTo :: SourceUnpackedness -> SourceUnpackedness -> SourceUnpackedness -> [SourceUnpackedness] # | |
Enum UTF32_Invalid | |
Defined in Basement.String.Encoding.UTF32 Methods succ :: UTF32_Invalid -> UTF32_Invalid # pred :: UTF32_Invalid -> UTF32_Invalid # toEnum :: Int -> UTF32_Invalid # fromEnum :: UTF32_Invalid -> Int # enumFrom :: UTF32_Invalid -> [UTF32_Invalid] # enumFromThen :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] # enumFromTo :: UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] # enumFromThenTo :: UTF32_Invalid -> UTF32_Invalid -> UTF32_Invalid -> [UTF32_Invalid] # | |
Enum CDouble | |
Defined in Foreign.C.Types Methods enumFrom :: CDouble -> [CDouble] # enumFromThen :: CDouble -> CDouble -> [CDouble] # enumFromTo :: CDouble -> CDouble -> [CDouble] # enumFromThenTo :: CDouble -> CDouble -> CDouble -> [CDouble] # | |
Enum CFloat | |
Defined in Foreign.C.Types | |
Enum CIntMax | |
Defined in Foreign.C.Types Methods enumFrom :: CIntMax -> [CIntMax] # enumFromThen :: CIntMax -> CIntMax -> [CIntMax] # enumFromTo :: CIntMax -> CIntMax -> [CIntMax] # enumFromThenTo :: CIntMax -> CIntMax -> CIntMax -> [CIntMax] # | |
Enum CLLong | |
Defined in Foreign.C.Types | |
Enum CLong | |
Defined in Foreign.C.Types | |
Enum CPtrdiff | |
Defined in Foreign.C.Types Methods succ :: CPtrdiff -> CPtrdiff # pred :: CPtrdiff -> CPtrdiff # enumFrom :: CPtrdiff -> [CPtrdiff] # enumFromThen :: CPtrdiff -> CPtrdiff -> [CPtrdiff] # enumFromTo :: CPtrdiff -> CPtrdiff -> [CPtrdiff] # enumFromThenTo :: CPtrdiff -> CPtrdiff -> CPtrdiff -> [CPtrdiff] # | |
Enum CSChar | |
Defined in Foreign.C.Types | |
Enum CShort | |
Defined in Foreign.C.Types | |
Enum CWchar | |
Defined in Foreign.C.Types | |
Enum CBool | |
Defined in Foreign.C.Types | |
Enum CClock | |
Defined in Foreign.C.Types | |
Enum CIntPtr | |
Defined in Foreign.C.Types Methods enumFrom :: CIntPtr -> [CIntPtr] # enumFromThen :: CIntPtr -> CIntPtr -> [CIntPtr] # enumFromTo :: CIntPtr -> CIntPtr -> [CIntPtr] # enumFromThenTo :: CIntPtr -> CIntPtr -> CIntPtr -> [CIntPtr] # | |
Enum COff | |
Defined in System.Posix.Types | |
Enum CSUSeconds | |
Defined in Foreign.C.Types Methods succ :: CSUSeconds -> CSUSeconds # pred :: CSUSeconds -> CSUSeconds # fromEnum :: CSUSeconds -> Int # enumFrom :: CSUSeconds -> [CSUSeconds] # enumFromThen :: CSUSeconds -> CSUSeconds -> [CSUSeconds] # enumFromTo :: CSUSeconds -> CSUSeconds -> [CSUSeconds] # enumFromThenTo :: CSUSeconds -> CSUSeconds -> CSUSeconds -> [CSUSeconds] # | |
Enum CSigAtomic | |
Defined in Foreign.C.Types Methods succ :: CSigAtomic -> CSigAtomic # pred :: CSigAtomic -> CSigAtomic # fromEnum :: CSigAtomic -> Int # enumFrom :: CSigAtomic -> [CSigAtomic] # enumFromThen :: CSigAtomic -> CSigAtomic -> [CSigAtomic] # enumFromTo :: CSigAtomic -> CSigAtomic -> [CSigAtomic] # enumFromThenTo :: CSigAtomic -> CSigAtomic -> CSigAtomic -> [CSigAtomic] # | |
Enum CTime | |
Defined in Foreign.C.Types | |
Enum CUInt | |
Defined in Foreign.C.Types | |
Enum CUIntMax | |
Defined in Foreign.C.Types Methods succ :: CUIntMax -> CUIntMax # pred :: CUIntMax -> CUIntMax # enumFrom :: CUIntMax -> [CUIntMax] # enumFromThen :: CUIntMax -> CUIntMax -> [CUIntMax] # enumFromTo :: CUIntMax -> CUIntMax -> [CUIntMax] # enumFromThenTo :: CUIntMax -> CUIntMax -> CUIntMax -> [CUIntMax] # | |
Enum CUIntPtr | |
Defined in Foreign.C.Types Methods succ :: CUIntPtr -> CUIntPtr # pred :: CUIntPtr -> CUIntPtr # enumFrom :: CUIntPtr -> [CUIntPtr] # enumFromThen :: CUIntPtr -> CUIntPtr -> [CUIntPtr] # enumFromTo :: CUIntPtr -> CUIntPtr -> [CUIntPtr] # enumFromThenTo :: CUIntPtr -> CUIntPtr -> CUIntPtr -> [CUIntPtr] # | |
Enum CULLong | |
Defined in Foreign.C.Types Methods enumFrom :: CULLong -> [CULLong] # enumFromThen :: CULLong -> CULLong -> [CULLong] # enumFromTo :: CULLong -> CULLong -> [CULLong] # enumFromThenTo :: CULLong -> CULLong -> CULLong -> [CULLong] # | |
Enum CULong | |
Defined in Foreign.C.Types | |
Enum CUSeconds | |
Defined in Foreign.C.Types Methods succ :: CUSeconds -> CUSeconds # pred :: CUSeconds -> CUSeconds # fromEnum :: CUSeconds -> Int # enumFrom :: CUSeconds -> [CUSeconds] # enumFromThen :: CUSeconds -> CUSeconds -> [CUSeconds] # enumFromTo :: CUSeconds -> CUSeconds -> [CUSeconds] # enumFromThenTo :: CUSeconds -> CUSeconds -> CUSeconds -> [CUSeconds] # | |
Enum CUShort | |
Defined in Foreign.C.Types Methods enumFrom :: CUShort -> [CUShort] # enumFromThen :: CUShort -> CUShort -> [CUShort] # enumFromTo :: CUShort -> CUShort -> [CUShort] # enumFromThenTo :: CUShort -> CUShort -> CUShort -> [CUShort] # | |
Enum IntPtr | |
Defined in Foreign.Ptr | |
Enum CMode | |
Defined in System.Posix.Types | |
Enum SeekMode | |
Defined in GHC.IO.Device Methods succ :: SeekMode -> SeekMode # pred :: SeekMode -> SeekMode # enumFrom :: SeekMode -> [SeekMode] # enumFromThen :: SeekMode -> SeekMode -> [SeekMode] # enumFromTo :: SeekMode -> SeekMode -> [SeekMode] # enumFromThenTo :: SeekMode -> SeekMode -> SeekMode -> [SeekMode] # | |
Enum IOMode | |
Defined in GHC.IO.IOMode | |
Enum CDev | |
Defined in System.Posix.Types | |
Enum CIno | |
Defined in System.Posix.Types | |
Enum CBlkCnt | |
Defined in System.Posix.Types Methods enumFrom :: CBlkCnt -> [CBlkCnt] # enumFromThen :: CBlkCnt -> CBlkCnt -> [CBlkCnt] # enumFromTo :: CBlkCnt -> CBlkCnt -> [CBlkCnt] # enumFromThenTo :: CBlkCnt -> CBlkCnt -> CBlkCnt -> [CBlkCnt] # | |
Enum CBlkSize | |
Defined in System.Posix.Types Methods succ :: CBlkSize -> CBlkSize # pred :: CBlkSize -> CBlkSize # enumFrom :: CBlkSize -> [CBlkSize] # enumFromThen :: CBlkSize -> CBlkSize -> [CBlkSize] # enumFromTo :: CBlkSize -> CBlkSize -> [CBlkSize] # enumFromThenTo :: CBlkSize -> CBlkSize -> CBlkSize -> [CBlkSize] # | |
Enum CCc | |
Defined in System.Posix.Types | |
Enum CClockId | |
Defined in System.Posix.Types Methods succ :: CClockId -> CClockId # pred :: CClockId -> CClockId # enumFrom :: CClockId -> [CClockId] # enumFromThen :: CClockId -> CClockId -> [CClockId] # enumFromTo :: CClockId -> CClockId -> [CClockId] # enumFromThenTo :: CClockId -> CClockId -> CClockId -> [CClockId] # | |
Enum CFsBlkCnt | |
Defined in System.Posix.Types Methods succ :: CFsBlkCnt -> CFsBlkCnt # pred :: CFsBlkCnt -> CFsBlkCnt # fromEnum :: CFsBlkCnt -> Int # enumFrom :: CFsBlkCnt -> [CFsBlkCnt] # enumFromThen :: CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] # enumFromTo :: CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] # enumFromThenTo :: CFsBlkCnt -> CFsBlkCnt -> CFsBlkCnt -> [CFsBlkCnt] # | |
Enum CFsFilCnt | |
Defined in System.Posix.Types Methods succ :: CFsFilCnt -> CFsFilCnt # pred :: CFsFilCnt -> CFsFilCnt # fromEnum :: CFsFilCnt -> Int # enumFrom :: CFsFilCnt -> [CFsFilCnt] # enumFromThen :: CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] # enumFromTo :: CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] # enumFromThenTo :: CFsFilCnt -> CFsFilCnt -> CFsFilCnt -> [CFsFilCnt] # | |
Enum CGid | |
Defined in System.Posix.Types | |
Enum CId | |
Defined in System.Posix.Types | |
Enum CKey | |
Defined in System.Posix.Types | |
Enum CNlink | |
Defined in System.Posix.Types | |
Enum CPid | |
Defined in System.Posix.Types | |
Enum CRLim | |
Defined in System.Posix.Types | |
Enum CSpeed | |
Defined in System.Posix.Types | |
Enum CTcflag | |
Defined in System.Posix.Types Methods enumFrom :: CTcflag -> [CTcflag] # enumFromThen :: CTcflag -> CTcflag -> [CTcflag] # enumFromTo :: CTcflag -> CTcflag -> [CTcflag] # enumFromThenTo :: CTcflag -> CTcflag -> CTcflag -> [CTcflag] # | |
Enum CUid | |
Defined in System.Posix.Types | |
Enum Fd | |
Defined in System.Posix.Types | |
Enum WordPtr | |
Defined in Foreign.Ptr Methods enumFrom :: WordPtr -> [WordPtr] # enumFromThen :: WordPtr -> WordPtr -> [WordPtr] # enumFromTo :: WordPtr -> WordPtr -> [WordPtr] # enumFromThenTo :: WordPtr -> WordPtr -> WordPtr -> [WordPtr] # | |
Enum GeneralCategory | |
Defined in GHC.Unicode Methods succ :: GeneralCategory -> GeneralCategory # pred :: GeneralCategory -> GeneralCategory # toEnum :: Int -> GeneralCategory # fromEnum :: GeneralCategory -> Int # enumFrom :: GeneralCategory -> [GeneralCategory] # enumFromThen :: GeneralCategory -> GeneralCategory -> [GeneralCategory] # enumFromTo :: GeneralCategory -> GeneralCategory -> [GeneralCategory] # enumFromThenTo :: GeneralCategory -> GeneralCategory -> GeneralCategory -> [GeneralCategory] # | |
Enum Escaping Source # | |
Defined in Foundation.Format.CSV.Types | |
Enum Arch Source # | |
Enum OS Source # | |
Enum Seconds Source # | |
Enum NanoSeconds Source # | |
Defined in Foundation.Time.Types Methods succ :: NanoSeconds -> NanoSeconds # pred :: NanoSeconds -> NanoSeconds # toEnum :: Int -> NanoSeconds # fromEnum :: NanoSeconds -> Int # enumFrom :: NanoSeconds -> [NanoSeconds] # enumFromThen :: NanoSeconds -> NanoSeconds -> [NanoSeconds] # enumFromTo :: NanoSeconds -> NanoSeconds -> [NanoSeconds] # enumFromThenTo :: NanoSeconds -> NanoSeconds -> NanoSeconds -> [NanoSeconds] # | |
Integral a => Enum (Ratio a) | |
Defined in GHC.Real Methods enumFrom :: Ratio a -> [Ratio a] # enumFromThen :: Ratio a -> Ratio a -> [Ratio a] # enumFromTo :: Ratio a -> Ratio a -> [Ratio a] # enumFromThenTo :: Ratio a -> Ratio a -> Ratio a -> [Ratio a] # | |
Enum (Offset ty) | |
Defined in Basement.Types.OffsetSize Methods succ :: Offset ty -> Offset ty # pred :: Offset ty -> Offset ty # fromEnum :: Offset ty -> Int # enumFrom :: Offset ty -> [Offset ty] # enumFromThen :: Offset ty -> Offset ty -> [Offset ty] # enumFromTo :: Offset ty -> Offset ty -> [Offset ty] # enumFromThenTo :: Offset ty -> Offset ty -> Offset ty -> [Offset ty] # | |
Enum (CountOf ty) | |
Defined in Basement.Types.OffsetSize Methods succ :: CountOf ty -> CountOf ty # pred :: CountOf ty -> CountOf ty # fromEnum :: CountOf ty -> Int # enumFrom :: CountOf ty -> [CountOf ty] # enumFromThen :: CountOf ty -> CountOf ty -> [CountOf ty] # enumFromTo :: CountOf ty -> CountOf ty -> [CountOf ty] # enumFromThenTo :: CountOf ty -> CountOf ty -> CountOf ty -> [CountOf ty] # | |
Enum a => Enum (Identity a) | |
Defined in Data.Functor.Identity Methods succ :: Identity a -> Identity a # pred :: Identity a -> Identity a # fromEnum :: Identity a -> Int # enumFrom :: Identity a -> [Identity a] # enumFromThen :: Identity a -> Identity a -> [Identity a] # enumFromTo :: Identity a -> Identity a -> [Identity a] # enumFromThenTo :: Identity a -> Identity a -> Identity a -> [Identity a] # | |
Enum a => Enum (First a) | |
Defined in Data.Semigroup Methods enumFrom :: First a -> [First a] # enumFromThen :: First a -> First a -> [First a] # enumFromTo :: First a -> First a -> [First a] # enumFromThenTo :: First a -> First a -> First a -> [First a] # | |
Enum a => Enum (Last a) | |
Defined in Data.Semigroup | |
Enum a => Enum (Max a) | |
Defined in Data.Semigroup | |
Enum a => Enum (Min a) | |
Defined in Data.Semigroup | |
Enum a => Enum (WrappedMonoid a) | |
Defined in Data.Semigroup Methods succ :: WrappedMonoid a -> WrappedMonoid a # pred :: WrappedMonoid a -> WrappedMonoid a # toEnum :: Int -> WrappedMonoid a # fromEnum :: WrappedMonoid a -> Int # enumFrom :: WrappedMonoid a -> [WrappedMonoid a] # enumFromThen :: WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] # enumFromTo :: WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] # enumFromThenTo :: WrappedMonoid a -> WrappedMonoid a -> WrappedMonoid a -> [WrappedMonoid a] # | |
SizeValid n => Enum (Bits n) | |
Defined in Basement.Bits | |
Enum (Proxy s) | |
Enum a => Enum (Const a b) | |
Defined in Data.Functor.Const Methods succ :: Const a b -> Const a b # pred :: Const a b -> Const a b # fromEnum :: Const a b -> Int # enumFrom :: Const a b -> [Const a b] # enumFromThen :: Const a b -> Const a b -> [Const a b] # enumFromTo :: Const a b -> Const a b -> [Const a b] # enumFromThenTo :: Const a b -> Const a b -> Const a b -> [Const a b] # | |
a ~ b => Enum (a :~: b) | |
Defined in Data.Type.Equality Methods succ :: (a :~: b) -> a :~: b # pred :: (a :~: b) -> a :~: b # fromEnum :: (a :~: b) -> Int # enumFrom :: (a :~: b) -> [a :~: b] # enumFromThen :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromTo :: (a :~: b) -> (a :~: b) -> [a :~: b] # enumFromThenTo :: (a :~: b) -> (a :~: b) -> (a :~: b) -> [a :~: b] # | |
Coercible a b => Enum (Coercion a b) | |
Defined in Data.Type.Coercion Methods succ :: Coercion a b -> Coercion a b # pred :: Coercion a b -> Coercion a b # toEnum :: Int -> Coercion a b # fromEnum :: Coercion a b -> Int # enumFrom :: Coercion a b -> [Coercion a b] # enumFromThen :: Coercion a b -> Coercion a b -> [Coercion a b] # enumFromTo :: Coercion a b -> Coercion a b -> [Coercion a b] # enumFromThenTo :: Coercion a b -> Coercion a b -> Coercion a b -> [Coercion a b] # | |
Enum (f a) => Enum (Alt f a) | |
Defined in Data.Semigroup.Internal Methods enumFrom :: Alt f a -> [Alt f a] # enumFromThen :: Alt f a -> Alt f a -> [Alt f a] # enumFromTo :: Alt f a -> Alt f a -> [Alt f a] # enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] # | |
Enum (f a) => Enum (Ap f a) | |
Defined in Data.Monoid | |
a ~~ b => Enum (a :~~: b) | |
Defined in Data.Type.Equality Methods succ :: (a :~~: b) -> a :~~: b # pred :: (a :~~: b) -> a :~~: b # fromEnum :: (a :~~: b) -> Int # enumFrom :: (a :~~: b) -> [a :~~: b] # enumFromThen :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromTo :: (a :~~: b) -> (a :~~: b) -> [a :~~: b] # enumFromThenTo :: (a :~~: b) -> (a :~~: b) -> (a :~~: b) -> [a :~~: b] # |
class Functor (f :: Type -> Type) where #
Minimal complete definition
Instances
Methods
fromInteger :: Integer -> a #
Instances
class Fractional a where #
Methods
fromRational :: Rational -> a #
Instances
Fractional Double | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> Double # | |
Fractional Float | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> Float # | |
Fractional Rational | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> Rational # | |
Fractional CDouble | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> CDouble # | |
Fractional CFloat | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> CFloat # |
class HasNegation a where #
Instances
class Bifunctor (p :: Type -> Type -> Type) where #
Instances
Bifunctor Either | |
Bifunctor (,) | |
Bifunctor Arg | |
Bifunctor These | |
Bifunctor Tuple2 Source # | |
Bifunctor ((,,) x1) | |
Bifunctor (Const :: Type -> Type -> Type) | |
Bifunctor (K1 i :: Type -> Type -> Type) | |
Bifunctor ((,,,) x1 x2) | |
Bifunctor ((,,,,) x1 x2 x3) | |
Bifunctor ((,,,,,) x1 x2 x3 x4) | |
Bifunctor ((,,,,,,) x1 x2 x3 x4 x5) | |
class Functor f => Applicative (f :: Type -> Type) where #
Instances
Applicative [] | |
Applicative Maybe | |
Applicative IO | |
Applicative Par1 | |
Applicative NonEmpty | |
Applicative Down | |
Applicative P | |
Applicative ReadP | |
Applicative Dual | |
Applicative Product | |
Applicative Sum | |
Applicative First | |
Applicative Last | |
Applicative Identity | |
Applicative ZipList | |
Applicative First | |
Applicative Last | |
Applicative Max | |
Applicative Min | |
Applicative Option | |
Applicative DList Source # | |
Applicative Partial Source # | |
Applicative Gen Source # | |
Applicative Check Source # | |
Applicative STM | |
Applicative (Either e) | |
Applicative (U1 :: Type -> Type) | |
Monoid a => Applicative ((,) a) | |
Applicative (ST s) | |
Applicative (Proxy :: Type -> Type) | |
Monad m => Applicative (WrappedMonad m) | |
Defined in Control.Applicative Methods pure :: a -> WrappedMonad m a # (<*>) :: WrappedMonad m (a -> b) -> WrappedMonad m a -> WrappedMonad m b # liftA2 :: (a -> b -> c) -> WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m c # (*>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # (<*) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m a # | |
Applicative m => Applicative (ResourceT m) Source # | |
Defined in Foundation.Conduit.Internal | |
Arrow a => Applicative (ArrowMonad a) | |
Defined in Control.Arrow Methods pure :: a0 -> ArrowMonad a a0 # (<*>) :: ArrowMonad a (a0 -> b) -> ArrowMonad a a0 -> ArrowMonad a b # liftA2 :: (a0 -> b -> c) -> ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a c # (*>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # (<*) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a a0 # | |
ParserSource input => Applicative (Parser input) Source # | |
Defined in Foundation.Parser | |
Applicative (MonadRandomState gen) Source # | |
Defined in Foundation.Random.DRG Methods pure :: a -> MonadRandomState gen a # (<*>) :: MonadRandomState gen (a -> b) -> MonadRandomState gen a -> MonadRandomState gen b # liftA2 :: (a -> b -> c) -> MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen c # (*>) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen b # (<*) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen a # | |
Applicative f => Applicative (Rec1 f) | |
Monoid m => Applicative (Const m :: Type -> Type) | |
Monad m => Applicative (State s m) | |
Defined in Basement.Compat.MonadTrans | |
Applicative f => Applicative (Alt f) | |
Applicative f => Applicative (Ap f) | |
Monad m => Applicative (Reader r m) | |
Defined in Basement.Compat.MonadTrans | |
Arrow a => Applicative (WrappedArrow a b) | |
Defined in Control.Applicative Methods pure :: a0 -> WrappedArrow a b a0 # (<*>) :: WrappedArrow a b (a0 -> b0) -> WrappedArrow a b a0 -> WrappedArrow a b b0 # liftA2 :: (a0 -> b0 -> c) -> WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b c # (*>) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b b0 # (<*) :: WrappedArrow a b a0 -> WrappedArrow a b b0 -> WrappedArrow a b a0 # | |
(Applicative m, Monad m) => Applicative (StateT s m) Source # | |
Defined in Foundation.Monad.State | |
Applicative m => Applicative (ReaderT r m) Source # | |
Defined in Foundation.Monad.Reader | |
Monad m => Applicative (ExceptT e m) Source # | |
Defined in Foundation.Monad.Except | |
Monad m => Applicative (ZipSink i m) Source # | |
Defined in Foundation.Conduit.Internal | |
Applicative ((->) a :: Type -> Type) | |
Monoid c => Applicative (K1 i c :: Type -> Type) | |
(Applicative f, Applicative g) => Applicative (f :*: g) | |
Applicative (Conduit i o m) Source # | |
Defined in Foundation.Conduit.Internal Methods pure :: a -> Conduit i o m a # (<*>) :: Conduit i o m (a -> b) -> Conduit i o m a -> Conduit i o m b # liftA2 :: (a -> b -> c) -> Conduit i o m a -> Conduit i o m b -> Conduit i o m c # (*>) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m b # (<*) :: Conduit i o m a -> Conduit i o m b -> Conduit i o m a # | |
Applicative f => Applicative (M1 i c f) | |
(Applicative f, Applicative g) => Applicative (f :.: g) | |
Monad state => Applicative (Builder collection mutCollection step state err) | |
Defined in Basement.MutableBuilder Methods pure :: a -> Builder collection mutCollection step state err a # (<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b # 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 # (*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b # (<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a # |
class Applicative m => Monad (m :: Type -> Type) where #
Minimal complete definition
Instances
Monad [] | |
Monad Maybe | |
Monad IO | |
Monad Par1 | |
Monad NonEmpty | |
Monad Down | |
Monad P | |
Monad ReadP | |
Monad Dual | |
Monad Product | |
Monad Sum | |
Monad First | |
Monad Last | |
Monad Identity | |
Monad First | |
Monad Last | |
Monad Max | |
Monad Min | |
Monad Option | |
Monad DList Source # | |
Monad Partial Source # | |
Monad Gen Source # | |
Monad Check Source # | |
Monad STM | |
Monad (Either e) | |
Monad (U1 :: Type -> Type) | |
Monoid a => Monad ((,) a) | |
Monad (ST s) | |
Monad (Proxy :: Type -> Type) | |
Monad m => Monad (WrappedMonad m) | |
Monad m => Monad (ResourceT m) Source # | |
ArrowApply a => Monad (ArrowMonad a) | |
ParserSource input => Monad (Parser input) Source # | |
Monad (MonadRandomState gen) Source # | |
Defined in Foundation.Random.DRG Methods (>>=) :: MonadRandomState gen a -> (a -> MonadRandomState gen b) -> MonadRandomState gen b # (>>) :: MonadRandomState gen a -> MonadRandomState gen b -> MonadRandomState gen b # return :: a -> MonadRandomState gen a # fail :: String -> MonadRandomState gen a # | |
Monad f => Monad (Rec1 f) | |
Monad m => Monad (State r m) | |
Monad f => Monad (Alt f) | |
Monad f => Monad (Ap f) | |
Monad m => Monad (Reader r m) | |
(Functor m, Monad m) => Monad (StateT s m) Source # | |
Monad m => Monad (ReaderT r m) Source # | |
Monad m => Monad (ExceptT e m) Source # | |
Monad ((->) r :: Type -> Type) | |
(Monad f, Monad g) => Monad (f :*: g) | |
Monad (Conduit i o m) Source # | |
Monad f => Monad (M1 i c f) | |
Monad state => Monad (Builder collection mutCollection step state err) | |
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 # (>>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b # return :: a -> Builder collection mutCollection step state err a # fail :: String -> Builder collection mutCollection step state err a # |
Methods
fromString :: String -> a #
Instances
IsString String | |
Defined in Basement.UTF8.Base Methods fromString :: String0 -> String # | |
IsString AsciiString | |
Defined in Basement.Types.AsciiString Methods fromString :: String -> AsciiString # | |
IsString IPv6 Source # | |
Defined in Foundation.Network.IPv6 Methods fromString :: String -> IPv6 # | |
IsString IPv4 Source # | |
Defined in Foundation.Network.IPv4 Methods fromString :: String -> IPv4 # | |
IsString FileName Source # | |
Defined in Foundation.VFS.FilePath Methods fromString :: String -> FileName # | |
IsString FilePath Source # | |
Defined in Foundation.VFS.FilePath Methods fromString :: String -> FilePath # | |
a ~ Char => IsString [a] | |
Defined in Data.String Methods fromString :: String -> [a] # | |
IsString a => IsString (Identity a) | |
Defined in Data.String Methods fromString :: String -> Identity a # | |
IsString a => IsString (Const a b) | |
Defined in Data.String Methods fromString :: String -> Const a b # |
Instances
IsList CallStack | |
IsList String | |
IsList Version | |
IsList AsciiString | |
Defined in Basement.Types.AsciiString Associated Types type Item AsciiString :: Type # Methods fromList :: [Item AsciiString] -> AsciiString # fromListN :: Int -> [Item AsciiString] -> AsciiString # toList :: AsciiString -> [Item AsciiString] # | |
IsList Bitmap Source # | |
IsList CSV Source # | |
IsList Row Source # | |
IsList [a] | |
PrimType ty => IsList (UArray ty) | |
PrimType ty => IsList (Block ty) | |
IsList c => IsList (NonEmpty c) | |
IsList (NonEmpty a) | |
IsList (Array ty) | |
IsList (DList a) Source # | |
PrimType ty => IsList (ChunkedUArray ty) Source # | |
Defined in Foundation.Array.Chunked.Unboxed Associated Types type Item (ChunkedUArray ty) :: Type # Methods fromList :: [Item (ChunkedUArray ty)] -> ChunkedUArray ty # fromListN :: Int -> [Item (ChunkedUArray ty)] -> ChunkedUArray ty # toList :: ChunkedUArray ty -> [Item (ChunkedUArray ty)] # |
Numeric type classes
class (Integral a, Eq a, Ord a) => IsIntegral a where #
Instances
class IsIntegral a => IsNatural a where #
Instances
types that have sign and can be made absolute
Instances
class Subtractive a where #
Associated Types
type Difference a :: Type #
Methods
(-) :: a -> a -> Difference a #
Instances
Subtractive Char | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Char :: Type # | |
Subtractive Double | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Double :: Type # | |
Subtractive Float | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Float :: Type # | |
Subtractive Int | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int :: Type # | |
Subtractive Int8 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int8 :: Type # | |
Subtractive Int16 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int16 :: Type # | |
Subtractive Int32 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int32 :: Type # | |
Subtractive Int64 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int64 :: Type # | |
Subtractive Integer | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Integer :: Type # | |
Subtractive Natural | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Natural :: Type # | |
Subtractive Word | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word :: Type # | |
Subtractive Word8 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word8 :: Type # | |
Subtractive Word16 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word16 :: Type # | |
Subtractive Word32 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word32 :: Type # | |
Subtractive Word64 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word64 :: Type # | |
Subtractive CInt | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CInt :: Type # Methods (-) :: CInt -> CInt -> Difference CInt # | |
Subtractive CSize | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CSize :: Type # Methods (-) :: CSize -> CSize -> Difference CSize # | |
Subtractive CChar | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CChar :: Type # Methods (-) :: CChar -> CChar -> Difference CChar # | |
Subtractive CUChar | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUChar :: Type # Methods (-) :: CUChar -> CUChar -> Difference CUChar # | |
Subtractive Word128 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word128 :: Type # | |
Subtractive Word256 | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word256 :: Type # | |
Subtractive CDouble | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CDouble :: Type # Methods (-) :: CDouble -> CDouble -> Difference CDouble # | |
Subtractive CFloat | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CFloat :: Type # Methods (-) :: CFloat -> CFloat -> Difference CFloat # | |
Subtractive CIntMax | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CIntMax :: Type # Methods (-) :: CIntMax -> CIntMax -> Difference CIntMax # | |
Subtractive CLLong | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CLLong :: Type # Methods (-) :: CLLong -> CLLong -> Difference CLLong # | |
Subtractive CLong | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CLong :: Type # Methods (-) :: CLong -> CLong -> Difference CLong # | |
Subtractive CPtrdiff | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CPtrdiff :: Type # Methods (-) :: CPtrdiff -> CPtrdiff -> Difference CPtrdiff # | |
Subtractive CSChar | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CSChar :: Type # Methods (-) :: CSChar -> CSChar -> Difference CSChar # | |
Subtractive CShort | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CShort :: Type # Methods (-) :: CShort -> CShort -> Difference CShort # | |
Subtractive CWchar | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CWchar :: Type # Methods (-) :: CWchar -> CWchar -> Difference CWchar # | |
Subtractive CBool | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CBool :: Type # Methods (-) :: CBool -> CBool -> Difference CBool # | |
Subtractive CClock | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CClock :: Type # Methods (-) :: CClock -> CClock -> Difference CClock # | |
Subtractive CIntPtr | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CIntPtr :: Type # Methods (-) :: CIntPtr -> CIntPtr -> Difference CIntPtr # | |
Subtractive COff | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference COff :: Type # Methods (-) :: COff -> COff -> Difference COff # | |
Subtractive CSUSeconds | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CSUSeconds :: Type # Methods (-) :: CSUSeconds -> CSUSeconds -> Difference CSUSeconds # | |
Subtractive CSigAtomic | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CSigAtomic :: Type # Methods (-) :: CSigAtomic -> CSigAtomic -> Difference CSigAtomic # | |
Subtractive CTime | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CTime :: Type # Methods (-) :: CTime -> CTime -> Difference CTime # | |
Subtractive CUInt | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUInt :: Type # Methods (-) :: CUInt -> CUInt -> Difference CUInt # | |
Subtractive CUIntMax | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUIntMax :: Type # Methods (-) :: CUIntMax -> CUIntMax -> Difference CUIntMax # | |
Subtractive CUIntPtr | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUIntPtr :: Type # Methods (-) :: CUIntPtr -> CUIntPtr -> Difference CUIntPtr # | |
Subtractive CULLong | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CULLong :: Type # Methods (-) :: CULLong -> CULLong -> Difference CULLong # | |
Subtractive CULong | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CULong :: Type # Methods (-) :: CULong -> CULong -> Difference CULong # | |
Subtractive CUSeconds | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUSeconds :: Type # Methods (-) :: CUSeconds -> CUSeconds -> Difference CUSeconds # | |
Subtractive CUShort | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference CUShort :: Type # Methods (-) :: CUShort -> CUShort -> Difference CUShort # | |
Subtractive (Offset ty) | |
Defined in Basement.Types.OffsetSize Associated Types type Difference (Offset ty) :: Type # | |
Subtractive (CountOf ty) | |
Defined in Basement.Types.OffsetSize Associated Types type Difference (CountOf ty) :: Type # | |
KnownNat n => Subtractive (Zn n) | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference (Zn n) :: Type # Methods (-) :: Zn n -> Zn n -> Difference (Zn n) # | |
(KnownNat n, NatWithinBound Word64 n) => Subtractive (Zn64 n) | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference (Zn64 n) :: Type # Methods (-) :: Zn64 n -> Zn64 n -> Difference (Zn64 n) # | |
SizeValid n => Subtractive (Bits n) | |
Defined in Basement.Bits Associated Types type Difference (Bits n) :: Type # Methods (-) :: Bits n -> Bits n -> Difference (Bits n) # |
class Multiplicative a where #
Methods
(^) :: (IsNatural n, Enum n, IDivisible n) => a -> n -> a #
Instances
class (Additive a, Multiplicative a) => IDivisible a where #
Instances
IDivisible Int | |
IDivisible Int8 | |
IDivisible Int16 | |
IDivisible Int32 | |
IDivisible Int64 | |
IDivisible Integer | |
IDivisible Natural | |
IDivisible Word | |
IDivisible Word8 | |
IDivisible Word16 | |
IDivisible Word32 | |
IDivisible Word64 | |
IDivisible CInt | |
IDivisible CSize | |
IDivisible CChar | |
IDivisible CUChar | |
IDivisible Word128 | |
IDivisible Word256 | |
IDivisible CIntMax | |
IDivisible CLLong | |
IDivisible CLong | |
IDivisible CPtrdiff | |
IDivisible CSChar | |
IDivisible CShort | |
IDivisible CWchar | |
IDivisible CIntPtr | |
IDivisible CSigAtomic | |
IDivisible CUInt | |
IDivisible CUIntMax | |
IDivisible CUIntPtr | |
IDivisible CULLong | |
IDivisible CULong | |
IDivisible CUShort | |
SizeValid n => IDivisible (Bits n) | |
class Multiplicative a => Divisible a where #
Instances
Divisible Double | |
Divisible Float | |
Divisible Rational | |
Divisible CDouble | |
Defined in Basement.Numerical.Multiplicative | |
Divisible CFloat | |
Defined in Basement.Numerical.Multiplicative |
Data types
Instances
Monad Maybe | |
Functor Maybe | |
MonadFix Maybe | |
Defined in Control.Monad.Fix | |
Applicative Maybe | |
Foldable Maybe | |
Defined in Data.Foldable Methods fold :: Monoid m => Maybe m -> m foldMap :: Monoid m => (a -> m) -> Maybe a -> m foldr :: (a -> b -> b) -> b -> Maybe a -> b foldr' :: (a -> b -> b) -> b -> Maybe a -> b foldl :: (b -> a -> b) -> b -> Maybe a -> b foldl' :: (b -> a -> b) -> b -> Maybe a -> b foldr1 :: (a -> a -> a) -> Maybe a -> a foldl1 :: (a -> a -> a) -> Maybe a -> a elem :: Eq a => a -> Maybe a -> Bool maximum :: Ord a => Maybe a -> a | |
Traversable Maybe | |
MonadPlus Maybe | |
Alternative Maybe | |
MonadFailure Maybe | |
Eq a => Eq (Maybe a) | |
Data a => Data (Maybe a) | |
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) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) dataTypeOf :: Maybe a -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) | |
Ord a => Ord (Maybe a) | |
Read a => Read (Maybe a) | |
Show a => Show (Maybe a) | |
Generic (Maybe a) | |
Semigroup a => Semigroup (Maybe a) | |
Semigroup a => Monoid (Maybe a) | |
NormalForm a => NormalForm (Maybe a) | |
Defined in Basement.NormalForm Methods toNormalForm :: Maybe a -> () # | |
SingKind a => SingKind (Maybe a) | |
Defined in GHC.Generics Associated Types type DemoteRep (Maybe a) :: Type | |
Arbitrary a => Arbitrary (Maybe a) Source # | |
IsField a => IsField (Maybe a) Source # | |
Generic1 Maybe | |
SingI (Nothing :: Maybe a) | |
Defined in GHC.Generics | |
SingI a2 => SingI (Just a2 :: Maybe a1) | |
Defined in GHC.Generics | |
From (Maybe a) (Either () a) | |
Defined in Basement.From | |
type Failure Maybe | |
Defined in Basement.Monad | |
type Rep (Maybe a) | |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
data Sing (b :: Maybe a) | |
type Rep1 Maybe | |
Instances
Bounded Ordering | |
Enum Ordering | |
Eq Ordering | |
Data Ordering | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering toConstr :: Ordering -> Constr dataTypeOf :: Ordering -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering | |
Ord Ordering | |
Defined in GHC.Classes | |
Read Ordering | |
Show Ordering | |
Ix Ordering | |
Defined in GHC.Arr | |
Generic Ordering | |
Semigroup Ordering | |
Monoid Ordering | |
type Rep Ordering | |
Instances
Bounded Bool | |
Enum Bool | |
Eq Bool | |
Data Bool | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool dataTypeOf :: Bool -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool | |
Ord Bool | |
Read Bool | |
Show Bool | |
Ix Bool | |
Generic Bool | |
NormalForm Bool | |
Defined in Basement.NormalForm Methods toNormalForm :: Bool -> () # | |
Storable Bool | |
Defined in Foreign.Storable | |
Bits Bool | |
Defined in Data.Bits Methods (.&.) :: Bool -> Bool -> Bool # (.|.) :: Bool -> Bool -> Bool # complement :: Bool -> Bool # shift :: Bool -> Int -> Bool # rotate :: Bool -> Int -> Bool # setBit :: Bool -> Int -> Bool # clearBit :: Bool -> Int -> Bool # complementBit :: Bool -> Int -> Bool # testBit :: Bool -> Int -> Bool # bitSizeMaybe :: Bool -> Maybe Int # shiftL :: Bool -> Int -> Bool # unsafeShiftL :: Bool -> Int -> Bool # shiftR :: Bool -> Int -> Bool # unsafeShiftR :: Bool -> Int -> Bool # rotateL :: Bool -> Int -> Bool # | |
FiniteBits Bool | |
Defined in Data.Bits Methods finiteBitSize :: Bool -> Int countLeadingZeros :: Bool -> Int countTrailingZeros :: Bool -> Int | |
SingKind Bool | |
Defined in GHC.Generics Associated Types type DemoteRep Bool :: Type | |
Arbitrary Bool Source # | |
IsField Bool Source # | |
IsProperty Bool Source # | |
BitOps Bool | |
FiniteBitsOps Bool | |
SingI False | |
Defined in GHC.Generics | |
SingI True | |
Defined in GHC.Generics | |
IsProperty (String, Bool) Source # | |
type Rep Bool | |
Defined in GHC.Generics | |
type DemoteRep Bool | |
Defined in GHC.Generics | |
data Sing (a :: Bool) | |
Instances
Bounded Char | |
Enum Char | |
Eq Char | |
Data Char | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Char dataTypeOf :: Char -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Char) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Char) gmapT :: (forall b. Data b => b -> b) -> Char -> Char gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Char -> r gmapQ :: (forall d. Data d => d -> u) -> Char -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Char -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Char -> m Char gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Char -> m Char | |
Ord Char | |
Read Char | |
Show Char | |
Ix Char | |
PrimType Char | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Char -> CountOf Word8 # primShiftToBytes :: Proxy Char -> Int # primBaUIndex :: ByteArray# -> Offset Char -> Char # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char -> prim Char # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char -> Char -> prim () # primAddrIndex :: Addr# -> Offset Char -> Char # primAddrRead :: PrimMonad prim => Addr# -> Offset Char -> prim Char # primAddrWrite :: PrimMonad prim => Addr# -> Offset Char -> Char -> prim () # | |
NormalForm Char | |
Defined in Basement.NormalForm Methods toNormalForm :: Char -> () # | |
Subtractive Char | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Char :: Type # | |
PrimMemoryComparable Char | |
Defined in Basement.PrimType | |
Storable Char | |
Defined in Foreign.Storable | |
StorableFixed Char Source # | |
Storable Char Source # | |
Arbitrary Char Source # | |
IsField Char Source # | |
IsChar Char | |
PrintfArg Char | |
Defined in Text.Printf | |
Generic1 (URec Char :: k -> Type) | |
IsField [Char] Source # | |
Functor (URec Char :: Type -> Type) | |
Foldable (URec Char :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec Char m -> m foldMap :: Monoid m => (a -> m) -> URec Char a -> m foldr :: (a -> b -> b) -> b -> URec Char a -> b foldr' :: (a -> b -> b) -> b -> URec Char a -> b foldl :: (b -> a -> b) -> b -> URec Char a -> b foldl' :: (b -> a -> b) -> b -> URec Char a -> b foldr1 :: (a -> a -> a) -> URec Char a -> a foldl1 :: (a -> a -> a) -> URec Char a -> a elem :: Eq a => a -> URec Char a -> Bool maximum :: Ord a => URec Char a -> a minimum :: Ord a => URec Char a -> a | |
Traversable (URec Char :: Type -> Type) | |
Eq (URec Char p) | |
Ord (URec Char p) | |
Defined in GHC.Generics | |
Show (URec Char p) | |
Generic (URec Char p) | |
type PrimSize Char | |
Defined in Basement.PrimType | |
type Difference Char | |
Defined in Basement.Numerical.Subtractive | |
type NatNumMaxBound Char | |
Defined in Basement.Nat type NatNumMaxBound Char = 1114111 | |
data URec Char (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Char :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Char p) | |
Defined in GHC.Generics |
Instances
Eq Char7 | |
Ord Char7 | |
Show Char7 | |
PrimType Char7 | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Char7 -> CountOf Word8 # primShiftToBytes :: Proxy Char7 -> Int # primBaUIndex :: ByteArray# -> Offset Char7 -> Char7 # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char7 -> prim Char7 # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Char7 -> Char7 -> prim () # primAddrIndex :: Addr# -> Offset Char7 -> Char7 # primAddrRead :: PrimMonad prim => Addr# -> Offset Char7 -> prim Char7 # primAddrWrite :: PrimMonad prim => Addr# -> Offset Char7 -> Char7 -> prim () # | |
NormalForm Char7 | |
Defined in Basement.NormalForm Methods toNormalForm :: Char7 -> () # | |
Arbitrary Char7 Source # | |
type PrimSize Char7 | |
Defined in Basement.PrimType | |
type NatNumMaxBound Char7 | |
Defined in Basement.Nat type NatNumMaxBound Char7 = 127 |
Instances
Instances
Bifunctor Either | |
Monad (Either e) | |
Functor (Either a) | |
MonadFix (Either e) | |
Defined in Control.Monad.Fix | |
Applicative (Either e) | |
Foldable (Either a) | |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 elem :: Eq a0 => a0 -> Either a a0 -> Bool maximum :: Ord a0 => Either a a0 -> a0 minimum :: Ord a0 => Either a a0 -> a0 | |
Traversable (Either a) | |
MonadFailure (Either a) | |
Generic1 (Either a :: Type -> Type) | |
From (Maybe a) (Either () a) | |
Defined in Basement.From | |
(Eq a, Eq b) => Eq (Either a b) | |
(Data a, Data b) => Data (Either a b) | |
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) gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) toConstr :: Either a b -> Constr dataTypeOf :: Either a b -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) | |
(Ord a, Ord b) => Ord (Either a b) | |
(Read a, Read b) => Read (Either a b) | |
Defined in Data.Either | |
(Show a, Show b) => Show (Either a b) | |
Generic (Either a b) | |
Semigroup (Either a b) | |
(NormalForm l, NormalForm r) => NormalForm (Either l r) | |
Defined in Basement.NormalForm Methods toNormalForm :: Either l r -> () # | |
(Arbitrary l, Arbitrary r) => Arbitrary (Either l r) Source # | |
From (Either a b) (These a b) | |
Defined in Basement.From | |
type Failure (Either a) | |
Defined in Basement.Monad | |
type Rep1 (Either a :: Type -> Type) | |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Rep (Either a b) | |
Defined in GHC.Generics type Rep (Either a b) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) |
Numbers
Instances
Instances
Instances
Instances
Instances
Instances
Instances
Instances
Instances
Bounded Word | |
Enum Word | |
Eq Word | |
Integral Word | |
Data Word | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word dataTypeOf :: Word -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) gmapT :: (forall b. Data b => b -> b) -> Word -> Word gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word | |
Num Word | |
Ord Word | |
Read Word | |
Real Word | |
Defined in GHC.Real Methods toRational :: Word -> Rational | |
Show Word | |
Ix Word | |
PrimType Word | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Word -> CountOf Word8 # primShiftToBytes :: Proxy Word -> Int # primBaUIndex :: ByteArray# -> Offset Word -> Word # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Word -> prim Word # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Word -> Word -> prim () # primAddrIndex :: Addr# -> Offset Word -> Word # primAddrRead :: PrimMonad prim => Addr# -> Offset Word -> prim Word # primAddrWrite :: PrimMonad prim => Addr# -> Offset Word -> Word -> prim () # | |
NormalForm Word | |
Defined in Basement.NormalForm Methods toNormalForm :: Word -> () # | |
Additive Word | |
IsNatural Word | |
Defined in Basement.Numerical.Number | |
Integral Word | |
Defined in Basement.Compat.NumLiteral Methods fromInteger :: Integer -> Word # | |
IsIntegral Word | |
Defined in Basement.Numerical.Number | |
Subtractive Word | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Word :: Type # | |
PrimMemoryComparable Word | |
Defined in Basement.PrimType | |
Storable Word | |
Defined in Foreign.Storable | |
Bits Word | |
Defined in Data.Bits Methods (.&.) :: Word -> Word -> Word # (.|.) :: Word -> Word -> Word # complement :: Word -> Word # shift :: Word -> Int -> Word # rotate :: Word -> Int -> Word # setBit :: Word -> Int -> Word # clearBit :: Word -> Int -> Word # complementBit :: Word -> Int -> Word # testBit :: Word -> Int -> Bool # bitSizeMaybe :: Word -> Maybe Int # shiftL :: Word -> Int -> Word # unsafeShiftL :: Word -> Int -> Word # shiftR :: Word -> Int -> Word # unsafeShiftR :: Word -> Int -> Word # rotateL :: Word -> Int -> Word # | |
FiniteBits Word | |
Defined in Data.Bits Methods finiteBitSize :: Word -> Int countLeadingZeros :: Word -> Int countTrailingZeros :: Word -> Int | |
HasNegation Word | |
Defined in Basement.Compat.NumLiteral | |
Multiplicative Word | |
IDivisible Word | |
Arbitrary Word Source # | |
IsField Word Source # | |
PrintfArg Word | |
Defined in Text.Printf | |
BitOps Word | |
FiniteBitsOps Word | |
IntegralUpsize Word Word64 | |
Defined in Basement.IntegralConv Methods integralUpsize :: Word -> Word64 # | |
IntegralUpsize Word8 Word | |
Defined in Basement.IntegralConv Methods integralUpsize :: Word8 -> Word # | |
IntegralUpsize Word16 Word | |
Defined in Basement.IntegralConv Methods integralUpsize :: Word16 -> Word # | |
IntegralUpsize Word32 Word | |
Defined in Basement.IntegralConv Methods integralUpsize :: Word32 -> Word # | |
IntegralDownsize Word Word8 | |
Defined in Basement.IntegralConv | |
IntegralDownsize Word Word16 | |
Defined in Basement.IntegralConv | |
IntegralDownsize Word Word32 | |
Defined in Basement.IntegralConv | |
Cast Int Word | |
Defined in Basement.Cast | |
Cast Int64 Word | |
Defined in Basement.Cast | |
Cast Word Int | |
Defined in Basement.Cast | |
Cast Word Int64 | |
Defined in Basement.Cast | |
Cast Word Word64 | |
Defined in Basement.Cast | |
Cast Word64 Word | |
Defined in Basement.Cast | |
From Word Word64 | |
Defined in Basement.From | |
From Word8 Word | |
Defined in Basement.From | |
From Word16 Word | |
Defined in Basement.From | |
From Word32 Word | |
Defined in Basement.From | |
From Word (Offset ty) | |
Defined in Basement.From | |
From Word (CountOf ty) | |
Defined in Basement.From | |
Generic1 (URec Word :: k -> Type) | |
From (CountOf ty) Word | |
Defined in Basement.From | |
Functor (URec Word :: Type -> Type) | |
Foldable (URec Word :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec Word m -> m foldMap :: Monoid m => (a -> m) -> URec Word a -> m foldr :: (a -> b -> b) -> b -> URec Word a -> b foldr' :: (a -> b -> b) -> b -> URec Word a -> b foldl :: (b -> a -> b) -> b -> URec Word a -> b foldl' :: (b -> a -> b) -> b -> URec Word a -> b foldr1 :: (a -> a -> a) -> URec Word a -> a foldl1 :: (a -> a -> a) -> URec Word a -> a elem :: Eq a => a -> URec Word a -> Bool maximum :: Ord a => URec Word a -> a minimum :: Ord a => URec Word a -> a | |
Traversable (URec Word :: Type -> Type) | |
Eq (URec Word p) | |
Ord (URec Word p) | |
Defined in GHC.Generics | |
Show (URec Word p) | |
Generic (URec Word p) | |
type PrimSize Word | |
Defined in Basement.PrimType | |
type Difference Word | |
Defined in Basement.Numerical.Subtractive | |
type NatNumMaxBound Word | |
Defined in Basement.Nat | |
data URec Word (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Word :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Word p) | |
Defined in GHC.Generics |
Instances
Instances
Instances
Bounded Int | |
Enum Int | |
Eq Int | |
Integral Int | |
Data Int | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int dataTypeOf :: Int -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int) gmapT :: (forall b. Data b => b -> b) -> Int -> Int gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int -> r gmapQ :: (forall d. Data d => d -> u) -> Int -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Int -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int -> m Int gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int -> m Int | |
Num Int | |
Ord Int | |
Read Int | |
Real Int | |
Defined in GHC.Real Methods toRational :: Int -> Rational | |
Show Int | |
Ix Int | |
PrimType Int | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Int -> CountOf Word8 # primShiftToBytes :: Proxy Int -> Int # primBaUIndex :: ByteArray# -> Offset Int -> Int # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int -> prim Int # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Int -> Int -> prim () # primAddrIndex :: Addr# -> Offset Int -> Int # primAddrRead :: PrimMonad prim => Addr# -> Offset Int -> prim Int # primAddrWrite :: PrimMonad prim => Addr# -> Offset Int -> Int -> prim () # | |
NormalForm Int | |
Defined in Basement.NormalForm Methods toNormalForm :: Int -> () # | |
Additive Int | |
Integral Int | |
Defined in Basement.Compat.NumLiteral Methods fromInteger :: Integer -> Int # | |
IsIntegral Int | |
Defined in Basement.Numerical.Number | |
Subtractive Int | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Int :: Type # | |
PrimMemoryComparable Int | |
Defined in Basement.PrimType | |
Storable Int | |
Bits Int | |
Defined in Data.Bits | |
FiniteBits Int | |
Defined in Data.Bits | |
HasNegation Int | |
Defined in Basement.Compat.NumLiteral | |
Multiplicative Int | |
IDivisible Int | |
Signed Int Source # | |
Arbitrary Int Source # | |
IsField Int Source # | |
PrintfArg Int | |
Defined in Text.Printf | |
IntegralUpsize Int Int64 | |
Defined in Basement.IntegralConv Methods integralUpsize :: Int -> Int64 # | |
IntegralUpsize Int8 Int | |
Defined in Basement.IntegralConv Methods integralUpsize :: Int8 -> Int # | |
IntegralUpsize Int16 Int | |
Defined in Basement.IntegralConv Methods integralUpsize :: Int16 -> Int # | |
IntegralUpsize Int32 Int | |
Defined in Basement.IntegralConv Methods integralUpsize :: Int32 -> Int # | |
IntegralUpsize Word8 Int | |
Defined in Basement.IntegralConv Methods integralUpsize :: Word8 -> Int # | |
IntegralDownsize Int Int8 | |
Defined in Basement.IntegralConv | |
IntegralDownsize Int Int16 | |
Defined in Basement.IntegralConv | |
IntegralDownsize Int Int32 | |
Defined in Basement.IntegralConv | |
IntegralDownsize Int64 Int | |
Defined in Basement.IntegralConv | |
Cast Int Int64 | |
Defined in Basement.Cast | |
Cast Int Word | |
Defined in Basement.Cast | |
Cast Int Word64 | |
Defined in Basement.Cast | |
Cast Int64 Int | |
Defined in Basement.Cast | |
Cast Word Int | |
Defined in Basement.Cast | |
Cast Word64 Int | |
Defined in Basement.Cast | |
From Int Int64 | |
Defined in Basement.From | |
From Int8 Int | |
Defined in Basement.From | |
From Int16 Int | |
Defined in Basement.From | |
From Int32 Int | |
Defined in Basement.From | |
From Word8 Int | |
Defined in Basement.From | |
From Word16 Int | |
Defined in Basement.From | |
From Word32 Int | |
Defined in Basement.From | |
TryFrom Int (Offset ty) | |
Defined in Basement.From | |
TryFrom Int (CountOf ty) | |
Defined in Basement.From | |
Generic1 (URec Int :: k -> Type) | |
From (CountOf ty) Int | |
Defined in Basement.From | |
Functor (URec Int :: Type -> Type) | |
Foldable (URec Int :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec Int m -> m foldMap :: Monoid m => (a -> m) -> URec Int a -> m foldr :: (a -> b -> b) -> b -> URec Int a -> b foldr' :: (a -> b -> b) -> b -> URec Int a -> b foldl :: (b -> a -> b) -> b -> URec Int a -> b foldl' :: (b -> a -> b) -> b -> URec Int a -> b foldr1 :: (a -> a -> a) -> URec Int a -> a foldl1 :: (a -> a -> a) -> URec Int a -> a elem :: Eq a => a -> URec Int a -> Bool maximum :: Ord a => URec Int a -> a minimum :: Ord a => URec Int a -> a | |
Traversable (URec Int :: Type -> Type) | |
Eq (URec Int p) | |
Ord (URec Int p) | |
Show (URec Int p) | |
Generic (URec Int p) | |
type PrimSize Int | |
Defined in Basement.PrimType | |
type Difference Int | |
Defined in Basement.Numerical.Subtractive | |
type NatNumMaxBound Int | |
Defined in Basement.Nat | |
data URec Int (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Int :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Int p) | |
Defined in GHC.Generics |
Instances
Instances
Instances
Eq Float | |
Floating Float | |
Data Float | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Float dataTypeOf :: Float -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Float) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Float) gmapT :: (forall b. Data b => b -> b) -> Float -> Float gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Float -> r gmapQ :: (forall d. Data d => d -> u) -> Float -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Float -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Float -> m Float gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Float -> m Float | |
Ord Float | |
Read Float | |
RealFloat Float | |
Defined in GHC.Float Methods floatRadix :: Float -> Integer floatDigits :: Float -> Int floatRange :: Float -> (Int, Int) decodeFloat :: Float -> (Integer, Int) encodeFloat :: Integer -> Int -> Float significand :: Float -> Float scaleFloat :: Int -> Float -> Float isInfinite :: Float -> Bool isDenormalized :: Float -> Bool isNegativeZero :: Float -> Bool | |
PrimType Float | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Float -> CountOf Word8 # primShiftToBytes :: Proxy Float -> Int # primBaUIndex :: ByteArray# -> Offset Float -> Float # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Float -> prim Float # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Float -> Float -> prim () # primAddrIndex :: Addr# -> Offset Float -> Float # primAddrRead :: PrimMonad prim => Addr# -> Offset Float -> prim Float # primAddrWrite :: PrimMonad prim => Addr# -> Offset Float -> Float -> prim () # | |
NormalForm Float | |
Defined in Basement.NormalForm Methods toNormalForm :: Float -> () # | |
Additive Float | |
Integral Float | |
Defined in Basement.Compat.NumLiteral Methods fromInteger :: Integer -> Float # | |
Subtractive Float | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Float :: Type # | |
Storable Float | |
Defined in Foreign.Storable | |
Fractional Float | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> Float # | |
HasNegation Float | |
Defined in Basement.Compat.NumLiteral | |
Multiplicative Float | |
Trigonometry Float Source # | |
Defined in Foundation.Math.Trigonometry Methods sin :: Float -> Float Source # cos :: Float -> Float Source # tan :: Float -> Float Source # asin :: Float -> Float Source # acos :: Float -> Float Source # atan :: Float -> Float Source # sinh :: Float -> Float Source # cosh :: Float -> Float Source # tanh :: Float -> Float Source # asinh :: Float -> Float Source # | |
FloatingPoint Float Source # | |
Divisible Float | |
IntegralRounding Float Source # | |
Signed Float Source # | |
StorableFixed Float Source # | |
Storable Float Source # | |
Arbitrary Float Source # | |
PrintfArg Float | |
Defined in Text.Printf | |
Generic1 (URec Float :: k -> Type) | |
Functor (URec Float :: Type -> Type) | |
Foldable (URec Float :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec Float m -> m foldMap :: Monoid m => (a -> m) -> URec Float a -> m foldr :: (a -> b -> b) -> b -> URec Float a -> b foldr' :: (a -> b -> b) -> b -> URec Float a -> b foldl :: (b -> a -> b) -> b -> URec Float a -> b foldl' :: (b -> a -> b) -> b -> URec Float a -> b foldr1 :: (a -> a -> a) -> URec Float a -> a foldl1 :: (a -> a -> a) -> URec Float a -> a elem :: Eq a => a -> URec Float a -> Bool maximum :: Ord a => URec Float a -> a minimum :: Ord a => URec Float a -> a | |
Traversable (URec Float :: Type -> Type) | |
Defined in Data.Traversable | |
Eq (URec Float p) | |
Ord (URec Float p) | |
Defined in GHC.Generics | |
Show (URec Float p) | |
Generic (URec Float p) | |
type PrimSize Float | |
Defined in Basement.PrimType | |
type Difference Float | |
Defined in Basement.Numerical.Subtractive | |
data URec Float (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Float :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Float p) | |
Defined in GHC.Generics |
Instances
Eq Double | |
Floating Double | |
Data Double | |
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 gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Double dataTypeOf :: Double -> DataType dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Double) dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Double) gmapT :: (forall b. Data b => b -> b) -> Double -> Double gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Double -> r gmapQ :: (forall d. Data d => d -> u) -> Double -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Double -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Double -> m Double gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Double -> m Double | |
Ord Double | |
Read Double | |
RealFloat Double | |
Defined in GHC.Float Methods floatRadix :: Double -> Integer floatDigits :: Double -> Int floatRange :: Double -> (Int, Int) decodeFloat :: Double -> (Integer, Int) encodeFloat :: Integer -> Int -> Double significand :: Double -> Double scaleFloat :: Int -> Double -> Double isInfinite :: Double -> Bool isDenormalized :: Double -> Bool isNegativeZero :: Double -> Bool | |
PrimType Double | |
Defined in Basement.PrimType Methods primSizeInBytes :: Proxy Double -> CountOf Word8 # primShiftToBytes :: Proxy Double -> Int # primBaUIndex :: ByteArray# -> Offset Double -> Double # primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Double -> prim Double # primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset Double -> Double -> prim () # primAddrIndex :: Addr# -> Offset Double -> Double # primAddrRead :: PrimMonad prim => Addr# -> Offset Double -> prim Double # primAddrWrite :: PrimMonad prim => Addr# -> Offset Double -> Double -> prim () # | |
NormalForm Double | |
Defined in Basement.NormalForm Methods toNormalForm :: Double -> () # | |
Additive Double | |
Integral Double | |
Defined in Basement.Compat.NumLiteral Methods fromInteger :: Integer -> Double # | |
Subtractive Double | |
Defined in Basement.Numerical.Subtractive Associated Types type Difference Double :: Type # | |
Storable Double | |
Fractional Double | |
Defined in Basement.Compat.NumLiteral Methods fromRational :: Rational -> Double # | |
HasNegation Double | |
Defined in Basement.Compat.NumLiteral | |
Multiplicative Double | |
Trigonometry Double Source # | |
Defined in Foundation.Math.Trigonometry Methods sin :: Double -> Double Source # cos :: Double -> Double Source # tan :: Double -> Double Source # asin :: Double -> Double Source # acos :: Double -> Double Source # atan :: Double -> Double Source # sinh :: Double -> Double Source # cosh :: Double -> Double Source # tanh :: Double -> Double Source # asinh :: Double -> Double Source # | |
FloatingPoint Double Source # | |
Divisible Double | |
IntegralRounding Double Source # | |
Signed Double Source # | |
StorableFixed Double Source # | |
Storable Double Source # | |
Arbitrary Double Source # | |
IsField Double Source # | |
PrintfArg Double | |
Defined in Text.Printf | |
Generic1 (URec Double :: k -> Type) | |
Functor (URec Double :: Type -> Type) | |
Foldable (URec Double :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => URec Double m -> m foldMap :: Monoid m => (a -> m) -> URec Double a -> m foldr :: (a -> b -> b) -> b -> URec Double a -> b foldr' :: (a -> b -> b) -> b -> URec Double a -> b foldl :: (b -> a -> b) -> b -> URec Double a -> b foldl' :: (b -> a -> b) -> b -> URec Double a -> b foldr1 :: (a -> a -> a) -> URec Double a -> a foldl1 :: (a -> a -> a) -> URec Double a -> a toList :: URec Double a -> [a] length :: URec Double a -> Int elem :: Eq a => a -> URec Double a -> Bool maximum :: Ord a => URec Double a -> a minimum :: Ord a => URec Double a -> a | |
Traversable (URec Double :: Type -> Type) | |
Defined in Data.Traversable | |
Eq (URec Double p) | |
Ord (URec Double p) | |
Defined in GHC.Generics Methods compare :: URec Double p -> URec Double p -> Ordering # (<) :: URec Double p -> URec Double p -> Bool # (<=) :: URec Double p -> URec Double p -> Bool # (>) :: URec Double p -> URec Double p -> Bool # (>=) :: URec Double p -> URec Double p -> Bool # | |
Show (URec Double p) | |
Generic (URec Double p) | |
type PrimSize Double | |
Defined in Basement.PrimType | |
type Difference Double | |
Defined in Basement.Numerical.Subtractive | |
data URec Double (p :: k) | |
Defined in GHC.Generics | |
type Rep1 (URec Double :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (URec Double p) | |
Defined in GHC.Generics |
Instances
Instances
Collection types
Instances
Minimal complete definition
primSizeInBytes, primShiftToBytes, primBaUIndex, primMbaURead, primMbaUWrite, primAddrIndex, primAddrRead, primAddrWrite
Instances
Instances
Instances
Numeric functions
fromIntegral :: (Integral a, Num b) => a -> b #
realToFrac :: (Real a, Fractional b) => a -> b #
Monoids
Minimal complete definition
Instances
class Semigroup a => Monoid a where #
Minimal complete definition
Instances
Collection
class (IsList c, Item c ~ Element c) => Collection c where Source #
A set of methods for ordered colection
Methods
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
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
Minimal complete definition
(take, drop | splitAt), (revTake, revDrop | revSplitAt), splitOn, (break | span), (breakEnd | spanEnd), intersperse, filter, reverse, uncons, unsnoc, snoc, cons, find, sortBy, singleton, replicate
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 (
.
It inserts the list mconcat
(intersperse
xs xss))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 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.
isPrefixOf :: Eq c => c -> c -> Bool Source #
Takes two collections and returns True iff the first collection is a prefix of the second.
isSuffixOf :: Eq (Element c) => c -> c -> Bool Source #
Takes two collections and returns True iff the first collection is a suffix of the second.
isSuffixOf :: Eq c => c -> c -> Bool Source #
Takes two collections and returns True iff the first collection is a suffix of the second.
isInfixOf :: Eq (Element c) => c -> c -> Bool Source #
Takes two collections and returns True iff the first collection is an infix of the second.
isInfixOf :: Eq c => c -> c -> Bool Source #
Takes two collections and returns True iff the first collection is an infix of the second.
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
IsList c => IsList (NonEmpty c) | |
Eq a => Eq (NonEmpty a) | |
Show a => Show (NonEmpty a) | |
Collection c => Collection (NonEmpty c) Source # | |
Defined in Foundation.Collection.Collection Methods null :: NonEmpty c -> Bool Source # length :: NonEmpty c -> CountOf (Element (NonEmpty c)) Source # elem :: (Eq a, a ~ Element (NonEmpty c)) => Element (NonEmpty c) -> NonEmpty c -> Bool Source # notElem :: (Eq a, a ~ Element (NonEmpty c)) => Element (NonEmpty c) -> NonEmpty c -> Bool Source # maximum :: (Ord a, a ~ Element (NonEmpty c)) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source # minimum :: (Ord a, a ~ Element (NonEmpty c)) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source # any :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source # all :: (Element (NonEmpty c) -> Bool) -> NonEmpty c -> Bool Source # | |
type Item (NonEmpty c) | |
Defined in Basement.NonEmpty | |
type Element (NonEmpty a) Source # | |
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
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
Foldable Bitmap Source # | |
Foldable [a] Source # | |
PrimType ty => Foldable (UArray ty) Source # | |
PrimType ty => Foldable (Block ty) Source # | |
Foldable (Array ty) Source # | |
Foldable (DList a) Source # | |
PrimType ty => Foldable (ChunkedUArray ty) Source # | |
Defined in Foundation.Array.Chunked.Unboxed Methods foldl' :: (a -> Element (ChunkedUArray ty) -> a) -> a -> ChunkedUArray ty -> a Source # foldr :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source # foldr' :: (Element (ChunkedUArray ty) -> a -> a) -> a -> ChunkedUArray ty -> a Source # | |
PrimType ty => Foldable (BlockN n ty) Source # | |
Foldable (ListN n a) Source # | |
Maybe
listToMaybe :: [a] -> Maybe a #
maybeToList :: Maybe a -> [a] #
Either
partitionEithers :: [Either a b] -> ([a], [b]) #
Function
Applicative
Monad
Exceptions
class (Typeable e, Show e) => Exception e where #
Minimal complete definition
Nothing
Methods
toException :: e -> SomeException #
fromException :: SomeException -> Maybe e #
displayException :: e -> String #
Instances
data SomeException #
Instances
Show SomeException | |
Defined in GHC.Exception.Type Methods showsPrec :: Int -> SomeException -> ShowS show :: SomeException -> String showList :: [SomeException] -> ShowS | |
Exception SomeException | |
Defined in GHC.Exception.Type Methods toException :: SomeException -> SomeException # fromException :: SomeException -> Maybe SomeException # displayException :: SomeException -> String # |
data IOException #
Instances
Eq IOException | |
Defined in GHC.IO.Exception | |
Show IOException | |
Defined in GHC.IO.Exception Methods showsPrec :: Int -> IOException -> ShowS show :: IOException -> String showList :: [IOException] -> ShowS | |
Exception IOException | |
Defined in GHC.IO.Exception Methods toException :: IOException -> SomeException # fromException :: SomeException -> Maybe IOException # displayException :: IOException -> String # |
Proxy
data Proxy (t :: k) :: forall k. k -> Type #
Constructors
Proxy |
Instances
Generic1 (Proxy :: k -> Type) | |
Monad (Proxy :: Type -> Type) | |
Functor (Proxy :: Type -> Type) | |
Applicative (Proxy :: Type -> Type) | |
Foldable (Proxy :: Type -> Type) | |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m foldMap :: Monoid m => (a -> m) -> Proxy a -> m foldr :: (a -> b -> b) -> b -> Proxy a -> b foldr' :: (a -> b -> b) -> b -> Proxy a -> b foldl :: (b -> a -> b) -> b -> Proxy a -> b foldl' :: (b -> a -> b) -> b -> Proxy a -> b foldr1 :: (a -> a -> a) -> Proxy a -> a foldl1 :: (a -> a -> a) -> Proxy a -> a elem :: Eq a => a -> Proxy a -> Bool maximum :: Ord a => Proxy a -> a | |
Traversable (Proxy :: Type -> Type) | |
MonadPlus (Proxy :: Type -> Type) | |
Alternative (Proxy :: Type -> Type) | |
Bounded (Proxy t) | |
Enum (Proxy s) | |
Eq (Proxy s) | |
Data t => Data (Proxy t) | |
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) gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) dataTypeOf :: Proxy t -> DataType dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) | |
Ord (Proxy s) | |
Read (Proxy t) | |
Defined in Data.Proxy | |
Show (Proxy s) | |
Ix (Proxy s) | |
Generic (Proxy t) | |
Semigroup (Proxy s) | |
Monoid (Proxy s) | |
type Rep1 (Proxy :: k -> Type) | |
Defined in GHC.Generics | |
type Rep (Proxy t) | |
Defined in GHC.Generics |
asProxyTypeOf :: a -> proxy a -> a #
Partial
Partialiality wrapper.
partial :: a -> Partial a Source #
Create a value that is partial. this can only be
unwrap using the fromPartial
function
data PartialError Source #
An error related to the evaluation of a Partial value that failed.
it contains the name of the function and the reason for failure
Instances
Eq PartialError Source # | |
Defined in Foundation.Partial | |
Show PartialError Source # | |
Defined in Foundation.Partial Methods showsPrec :: Int -> PartialError -> ShowS show :: PartialError -> String showList :: [PartialError] -> ShowS | |
Exception PartialError Source # | |
Defined in Foundation.Partial Methods toException :: PartialError -> SomeException # fromException :: SomeException -> Maybe PartialError # displayException :: PartialError -> String # |
fromPartial :: Partial a -> a Source #
Dewrap a possible partial value
ifThenElse :: Bool -> a -> a -> a #