Newer
Older
and :: forall (t :: * -> *). Foldable t => t GHC.Types.Bool -> GHC.Types.Bool
any :: forall (t :: * -> *) a. Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
asum :: forall (t :: * -> *) (f :: * -> *) a. (Foldable t, GHC.Internal.Base.Alternative f) => t (f a) -> f a
concat :: forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concatMap :: forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
find :: forall (t :: * -> *) a. Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Internal.Maybe.Maybe a
foldlM :: forall (t :: * -> *) (m :: * -> *) b a. (Foldable t, GHC.Internal.Base.Monad m) => (b -> a -> m b) -> b -> t a -> m b
foldrM :: forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, GHC.Internal.Base.Monad m) => (a -> b -> m b) -> b -> t a -> m b
forM_ :: forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, GHC.Internal.Base.Monad m) => t a -> (a -> m b) -> m ()
for_ :: forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, GHC.Internal.Base.Applicative f) => t a -> (a -> f b) -> f ()
mapM_ :: forall (t :: * -> *) (m :: * -> *) a b. (Foldable t, GHC.Internal.Base.Monad m) => (a -> m b) -> t a -> m ()
maximumBy :: forall (t :: * -> *) a. Foldable t => (a -> a -> GHC.Types.Ordering) -> t a -> a
minimumBy :: forall (t :: * -> *) a. Foldable t => (a -> a -> GHC.Types.Ordering) -> t a -> a
msum :: forall (t :: * -> *) (m :: * -> *) a. (Foldable t, GHC.Internal.Base.MonadPlus m) => t (m a) -> m a
notElem :: forall (t :: * -> *) a. (Foldable t, GHC.Classes.Eq a) => a -> t a -> GHC.Types.Bool
or :: forall (t :: * -> *). Foldable t => t GHC.Types.Bool -> GHC.Types.Bool
sequenceA_ :: forall (t :: * -> *) (f :: * -> *) a. (Foldable t, GHC.Internal.Base.Applicative f) => t (f a) -> f ()
sequence_ :: forall (t :: * -> *) (m :: * -> *) a. (Foldable t, GHC.Internal.Base.Monad m) => t (m a) -> m ()
traverse_ :: forall (t :: * -> *) (f :: * -> *) a b. (Foldable t, GHC.Internal.Base.Applicative f) => (a -> f b) -> t a -> f ()
module Data.Foldable1 where
-- Safety: Trustworthy
type Foldable1 :: (* -> *) -> Constraint
class GHC.Internal.Data.Foldable.Foldable t => Foldable1 t where
fold1 :: forall m. GHC.Internal.Base.Semigroup m => t m -> m
foldMap1 :: forall m a. GHC.Internal.Base.Semigroup m => (a -> m) -> t a -> m
foldMap1' :: forall m a. GHC.Internal.Base.Semigroup m => (a -> m) -> t a -> m
toNonEmpty :: forall a. t a -> GHC.Internal.Base.NonEmpty a
maximum :: forall a. GHC.Classes.Ord a => t a -> a
minimum :: forall a. GHC.Classes.Ord a => t a -> a
head :: forall a. t a -> a
last :: forall a. t a -> a
foldrMap1 :: forall a b. (a -> b) -> (a -> b -> b) -> t a -> b
foldlMap1' :: forall a b. (a -> b) -> (b -> a -> b) -> t a -> b
foldlMap1 :: forall a b. (a -> b) -> (b -> a -> b) -> t a -> b
foldrMap1' :: forall a b. (a -> b) -> (a -> b -> b) -> t a -> b
{-# MINIMAL foldMap1 | foldrMap1 #-}
foldl1 :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> a) -> t a -> a
foldl1' :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> a) -> t a -> a
foldlM1 :: forall (t :: * -> *) (m :: * -> *) a. (Foldable1 t, GHC.Internal.Base.Monad m) => (a -> a -> m a) -> t a -> m a
foldlMapM1 :: forall (t :: * -> *) (m :: * -> *) a b. (Foldable1 t, GHC.Internal.Base.Monad m) => (a -> m b) -> (b -> a -> m b) -> t a -> m b
foldr1 :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> a) -> t a -> a
foldr1' :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> a) -> t a -> a
foldrM1 :: forall (t :: * -> *) (m :: * -> *) a. (Foldable1 t, GHC.Internal.Base.Monad m) => (a -> a -> m a) -> t a -> m a
foldrMapM1 :: forall (t :: * -> *) (m :: * -> *) a b. (Foldable1 t, GHC.Internal.Base.Monad m) => (a -> m b) -> (a -> b -> m b) -> t a -> m b
intercalate1 :: forall (t :: * -> *) m. (Foldable1 t, GHC.Internal.Base.Semigroup m) => m -> t m -> m
maximumBy :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> GHC.Types.Ordering) -> t a -> a
minimumBy :: forall (t :: * -> *) a. Foldable1 t => (a -> a -> GHC.Types.Ordering) -> t a -> a
module Data.Function where
($) :: forall (repa :: GHC.Types.RuntimeRep) (repb :: GHC.Types.RuntimeRep) (a :: TYPE repa) (b :: TYPE repb). (a -> b) -> a -> b
(&) :: forall (r :: GHC.Types.RuntimeRep) a (b :: TYPE r). a -> (a -> b) -> b
(.) :: forall b c a. (b -> c) -> (a -> b) -> a -> c
applyWhen :: forall a. GHC.Types.Bool -> (a -> a) -> a -> a
const :: forall a b. a -> b -> a
fix :: forall a. (a -> a) -> a
flip :: forall a b c. (a -> b -> c) -> b -> a -> c
id :: forall a. a -> a
on :: forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
module Data.Functor where
1064
1065
1066
1067
1068
1069
1070
1071
1072
1073
1074
1075
1076
1077
1078
1079
1080
1081
1082
1083
1084
1085
1086
1087
1088
1089
1090
1091
1092
1093
1094
1095
($>) :: forall (f :: * -> *) a b. Functor f => f a -> b -> f b
(<$>) :: forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
(<&>) :: forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
type Functor :: (* -> *) -> Constraint
class Functor f where
fmap :: forall a b. (a -> b) -> f a -> f b
(<$) :: forall a b. a -> f b -> f a
{-# MINIMAL fmap #-}
unzip :: forall (f :: * -> *) a b. Functor f => f (a, b) -> (f a, f b)
void :: forall (f :: * -> *) a. Functor f => f a -> f ()
module Data.Functor.Classes where
-- Safety: Safe
type Eq1 :: (* -> *) -> Constraint
class (forall a. GHC.Classes.Eq a => GHC.Classes.Eq (f a)) => Eq1 f where
liftEq :: forall a b. (a -> b -> GHC.Types.Bool) -> f a -> f b -> GHC.Types.Bool
default liftEq :: forall (f' :: * -> * -> *) c a b. (f ~ f' c, Eq2 f', GHC.Classes.Eq c) => (a -> b -> GHC.Types.Bool) -> f a -> f b -> GHC.Types.Bool
{-# MINIMAL #-}
type Eq2 :: (* -> * -> *) -> Constraint
class (forall a. GHC.Classes.Eq a => Eq1 (f a)) => Eq2 f where
liftEq2 :: forall a b c d. (a -> b -> GHC.Types.Bool) -> (c -> d -> GHC.Types.Bool) -> f a c -> f b d -> GHC.Types.Bool
{-# MINIMAL liftEq2 #-}
type Ord1 :: (* -> *) -> Constraint
class (Eq1 f, forall a. GHC.Classes.Ord a => GHC.Classes.Ord (f a)) => Ord1 f where
liftCompare :: forall a b. (a -> b -> GHC.Types.Ordering) -> f a -> f b -> GHC.Types.Ordering
default liftCompare :: forall (f' :: * -> * -> *) c a b. (f ~ f' c, Ord2 f', GHC.Classes.Ord c) => (a -> b -> GHC.Types.Ordering) -> f a -> f b -> GHC.Types.Ordering
{-# MINIMAL #-}
type Ord2 :: (* -> * -> *) -> Constraint
class (Eq2 f, forall a. GHC.Classes.Ord a => Ord1 (f a)) => Ord2 f where
liftCompare2 :: forall a b c d. (a -> b -> GHC.Types.Ordering) -> (c -> d -> GHC.Types.Ordering) -> f a c -> f b d -> GHC.Types.Ordering
{-# MINIMAL liftCompare2 #-}
type Read1 :: (* -> *) -> Constraint
class (forall a. GHC.Internal.Read.Read a => GHC.Internal.Read.Read (f a)) => Read1 f where
liftReadsPrec :: forall a. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS (f a)
liftReadList :: forall a. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [f a]
liftReadPrec :: forall a. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec (f a)
liftReadListPrec :: forall a. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [f a]
{-# MINIMAL liftReadsPrec | liftReadPrec #-}
type Read2 :: (* -> * -> *) -> Constraint
class (forall a. GHC.Internal.Read.Read a => Read1 (f a)) => Read2 f where
liftReadsPrec2 :: forall a b. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS b) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [b] -> GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS (f a b)
liftReadList2 :: forall a b. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS b) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [b] -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [f a b]
liftReadPrec2 :: forall a b. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec b -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [b] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec (f a b)
liftReadListPrec2 :: forall a b. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec b -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [b] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [f a b]
{-# MINIMAL liftReadsPrec2 | liftReadPrec2 #-}
type Show1 :: (* -> *) -> Constraint
class (forall a. GHC.Internal.Show.Show a => GHC.Internal.Show.Show (f a)) => Show1 f where
liftShowsPrec :: forall a. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> ([a] -> GHC.Internal.Show.ShowS) -> GHC.Types.Int -> f a -> GHC.Internal.Show.ShowS
default liftShowsPrec :: forall (f' :: * -> * -> *) b a. (f ~ f' b, Show2 f', GHC.Internal.Show.Show b) => (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> ([a] -> GHC.Internal.Show.ShowS) -> GHC.Types.Int -> f a -> GHC.Internal.Show.ShowS
liftShowList :: forall a. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> ([a] -> GHC.Internal.Show.ShowS) -> [f a] -> GHC.Internal.Show.ShowS
{-# MINIMAL #-}
type Show2 :: (* -> * -> *) -> Constraint
class (forall a. GHC.Internal.Show.Show a => Show1 (f a)) => Show2 f where
liftShowsPrec2 :: forall a b. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> ([a] -> GHC.Internal.Show.ShowS) -> (GHC.Types.Int -> b -> GHC.Internal.Show.ShowS) -> ([b] -> GHC.Internal.Show.ShowS) -> GHC.Types.Int -> f a b -> GHC.Internal.Show.ShowS
liftShowList2 :: forall a b. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> ([a] -> GHC.Internal.Show.ShowS) -> (GHC.Types.Int -> b -> GHC.Internal.Show.ShowS) -> ([b] -> GHC.Internal.Show.ShowS) -> [f a b] -> GHC.Internal.Show.ShowS
{-# MINIMAL liftShowsPrec2 #-}
compare1 :: forall (f :: * -> *) a. (Ord1 f, GHC.Classes.Ord a) => f a -> f a -> GHC.Types.Ordering
compare2 :: forall (f :: * -> * -> *) a b. (Ord2 f, GHC.Classes.Ord a, GHC.Classes.Ord b) => f a b -> f a b -> GHC.Types.Ordering
eq1 :: forall (f :: * -> *) a. (Eq1 f, GHC.Classes.Eq a) => f a -> f a -> GHC.Types.Bool
eq2 :: forall (f :: * -> * -> *) a b. (Eq2 f, GHC.Classes.Eq a, GHC.Classes.Eq b) => f a b -> f a b -> GHC.Types.Bool
1124
1125
1126
1127
1128
1129
1130
1131
1132
1133
1134
1135
1136
1137
1138
1139
1140
1141
1142
1143
1144
1145
1146
1147
liftReadList2Default :: forall (f :: * -> * -> *) a b. Read2 f => (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS b) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [b] -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [f a b]
liftReadListDefault :: forall (f :: * -> *) a. Read1 f => (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [a] -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS [f a]
liftReadListPrec2Default :: forall (f :: * -> * -> *) a b. Read2 f => GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec b -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [b] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [f a b]
liftReadListPrecDefault :: forall (f :: * -> *) a. Read1 f => GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [a] -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec [f a]
readBinaryWith :: forall a b t. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec b -> GHC.Internal.Base.String -> (a -> b -> t) -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec t
readData :: forall a. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a
readPrec1 :: forall (f :: * -> *) a. (Read1 f, GHC.Internal.Read.Read a) => GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec (f a)
readPrec2 :: forall (f :: * -> * -> *) a b. (Read2 f, GHC.Internal.Read.Read a, GHC.Internal.Read.Read b) => GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec (f a b)
readUnaryWith :: forall a t. GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec a -> GHC.Internal.Base.String -> (a -> t) -> GHC.Internal.Text.ParserCombinators.ReadPrec.ReadPrec t
readsBinary1 :: forall (f :: * -> *) (g :: * -> *) a t. (Read1 f, Read1 g, GHC.Internal.Read.Read a) => GHC.Internal.Base.String -> (f a -> g a -> t) -> GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS t
readsBinaryWith :: forall a b t. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS b) -> GHC.Internal.Base.String -> (a -> b -> t) -> GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS t
readsData :: forall a. (GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a
readsPrec1 :: forall (f :: * -> *) a. (Read1 f, GHC.Internal.Read.Read a) => GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS (f a)
readsPrec2 :: forall (f :: * -> * -> *) a b. (Read2 f, GHC.Internal.Read.Read a, GHC.Internal.Read.Read b) => GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS (f a b)
readsUnary :: forall a t. GHC.Internal.Read.Read a => GHC.Internal.Base.String -> (a -> t) -> GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS t
readsUnary1 :: forall (f :: * -> *) a t. (Read1 f, GHC.Internal.Read.Read a) => GHC.Internal.Base.String -> (f a -> t) -> GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS t
readsUnaryWith :: forall a t. (GHC.Types.Int -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS a) -> GHC.Internal.Base.String -> (a -> t) -> GHC.Internal.Base.String -> GHC.Internal.Text.ParserCombinators.ReadP.ReadS t
showsBinary1 :: forall (f :: * -> *) (g :: * -> *) a. (Show1 f, Show1 g, GHC.Internal.Show.Show a) => GHC.Internal.Base.String -> GHC.Types.Int -> f a -> g a -> GHC.Internal.Show.ShowS
showsBinaryWith :: forall a b. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> (GHC.Types.Int -> b -> GHC.Internal.Show.ShowS) -> GHC.Internal.Base.String -> GHC.Types.Int -> a -> b -> GHC.Internal.Show.ShowS
showsPrec1 :: forall (f :: * -> *) a. (Show1 f, GHC.Internal.Show.Show a) => GHC.Types.Int -> f a -> GHC.Internal.Show.ShowS
showsPrec2 :: forall (f :: * -> * -> *) a b. (Show2 f, GHC.Internal.Show.Show a, GHC.Internal.Show.Show b) => GHC.Types.Int -> f a b -> GHC.Internal.Show.ShowS
showsUnary :: forall a. GHC.Internal.Show.Show a => GHC.Internal.Base.String -> GHC.Types.Int -> a -> GHC.Internal.Show.ShowS
showsUnary1 :: forall (f :: * -> *) a. (Show1 f, GHC.Internal.Show.Show a) => GHC.Internal.Base.String -> GHC.Types.Int -> f a -> GHC.Internal.Show.ShowS
showsUnaryWith :: forall a. (GHC.Types.Int -> a -> GHC.Internal.Show.ShowS) -> GHC.Internal.Base.String -> GHC.Types.Int -> a -> GHC.Internal.Show.ShowS
module Data.Functor.Compose where
-- Safety: Trustworthy
type role Compose representational nominal nominal
type Compose :: forall {k} {k1}. (k -> *) -> (k1 -> k) -> k1 -> *
newtype Compose f g a = Compose {getCompose :: f (g a)}
module Data.Functor.Const where
1157
1158
1159
1160
1161
1162
1163
1164
1165
1166
1167
1168
1169
1170
1171
1172
1173
1174
1175
1176
1177
1178
1179
1180
1181
type role Const representational phantom
type Const :: forall {k}. * -> k -> *
newtype Const a b = Const {getConst :: a}
module Data.Functor.Contravariant where
-- Safety: Trustworthy
($<) :: forall (f :: * -> *) b a. Contravariant f => f b -> b -> f a
(>$$<) :: forall (f :: * -> *) b a. Contravariant f => f b -> (a -> b) -> f a
(>$<) :: forall (f :: * -> *) a b. Contravariant f => (a -> b) -> f b -> f a
type Comparison :: * -> *
newtype Comparison a = Comparison {getComparison :: a -> a -> GHC.Types.Ordering}
type Contravariant :: (* -> *) -> Constraint
class Contravariant f where
contramap :: forall a' a. (a' -> a) -> f a -> f a'
(>$) :: forall b a. b -> f b -> f a
{-# MINIMAL contramap #-}
type Equivalence :: * -> *
newtype Equivalence a = Equivalence {getEquivalence :: a -> a -> GHC.Types.Bool}
type Op :: * -> * -> *
newtype Op a b = Op {getOp :: b -> a}
type Predicate :: * -> *
newtype Predicate a = Predicate {getPredicate :: a -> GHC.Types.Bool}
comparisonEquivalence :: forall a. Comparison a -> Equivalence a
defaultComparison :: forall a. GHC.Classes.Ord a => Comparison a
defaultEquivalence :: forall a. GHC.Classes.Eq a => Equivalence a
phantom :: forall (f :: * -> *) a b. (GHC.Internal.Base.Functor f, Contravariant f) => f a -> f b
module Data.Functor.Identity where
type Identity :: * -> *
newtype Identity a = Identity {runIdentity :: a}
module Data.Functor.Product where
-- Safety: Safe
type role Product representational representational nominal
type Product :: forall {k}. (k -> *) -> (k -> *) -> k -> *
data Product f g a = Pair (f a) (g a)
module Data.Functor.Sum where
-- Safety: Safe
type role Sum representational representational nominal
type Sum :: forall {k}. (k -> *) -> (k -> *) -> k -> *
data Sum f g a = InL (f a) | InR (g a)
module Data.IORef where
type IORef :: * -> *
newtype IORef a = ...
atomicModifyIORef :: forall a b. IORef a -> (a -> (a, b)) -> GHC.Types.IO b
atomicModifyIORef' :: forall a b. IORef a -> (a -> (a, b)) -> GHC.Types.IO b
atomicWriteIORef :: forall a. IORef a -> a -> GHC.Types.IO ()
mkWeakIORef :: forall a. IORef a -> GHC.Types.IO () -> GHC.Types.IO (GHC.Internal.Weak.Weak (IORef a))
modifyIORef :: forall a. IORef a -> (a -> a) -> GHC.Types.IO ()
modifyIORef' :: forall a. IORef a -> (a -> a) -> GHC.Types.IO ()
newIORef :: forall a. a -> GHC.Types.IO (IORef a)
readIORef :: forall a. IORef a -> GHC.Types.IO a
writeIORef :: forall a. IORef a -> a -> GHC.Types.IO ()
module Data.Int where
type Int :: *
data Int = ...
type Int16 :: *
data Int16 = ...
type Int32 :: *
data Int32 = ...
type Int64 :: *
data Int64 = ...
type Int8 :: *
data Int8 = ...
module Data.Ix where
type Ix :: * -> Constraint
class GHC.Classes.Ord a => Ix a where
range :: (a, a) -> [a]
index :: (a, a) -> a -> GHC.Types.Int
...
inRange :: (a, a) -> a -> GHC.Types.Bool
rangeSize :: (a, a) -> GHC.Types.Int
...
{-# MINIMAL range, (index | GHC.Internal.Ix.unsafeIndex), inRange #-}
module Data.Kind where
type Constraint :: *
type Constraint = GHC.Prim.CONSTRAINT GHC.Types.LiftedRep
type role FUN nominal representational representational
type FUN :: forall (n :: GHC.Types.Multiplicity) -> forall {q :: GHC.Types.RuntimeRep} {r :: GHC.Types.RuntimeRep}. TYPE q -> TYPE r -> *
data FUN n a b
type Type :: *
type Type = TYPE GHC.Types.LiftedRep
module Data.List where
-- Safety: Safe
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> GHC.Types.Int -> a
(!?) :: forall a. [a] -> GHC.Types.Int -> GHC.Internal.Maybe.Maybe a
(++) :: forall a. [a] -> [a] -> [a]
type List :: * -> *
data List a = ...
(\\) :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
all :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
and :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool
any :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Types.Bool
break :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a])
concat :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t [a] -> [a]
concatMap :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> [b]) -> t a -> [b]
cycle :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
delete :: forall a. GHC.Classes.Eq a => a -> [a] -> [a]
deleteBy :: forall a. (a -> a -> GHC.Types.Bool) -> a -> [a] -> [a]
deleteFirstsBy :: forall a. (a -> a -> GHC.Types.Bool) -> [a] -> [a] -> [a]
drop :: forall a. GHC.Types.Int -> [a] -> [a]
dropWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a]
dropWhileEnd :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a]
elem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Classes.Eq a) => a -> t a -> GHC.Types.Bool
elemIndex :: forall a. GHC.Classes.Eq a => a -> [a] -> GHC.Internal.Maybe.Maybe GHC.Types.Int
elemIndices :: forall a. GHC.Classes.Eq a => a -> [a] -> [GHC.Types.Int]
filter :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a]
find :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> GHC.Types.Bool) -> t a -> GHC.Internal.Maybe.Maybe a
findIndex :: forall a. (a -> GHC.Types.Bool) -> [a] -> GHC.Internal.Maybe.Maybe GHC.Types.Int
findIndices :: forall a. (a -> GHC.Types.Bool) -> [a] -> [GHC.Types.Int]
foldl :: forall (t :: * -> *) b a. GHC.Internal.Data.Foldable.Foldable t => (b -> a -> b) -> b -> t a -> b
foldl' :: forall (t :: * -> *) b a. GHC.Internal.Data.Foldable.Foldable t => (b -> a -> b) -> b -> t a -> b
foldl1 :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> a -> a) -> t a -> a
foldl1' :: forall a. GHC.Internal.Stack.Types.HasCallStack => (a -> a -> a) -> [a] -> a
foldr :: forall (t :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable t => (a -> b -> b) -> b -> t a -> b
foldr1 :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> a -> a) -> t a -> a
genericDrop :: forall i a. GHC.Internal.Real.Integral i => i -> [a] -> [a]
genericIndex :: forall i a. GHC.Internal.Real.Integral i => [a] -> i -> a
genericLength :: forall i a. GHC.Internal.Num.Num i => [a] -> i
genericReplicate :: forall i a. GHC.Internal.Real.Integral i => i -> a -> [a]
genericSplitAt :: forall i a. GHC.Internal.Real.Integral i => i -> [a] -> ([a], [a])
genericTake :: forall i a. GHC.Internal.Real.Integral i => i -> [a] -> [a]
group :: forall a. GHC.Classes.Eq a => [a] -> [[a]]
groupBy :: forall a. (a -> a -> GHC.Types.Bool) -> [a] -> [[a]]
head :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a
init :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
inits :: forall a. [a] -> [[a]]
insert :: forall a. GHC.Classes.Ord a => a -> [a] -> [a]
insertBy :: forall a. (a -> a -> GHC.Types.Ordering) -> a -> [a] -> [a]
intercalate :: forall a. [a] -> [[a]] -> [a]
intersect :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
intersectBy :: forall a. (a -> a -> GHC.Types.Bool) -> [a] -> [a] -> [a]
intersperse :: forall a. a -> [a] -> [a]
isInfixOf :: forall a. GHC.Classes.Eq a => [a] -> [a] -> GHC.Types.Bool
isPrefixOf :: forall a. GHC.Classes.Eq a => [a] -> [a] -> GHC.Types.Bool
isSubsequenceOf :: forall a. GHC.Classes.Eq a => [a] -> [a] -> GHC.Types.Bool
isSuffixOf :: forall a. GHC.Classes.Eq a => [a] -> [a] -> GHC.Types.Bool
iterate :: forall a. (a -> a) -> a -> [a]
iterate' :: forall a. (a -> a) -> a -> [a]
last :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> a
length :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Types.Int
lines :: GHC.Internal.Base.String -> [GHC.Internal.Base.String]
lookup :: forall a b. GHC.Classes.Eq a => a -> [(a, b)] -> GHC.Internal.Maybe.Maybe b
map :: forall a b. (a -> b) -> [a] -> [b]
mapAccumL :: forall (t :: * -> *) s a b. GHC.Internal.Data.Traversable.Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumR :: forall (t :: * -> *) s a b. GHC.Internal.Data.Traversable.Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
maximum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Classes.Ord a) => t a -> a
maximumBy :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> a -> GHC.Types.Ordering) -> t a -> a
minimum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Classes.Ord a) => t a -> a
minimumBy :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => (a -> a -> GHC.Types.Ordering) -> t a -> a
notElem :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Classes.Eq a) => a -> t a -> GHC.Types.Bool
nub :: forall a. GHC.Classes.Eq a => [a] -> [a]
nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> [a] -> [a]
null :: forall (t :: * -> *) a. GHC.Internal.Data.Foldable.Foldable t => t a -> GHC.Types.Bool
or :: forall (t :: * -> *). GHC.Internal.Data.Foldable.Foldable t => t GHC.Types.Bool -> GHC.Types.Bool
partition :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a])
permutations :: forall a. [a] -> [[a]]
product :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a
repeat :: forall a. a -> [a]
replicate :: forall a. GHC.Types.Int -> a -> [a]
reverse :: forall a. [a] -> [a]
scanl :: forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl' :: forall b a. (b -> a -> b) -> b -> [a] -> [b]
scanl1 :: forall a. (a -> a -> a) -> [a] -> [a]
scanr :: forall a b. (a -> b -> b) -> b -> [a] -> [b]
scanr1 :: forall a. (a -> a -> a) -> [a] -> [a]
singleton :: forall a. a -> [a]
sort :: forall a. GHC.Classes.Ord a => [a] -> [a]
sortBy :: forall a. (a -> a -> GHC.Types.Ordering) -> [a] -> [a]
sortOn :: forall b a. GHC.Classes.Ord b => (a -> b) -> [a] -> [a]
span :: forall a. (a -> GHC.Types.Bool) -> [a] -> ([a], [a])
splitAt :: forall a. GHC.Types.Int -> [a] -> ([a], [a])
stripPrefix :: forall a. GHC.Classes.Eq a => [a] -> [a] -> GHC.Internal.Maybe.Maybe [a]
subsequences :: forall a. [a] -> [[a]]
sum :: forall (t :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable t, GHC.Internal.Num.Num a) => t a -> a
tail :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> [a]
tails :: forall a. [a] -> [[a]]
take :: forall a. GHC.Types.Int -> [a] -> [a]
takeWhile :: forall a. (a -> GHC.Types.Bool) -> [a] -> [a]
transpose :: forall a. [[a]] -> [[a]]
uncons :: forall a. [a] -> GHC.Internal.Maybe.Maybe (a, [a])
unfoldr :: forall b a. (b -> GHC.Internal.Maybe.Maybe (a, b)) -> b -> [a]
union :: forall a. GHC.Classes.Eq a => [a] -> [a] -> [a]
unionBy :: forall a. (a -> a -> GHC.Types.Bool) -> [a] -> [a] -> [a]
unlines :: [GHC.Internal.Base.String] -> GHC.Internal.Base.String
unsnoc :: forall a. [a] -> GHC.Internal.Maybe.Maybe ([a], a)
unwords :: [GHC.Internal.Base.String] -> GHC.Internal.Base.String
unzip :: forall a b. [(a, b)] -> ([a], [b])
unzip3 :: forall a b c. [(a, b, c)] -> ([a], [b], [c])
unzip4 :: forall a b c d. [(a, b, c, d)] -> ([a], [b], [c], [d])
unzip5 :: forall a b c d e. [(a, b, c, d, e)] -> ([a], [b], [c], [d], [e])
unzip6 :: forall a b c d e f. [(a, b, c, d, e, f)] -> ([a], [b], [c], [d], [e], [f])
unzip7 :: forall a b c d e f g. [(a, b, c, d, e, f, g)] -> ([a], [b], [c], [d], [e], [f], [g])
words :: GHC.Internal.Base.String -> [GHC.Internal.Base.String]
zip :: forall a b. [a] -> [b] -> [(a, b)]
zip3 :: forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip4 :: forall a b c d. [a] -> [b] -> [c] -> [d] -> [(a, b, c, d)]
zip5 :: forall a b c d e. [a] -> [b] -> [c] -> [d] -> [e] -> [(a, b, c, d, e)]
zip6 :: forall a b c d e f. [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [(a, b, c, d, e, f)]
zip7 :: forall a b c d e f g. [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [(a, b, c, d, e, f, g)]
zipWith :: forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith3 :: forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith4 :: forall a b c d e. (a -> b -> c -> d -> e) -> [a] -> [b] -> [c] -> [d] -> [e]
zipWith5 :: forall a b c d e f. (a -> b -> c -> d -> e -> f) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f]
zipWith6 :: forall a b c d e f g. (a -> b -> c -> d -> e -> f -> g) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g]
zipWith7 :: forall a b c d e f g h. (a -> b -> c -> d -> e -> f -> g -> h) -> [a] -> [b] -> [c] -> [d] -> [e] -> [f] -> [g] -> [h]
module Data.List.NonEmpty where
-- Safety: Trustworthy
(!!) :: forall a. GHC.Internal.Stack.Types.HasCallStack => NonEmpty a -> GHC.Types.Int -> a
(<|) :: forall a. a -> NonEmpty a -> NonEmpty a
type NonEmpty :: * -> *
data NonEmpty a = a :| [a]
append :: forall a. NonEmpty a -> NonEmpty a -> NonEmpty a
appendList :: forall a. NonEmpty a -> [a] -> NonEmpty a
break :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
cons :: forall a. a -> NonEmpty a -> NonEmpty a
cycle :: forall a. NonEmpty a -> NonEmpty a
drop :: forall a. GHC.Types.Int -> NonEmpty a -> [a]
dropWhile :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> [a]
filter :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> [a]
fromList :: forall a. GHC.Internal.Stack.Types.HasCallStack => [a] -> NonEmpty a
group :: forall (f :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable f, GHC.Classes.Eq a) => f a -> [NonEmpty a]
group1 :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty (NonEmpty a)
groupAllWith :: forall b a. GHC.Classes.Ord b => (a -> b) -> [a] -> [NonEmpty a]
groupAllWith1 :: forall b a. GHC.Classes.Ord b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupBy :: forall (f :: * -> *) a. GHC.Internal.Data.Foldable.Foldable f => (a -> a -> GHC.Types.Bool) -> f a -> [NonEmpty a]
groupBy1 :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty (NonEmpty a)
groupWith :: forall (f :: * -> *) b a. (GHC.Internal.Data.Foldable.Foldable f, GHC.Classes.Eq b) => (a -> b) -> f a -> [NonEmpty a]
groupWith1 :: forall b a. GHC.Classes.Eq b => (a -> b) -> NonEmpty a -> NonEmpty (NonEmpty a)
head :: forall a. NonEmpty a -> a
init :: forall a. NonEmpty a -> [a]
inits :: forall (f :: * -> *) a. GHC.Internal.Data.Foldable.Foldable f => f a -> NonEmpty [a]
inits1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
insert :: forall (f :: * -> *) a. (GHC.Internal.Data.Foldable.Foldable f, GHC.Classes.Ord a) => a -> f a -> NonEmpty a
intersperse :: forall a. a -> NonEmpty a -> NonEmpty a
isPrefixOf :: forall a. GHC.Classes.Eq a => [a] -> NonEmpty a -> GHC.Types.Bool
iterate :: forall a. (a -> a) -> a -> NonEmpty a
last :: forall a. NonEmpty a -> a
length :: forall a. NonEmpty a -> GHC.Types.Int
map :: forall a b. (a -> b) -> NonEmpty a -> NonEmpty b
nonEmpty :: forall a. [a] -> GHC.Internal.Maybe.Maybe (NonEmpty a)
nub :: forall a. GHC.Classes.Eq a => NonEmpty a -> NonEmpty a
nubBy :: forall a. (a -> a -> GHC.Types.Bool) -> NonEmpty a -> NonEmpty a
partition :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
permutations :: forall a. [a] -> NonEmpty [a]
permutations1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
prependList :: forall a. [a] -> NonEmpty a -> NonEmpty a
repeat :: forall a. a -> NonEmpty a
reverse :: forall a. NonEmpty a -> NonEmpty a
scanl :: forall (f :: * -> *) b a. GHC.Internal.Data.Foldable.Foldable f => (b -> a -> b) -> b -> f a -> NonEmpty b
scanl1 :: forall a. (a -> a -> a) -> NonEmpty a -> NonEmpty a
scanr :: forall (f :: * -> *) a b. GHC.Internal.Data.Foldable.Foldable f => (a -> b -> b) -> b -> f a -> NonEmpty b
scanr1 :: forall a. (a -> a -> a) -> NonEmpty a -> NonEmpty a
singleton :: forall a. a -> NonEmpty a
some1 :: forall (f :: * -> *) a. GHC.Internal.Base.Alternative f => f a -> f (NonEmpty a)
sort :: forall a. GHC.Classes.Ord a => NonEmpty a -> NonEmpty a
sortBy :: forall a. (a -> a -> GHC.Types.Ordering) -> NonEmpty a -> NonEmpty a
sortOn :: forall b a. GHC.Classes.Ord b => (a -> b) -> NonEmpty a -> NonEmpty a
sortWith :: forall o a. GHC.Classes.Ord o => (a -> o) -> NonEmpty a -> NonEmpty a
span :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> ([a], [a])
splitAt :: forall a. GHC.Types.Int -> NonEmpty a -> ([a], [a])
tail :: forall a. NonEmpty a -> [a]
tails :: forall (f :: * -> *) a. GHC.Internal.Data.Foldable.Foldable f => f a -> NonEmpty [a]
tails1 :: forall a. NonEmpty a -> NonEmpty (NonEmpty a)
take :: forall a. GHC.Types.Int -> NonEmpty a -> [a]
takeWhile :: forall a. (a -> GHC.Types.Bool) -> NonEmpty a -> [a]
toList :: forall a. NonEmpty a -> [a]
transpose :: forall a. NonEmpty (NonEmpty a) -> NonEmpty (NonEmpty a)
uncons :: forall a. NonEmpty a -> (a, GHC.Internal.Maybe.Maybe (NonEmpty a))
unfold :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
unfoldr :: forall a b. (a -> (b, GHC.Internal.Maybe.Maybe a)) -> a -> NonEmpty b
unzip :: forall (f :: * -> *) a b. GHC.Internal.Base.Functor f => f (a, b) -> (f a, f b)
xor :: NonEmpty GHC.Types.Bool -> GHC.Types.Bool
zip :: forall a b. NonEmpty a -> NonEmpty b -> NonEmpty (a, b)
zipWith :: forall a b c. (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c
module Data.Maybe where
type Maybe :: * -> *
data Maybe a = Nothing | Just a
catMaybes :: forall a. [Maybe a] -> [a]
fromJust :: forall a. GHC.Internal.Stack.Types.HasCallStack => Maybe a -> a
fromMaybe :: forall a. a -> Maybe a -> a
isJust :: forall a. Maybe a -> GHC.Types.Bool
isNothing :: forall a. Maybe a -> GHC.Types.Bool
listToMaybe :: forall a. [a] -> Maybe a
mapMaybe :: forall a b. (a -> Maybe b) -> [a] -> [b]
maybe :: forall b a. b -> (a -> b) -> Maybe a -> b
maybeToList :: forall a. Maybe a -> [a]
module Data.Monoid where
-- Safety: Safe
(<>) :: forall a. GHC.Internal.Base.Semigroup a => a -> a -> a
type All :: *
newtype All = All {getAll :: GHC.Types.Bool}
type role Alt representational nominal
type Alt :: forall {k}. (k -> *) -> k -> *
newtype Alt f a = Alt {getAlt :: f a}
type Any :: *
newtype Any = Any {getAny :: GHC.Types.Bool}
type role Ap representational nominal
type Ap :: forall {k}. (k -> *) -> k -> *
newtype Ap f a = Ap {getAp :: f a}
type Dual :: * -> *
newtype Dual a = Dual {getDual :: a}
type Endo :: * -> *
newtype Endo a = Endo {appEndo :: a -> a}
type First :: * -> *
newtype First a = First {getFirst :: GHC.Internal.Maybe.Maybe a}
type Last :: * -> *
newtype Last a = Last {getLast :: GHC.Internal.Maybe.Maybe a}
type Monoid :: * -> Constraint
class GHC.Internal.Base.Semigroup a => Monoid a where
mempty :: a
mappend :: a -> a -> a
mconcat :: [a] -> a
{-# MINIMAL mempty | mconcat #-}
type Product :: * -> *
newtype Product a = Product {getProduct :: a}
type Sum :: * -> *
newtype Sum a = Sum {getSum :: a}
module Data.Ord where
type Down :: * -> *
newtype Down a = Down {getDown :: a}
type Ord :: * -> Constraint
class GHC.Classes.Eq a => Ord a where
compare :: a -> a -> Ordering
(<) :: a -> a -> GHC.Types.Bool
(<=) :: a -> a -> GHC.Types.Bool
(>) :: a -> a -> GHC.Types.Bool
(>=) :: a -> a -> GHC.Types.Bool
max :: a -> a -> a
min :: a -> a -> a
{-# MINIMAL compare | (<=) #-}
type Ordering :: *
data Ordering = LT | EQ | GT
clamp :: forall a. Ord a => (a, a) -> a -> a
comparing :: forall a b. Ord a => (b -> a) -> b -> b -> Ordering
module Data.Proxy where
type role KProxy phantom
type KProxy :: * -> *
data KProxy t = KProxy
type role Proxy phantom
type Proxy :: forall {k}. k -> *
data Proxy t = Proxy
asProxyTypeOf :: forall a (proxy :: * -> *). a -> proxy a -> a
module Data.Ratio where
-- Safety: Safe
(%) :: forall a. GHC.Internal.Real.Integral a => a -> a -> Ratio a
type Ratio :: * -> *
data Ratio a = ...
type Rational :: *
type Rational = Ratio GHC.Num.Integer.Integer
approxRational :: forall a. GHC.Internal.Real.RealFrac a => a -> a -> Rational
denominator :: forall a. Ratio a -> a
numerator :: forall a. Ratio a -> a
module Data.STRef where
type role STRef nominal representational
type STRef :: * -> * -> *
data STRef s a = ...
modifySTRef :: forall s a. STRef s a -> (a -> a) -> GHC.Internal.ST.ST s ()
modifySTRef' :: forall s a. STRef s a -> (a -> a) -> GHC.Internal.ST.ST s ()
newSTRef :: forall a s. a -> GHC.Internal.ST.ST s (STRef s a)
readSTRef :: forall s a. STRef s a -> GHC.Internal.ST.ST s a
writeSTRef :: forall s a. STRef s a -> a -> GHC.Internal.ST.ST s ()
module Data.STRef.Lazy where
-- Safety: Safe
type role STRef nominal representational
type STRef :: * -> * -> *
data STRef s a = ...
modifySTRef :: forall s a. STRef s a -> (a -> a) -> GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s ()
newSTRef :: forall a s. a -> GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s (STRef s a)
readSTRef :: forall s a. STRef s a -> GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s a
writeSTRef :: forall s a. STRef s a -> a -> GHC.Internal.Control.Monad.ST.Lazy.Imp.ST s ()
module Data.STRef.Strict where
-- Safety: Safe
type role STRef nominal representational
type STRef :: * -> * -> *
data STRef s a = ...
modifySTRef :: forall s a. STRef s a -> (a -> a) -> GHC.Internal.ST.ST s ()
modifySTRef' :: forall s a. STRef s a -> (a -> a) -> GHC.Internal.ST.ST s ()
newSTRef :: forall a s. a -> GHC.Internal.ST.ST s (STRef s a)
readSTRef :: forall s a. STRef s a -> GHC.Internal.ST.ST s a
writeSTRef :: forall s a. STRef s a -> a -> GHC.Internal.ST.ST s ()
1562
1563
1564
1565
1566
1567
1568
1569
1570
1571
1572
1573
1574
1575
1576
1577
1578
1579
1580
1581
1582
1583
1584
1585
1586
1587
1588
1589
1590
1591
module Data.Semigroup where
-- Safety: Trustworthy
type All :: *
newtype All = All {getAll :: GHC.Types.Bool}
type Any :: *
newtype Any = Any {getAny :: GHC.Types.Bool}
type Arg :: * -> * -> *
data Arg a b = Arg a b
type ArgMax :: * -> * -> *
type ArgMax a b = Max (Arg a b)
type ArgMin :: * -> * -> *
type ArgMin a b = Min (Arg a b)
type Dual :: * -> *
newtype Dual a = Dual {getDual :: a}
type Endo :: * -> *
newtype Endo a = Endo {appEndo :: a -> a}
type First :: * -> *
newtype First a = First {getFirst :: a}
type Last :: * -> *
newtype Last a = Last {getLast :: a}
type Max :: * -> *
newtype Max a = Max {getMax :: a}
type Min :: * -> *
newtype Min a = Min {getMin :: a}
type Product :: * -> *
newtype Product a = Product {getProduct :: a}
type Semigroup :: * -> Constraint
class Semigroup a where
(<>) :: a -> a -> a
sconcat :: GHC.Internal.Base.NonEmpty a -> a
stimes :: forall b. GHC.Internal.Real.Integral b => b -> a -> a
{-# MINIMAL (<>) | sconcat #-}
type Sum :: * -> *
newtype Sum a = Sum {getSum :: a}
type WrappedMonoid :: * -> *
newtype WrappedMonoid m = WrapMonoid {unwrapMonoid :: m}
cycle1 :: forall m. Semigroup m => m -> m
diff :: forall m. Semigroup m => m -> Endo m
mtimesDefault :: forall b a. (GHC.Internal.Real.Integral b, GHC.Internal.Base.Monoid a) => b -> a -> a
stimesIdempotent :: forall b a. GHC.Internal.Real.Integral b => b -> a -> a
stimesIdempotentMonoid :: forall b a. (GHC.Internal.Real.Integral b, GHC.Internal.Base.Monoid a) => b -> a -> a
stimesMonoid :: forall b a. (GHC.Internal.Real.Integral b, GHC.Internal.Base.Monoid a) => b -> a -> a
module Data.String where
type IsString :: * -> Constraint
class IsString a where
fromString :: String -> a
{-# MINIMAL fromString #-}
type String :: *
type String = [GHC.Types.Char]
lines :: String -> [String]
unlines :: [String] -> String
unwords :: [String] -> String
words :: String -> [String]
module Data.Traversable where
type Traversable :: (* -> *) -> Constraint
class (GHC.Internal.Base.Functor t, GHC.Internal.Data.Foldable.Foldable t) => Traversable t where
traverse :: forall (f :: * -> *) a b. GHC.Internal.Base.Applicative f => (a -> f b) -> t a -> f (t b)
sequenceA :: forall (f :: * -> *) a. GHC.Internal.Base.Applicative f => t (f a) -> f (t a)
mapM :: forall (m :: * -> *) a b. GHC.Internal.Base.Monad m => (a -> m b) -> t a -> m (t b)
sequence :: forall (m :: * -> *) a. GHC.Internal.Base.Monad m => t (m a) -> m (t a)
{-# MINIMAL traverse | sequenceA #-}
fmapDefault :: forall (t :: * -> *) a b. Traversable t => (a -> b) -> t a -> t b
foldMapDefault :: forall (t :: * -> *) m a. (Traversable t, GHC.Internal.Base.Monoid m) => (a -> m) -> t a -> m
for :: forall (t :: * -> *) (f :: * -> *) a b. (Traversable t, GHC.Internal.Base.Applicative f) => t a -> (a -> f b) -> f (t b)
forAccumM :: forall (m :: * -> *) (t :: * -> *) s a b. (GHC.Internal.Base.Monad m, Traversable t) => s -> t a -> (s -> a -> m (s, b)) -> m (s, t b)
forM :: forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, GHC.Internal.Base.Monad m) => t a -> (a -> m b) -> m (t b)
mapAccumL :: forall (t :: * -> *) s a b. Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumM :: forall (m :: * -> *) (t :: * -> *) s a b. (GHC.Internal.Base.Monad m, Traversable t) => (s -> a -> m (s, b)) -> s -> t a -> m (s, t b)
mapAccumR :: forall (t :: * -> *) s a b. Traversable t => (s -> a -> (s, b)) -> s -> t a -> (s, t b)
module Data.Tuple where
1639
1640
1641
1642
1643
1644
1645
1646
1647
1648
1649
1650
1651
1652
1653
1654
1655
1656
1657
1658
1659
1660
1661
1662
pattern Solo :: forall a. a -> Solo a
type Solo :: * -> *
data Solo a = MkSolo a
curry :: forall a b c. ((a, b) -> c) -> a -> b -> c
fst :: forall a b. (a, b) -> a
getSolo :: forall a. Solo a -> a
snd :: forall a b. (a, b) -> b
swap :: forall a b. (a, b) -> (b, a)
uncurry :: forall a b c. (a -> b -> c) -> (a, b) -> c
module Data.Type.Bool where
-- Safety: Safe
type (&&) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool
type family (&&) a b where
forall (a :: GHC.Types.Bool). (&&) GHC.Types.False a = GHC.Types.False
forall (a :: GHC.Types.Bool). (&&) GHC.Types.True a = a
forall (a :: GHC.Types.Bool). (&&) a GHC.Types.False = GHC.Types.False
forall (a :: GHC.Types.Bool). (&&) a GHC.Types.True = a
forall (a :: GHC.Types.Bool). (&&) a a = a
type If :: forall {k}. GHC.Types.Bool -> k -> k -> k
type family If cond tru fls where
forall k (tru :: k) (fls :: k). If GHC.Types.True tru fls = tru
forall k (tru :: k) (fls :: k). If GHC.Types.False tru fls = fls
type Not :: GHC.Types.Bool -> GHC.Types.Bool
type family Not a = res | res -> a where
Not GHC.Types.False = GHC.Types.True
Not GHC.Types.True = GHC.Types.False
type (||) :: GHC.Types.Bool -> GHC.Types.Bool -> GHC.Types.Bool
type family (||) a b where
forall (a :: GHC.Types.Bool). (||) GHC.Types.False a = a
forall (a :: GHC.Types.Bool). (||) GHC.Types.True a = GHC.Types.True
forall (a :: GHC.Types.Bool). (||) a GHC.Types.False = a
forall (a :: GHC.Types.Bool). (||) a GHC.Types.True = GHC.Types.True
forall (a :: GHC.Types.Bool). (||) a a = a
module Data.Type.Coercion where
-- Safety: None
type Coercion :: forall {k}. k -> k -> *
data Coercion a b where
Coercion :: forall {k} (a :: k) (b :: k). Coercible a b => Coercion a b
type TestCoercion :: forall {k}. (k -> *) -> Constraint
class TestCoercion f where
testCoercion :: forall (a :: k) (b :: k). f a -> f b -> GHC.Internal.Maybe.Maybe (Coercion a b)
{-# MINIMAL testCoercion #-}
coerceWith :: forall a b. Coercion a b -> a -> b
gcoerceWith :: forall {k} (a :: k) (b :: k) r. Coercion a b -> (Coercible a b => r) -> r
repr :: forall {k} (a :: k) (b :: k). (a GHC.Internal.Data.Type.Equality.:~: b) -> Coercion a b
sym :: forall {k} (a :: k) (b :: k). Coercion a b -> Coercion b a
trans :: forall {k} (a :: k) (b :: k) (c :: k). Coercion a b -> Coercion b c -> Coercion a c
module Data.Type.Equality where
type role (:~:) nominal nominal
type (:~:) :: forall {k}. k -> k -> *
data (:~:) a b where
Refl :: forall {k} (a :: k). (:~:) a a
type role (:~~:) nominal nominal
type (:~~:) :: forall k1 k2. k1 -> k2 -> *
data (:~~:) a b where
HRefl :: forall {k1} (a :: k1). (:~~:) a a
type (==) :: forall k. k -> k -> GHC.Types.Bool
type family (==) a b where
forall k1 k2 (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (==) (f a) (g b) = (f == g) GHC.Internal.Data.Type.Bool.&& (a == b)
forall k (a :: k). (==) a a = GHC.Types.True
forall k (_1 :: k) (_2 :: k). (==) _1 _2 = GHC.Types.False
type TestEquality :: forall {k}. (k -> *) -> Constraint
class TestEquality f where
testEquality :: forall (a :: k) (b :: k). f a -> f b -> GHC.Internal.Maybe.Maybe (a :~: b)
{-# MINIMAL testEquality #-}
apply :: forall {k1} {k2} (f :: k1 -> k2) (g :: k1 -> k2) (a :: k1) (b :: k1). (f :~: g) -> (a :~: b) -> f a :~: g b
castWith :: forall a b. (a :~: b) -> a -> b
gcastWith :: forall {k} (a :: k) (b :: k) r. (a :~: b) -> ((a ~ b) => r) -> r
inner :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> a :~: b
outer :: forall {k1} {k2} (f :: k1 -> k2) (a :: k1) (g :: k1 -> k2) (b :: k1). (f a :~: g b) -> f :~: g
sym :: forall {k} (a :: k) (b :: k). (a :~: b) -> b :~: a
trans :: forall {k} (a :: k) (b :: k) (c :: k). (a :~: b) -> (b :~: c) -> a :~: c
type (~) :: forall k. k -> k -> Constraint
class (a ~ b) => (~) a b
{-# MINIMAL #-}
type (~~) :: forall k0 k1. k0 -> k1 -> Constraint
class (a ~~ b) => (~~) a b
{-# MINIMAL #-}
module Data.Type.Ord where
type (<) :: forall {t}. t -> t -> Constraint
type (<) x y = GHC.Internal.TypeError.Assert (x <? y) (GHC.Internal.Data.Type.Ord.LtErrMsg x y) :: Constraint
type (<=) :: forall {t}. t -> t -> Constraint
type (<=) x y = GHC.Internal.TypeError.Assert (x <=? y) (GHC.Internal.Data.Type.Ord.LeErrMsg x y) :: Constraint
type (<=?) :: forall k. k -> k -> GHC.Types.Bool
type (<=?) m n = OrdCond (Compare m n) GHC.Types.True GHC.Types.True GHC.Types.False :: GHC.Types.Bool
type (<?) :: forall k. k -> k -> GHC.Types.Bool
type (<?) m n = OrdCond (Compare m n) GHC.Types.True GHC.Types.False GHC.Types.False :: GHC.Types.Bool
type (>) :: forall {t}. t -> t -> Constraint
type (>) x y = GHC.Internal.TypeError.Assert (x >? y) (GHC.Internal.Data.Type.Ord.GtErrMsg x y) :: Constraint
type (>=) :: forall {t}. t -> t -> Constraint
type (>=) x y = GHC.Internal.TypeError.Assert (x >=? y) (GHC.Internal.Data.Type.Ord.GeErrMsg x y) :: Constraint
1736
1737
1738
1739
1740
1741
1742
1743
1744
1745
1746
1747
1748
1749
1750
1751
1752
1753
1754
1755
1756
1757
1758
type (>=?) :: forall k. k -> k -> GHC.Types.Bool
type (>=?) m n = OrdCond (Compare m n) GHC.Types.False GHC.Types.True GHC.Types.True :: GHC.Types.Bool
type (>?) :: forall k. k -> k -> GHC.Types.Bool
type (>?) m n = OrdCond (Compare m n) GHC.Types.False GHC.Types.False GHC.Types.True :: GHC.Types.Bool
type Compare :: forall k. k -> k -> GHC.Types.Ordering
type family Compare a b
type Max :: forall k. k -> k -> k
type Max m n = OrdCond (Compare m n) n n m :: k
type Min :: forall k. k -> k -> k
type Min m n = OrdCond (Compare m n) m m n :: k
type OrdCond :: forall k. GHC.Types.Ordering -> k -> k -> k -> k
type family OrdCond o lt eq gt where
forall k (lt :: k) (eq :: k) (gt :: k). OrdCond GHC.Types.LT lt eq gt = lt
forall k (lt :: k) (eq :: k) (gt :: k). OrdCond GHC.Types.EQ lt eq gt = eq
forall k (lt :: k) (eq :: k) (gt :: k). OrdCond GHC.Types.GT lt eq gt = gt
type role OrderingI nominal nominal
type OrderingI :: forall {k}. k -> k -> *
data OrderingI a b where
LTI :: forall {k} (a :: k) (b :: k). (Compare a b ~ GHC.Types.LT) => OrderingI a b
EQI :: forall {k} (a :: k). (Compare a a ~ GHC.Types.EQ) => OrderingI a a
GTI :: forall {k} (a :: k) (b :: k). (Compare a b ~ GHC.Types.GT) => OrderingI a b
module Data.Typeable where
type role (:~:) nominal nominal
type (:~:) :: forall {k}. k -> k -> *
data (:~:) a b where
Refl :: forall {k} (a :: k). (:~:) a a
type role (:~~:) nominal nominal
type (:~~:) :: forall k1 k2. k1 -> k2 -> *
data (:~~:) a b where
HRefl :: forall {k1} (a :: k1). (:~~:) a a
type role Proxy phantom
type Proxy :: forall {k}. k -> *
data Proxy t = Proxy
type TyCon :: *
data TyCon = ...
type TypeRep :: *
type TypeRep = ghc-internal-0.1.0.0:GHC.Internal.Data.Typeable.Internal.SomeTypeRep
type Typeable :: forall k. k -> Constraint
class Typeable a where
...
{-# MINIMAL ghc-internal-0.1.0.0:GHC.Internal.Data.Typeable.Internal.typeRep# #-}
cast :: forall a b. (Typeable a, Typeable b) => a -> GHC.Internal.Maybe.Maybe b
decT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Data.Either.Either ((a :~: b) -> GHC.Internal.Base.Void) (a :~: b)
eqT :: forall {k} (a :: k) (b :: k). (Typeable a, Typeable b) => GHC.Internal.Maybe.Maybe (a :~: b)
funResultTy :: TypeRep -> TypeRep -> GHC.Internal.Maybe.Maybe TypeRep
gcast :: forall {k} (a :: k) (b :: k) (c :: k -> *). (Typeable a, Typeable b) => c a -> GHC.Internal.Maybe.Maybe (c b)
gcast1 :: forall {k1} {k2} (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1) (a :: k2). (Typeable t, Typeable t') => c (t a) -> GHC.Internal.Maybe.Maybe (c (t' a))
gcast2 :: forall {k1} {k2} {k3} (c :: k1 -> *) (t :: k2 -> k3 -> k1) (t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3). (Typeable t, Typeable t') => c (t a b) -> GHC.Internal.Maybe.Maybe (c (t' a b))
hdecT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => GHC.Internal.Data.Either.Either ((a :~~: b) -> GHC.Internal.Base.Void) (a :~~: b)
heqT :: forall {k1} {k2} (a :: k1) (b :: k2). (Typeable a, Typeable b) => GHC.Internal.Maybe.Maybe (a :~~: b)
mkFunTy :: TypeRep -> TypeRep -> TypeRep
rnfTyCon :: TyCon -> ()
rnfTypeRep :: TypeRep -> ()
showsTypeRep :: TypeRep -> GHC.Internal.Show.ShowS
splitTyConApp :: TypeRep -> (TyCon, [TypeRep])
trLiftedRep :: ghc-internal-0.1.0.0:GHC.Internal.Data.Typeable.Internal.TypeRep GHC.Types.LiftedRep
tyConFingerprint :: TyCon -> GHC.Internal.Fingerprint.Type.Fingerprint
tyConModule :: TyCon -> GHC.Internal.Base.String
tyConName :: TyCon -> GHC.Internal.Base.String
tyConPackage :: TyCon -> GHC.Internal.Base.String
typeOf :: forall a. Typeable a => a -> TypeRep
typeOf1 :: forall (t :: * -> *) a. Typeable t => t a -> TypeRep
typeOf2 :: forall (t :: * -> * -> *) a b. Typeable t => t a b -> TypeRep
typeOf3 :: forall (t :: * -> * -> * -> *) a b c. Typeable t => t a b c -> TypeRep
typeOf4 :: forall (t :: * -> * -> * -> * -> *) a b c d. Typeable t => t a b c d -> TypeRep
typeOf5 :: forall (t :: * -> * -> * -> * -> * -> *) a b c d e. Typeable t => t a b c d e -> TypeRep
typeOf6 :: forall (t :: * -> * -> * -> * -> * -> * -> *) a b c d e f. Typeable t => t a b c d e f -> TypeRep
typeOf7 :: forall (t :: * -> * -> * -> * -> * -> * -> * -> *) a b c d e f g. Typeable t => t a b c d e f g -> TypeRep
typeRep :: forall {k} (proxy :: k -> *) (a :: k). Typeable a => proxy a -> TypeRep
typeRepArgs :: TypeRep -> [TypeRep]
typeRepFingerprint :: TypeRep -> GHC.Internal.Fingerprint.Type.Fingerprint
typeRepTyCon :: TypeRep -> TyCon
module Data.Unique where
type Unique :: *
newtype Unique = ...
hashUnique :: Unique -> GHC.Types.Int
newUnique :: GHC.Types.IO Unique
module Data.Version where
data Version = Version {versionBranch :: [GHC.Types.Int], versionTags :: [GHC.Internal.Base.String]}
makeVersion :: [GHC.Types.Int] -> Version
parseVersion :: GHC.Internal.Text.ParserCombinators.ReadP.ReadP Version
showVersion :: Version -> GHC.Internal.Base.String
module Data.Void where
type Void :: *
data Void
absurd :: forall a. Void -> a
vacuous :: forall (f :: * -> *) a. GHC.Internal.Base.Functor f => f Void -> f a
1832
1833
1834
1835
1836
1837
1838
1839
1840
1841
1842
1843
1844
1845
1846
1847
1848
1849
1850
1851
1852
1853
module Data.Word where
-- Safety: Safe
type Word :: *
data Word = ...
type Word16 :: *
data Word16 = ...
type Word32 :: *
data Word32 = ...
type Word64 :: *
data Word64 = ...
type Word8 :: *
data Word8 = ...
bitReverse16 :: Word16 -> Word16
bitReverse32 :: Word32 -> Word32
bitReverse64 :: Word64 -> Word64
bitReverse8 :: Word8 -> Word8
byteSwap16 :: Word16 -> Word16
byteSwap32 :: Word32 -> Word32
byteSwap64 :: Word64 -> Word64
module Debug.Trace where
flushEventLog :: GHC.Types.IO ()
putTraceMsg :: GHC.Internal.Base.String -> GHC.Types.IO ()
trace :: forall a. GHC.Internal.Base.String -> a -> a
traceEvent :: forall a. GHC.Internal.Base.String -> a -> a
traceEventIO :: GHC.Internal.Base.String -> GHC.Types.IO ()
traceEventWith :: forall a. (a -> GHC.Internal.Base.String) -> a -> a
traceIO :: GHC.Internal.Base.String -> GHC.Types.IO ()
traceId :: GHC.Internal.Base.String -> GHC.Internal.Base.String
traceM :: forall (f :: * -> *). GHC.Internal.Base.Applicative f => GHC.Internal.Base.String -> f ()
traceMarker :: forall a. GHC.Internal.Base.String -> a -> a
traceMarkerIO :: GHC.Internal.Base.String -> GHC.Types.IO ()
traceShow :: forall a b. GHC.Internal.Show.Show a => a -> b -> b
traceShowId :: forall a. GHC.Internal.Show.Show a => a -> a
traceShowM :: forall a (f :: * -> *). (GHC.Internal.Show.Show a, GHC.Internal.Base.Applicative f) => a -> f ()
traceShowWith :: forall b a. GHC.Internal.Show.Show b => (a -> b) -> a -> a
traceStack :: forall a. GHC.Internal.Base.String -> a -> a
traceWith :: forall a. (a -> GHC.Internal.Base.String) -> a -> a
1872
1873
1874
1875
1876
1877
1878
1879
1880
1881
1882
1883
1884
1885
1886
1887
1888
1889
1890
1891
1892
1893
1894
1895
module Foreign where
-- Safety: Safe
(!<<.) :: forall a. Bits a => a -> Int -> a
(!>>.) :: forall a. Bits a => a -> Int -> a
(.<<.) :: forall a. Bits a => a -> Int -> a
(.>>.) :: forall a. Bits a => a -> Int -> a
(.^.) :: forall a. Bits a => a -> a -> a
type And :: * -> *
newtype And a = And {getAnd :: a}
type Bits :: * -> Constraint
class GHC.Classes.Eq a => Bits a where
(.&.) :: a -> a -> a
(.|.) :: a -> a -> a
xor :: a -> a -> a
complement :: a -> a
shift :: a -> Int -> a
rotate :: a -> Int -> a
zeroBits :: a
bit :: Int -> a
setBit :: a -> Int -> a
clearBit :: a -> Int -> a
complementBit :: a -> Int -> a
testBit :: a -> Int -> GHC.Types.Bool
bitSizeMaybe :: a -> GHC.Internal.Maybe.Maybe Int
1897
1898
1899
1900
1901
1902
1903
1904
1905
1906
1907
1908
1909
1910
1911
1912
1913
1914
1915
1916
1917
1918
1919
1920
1921
1922
1923
1924
1925
1926
1927
1928
1929
1930
1931
1932
1933
1934
1935
1936
1937
1938
1939
1940
1941
1942
1943
1944
1945
1946
1947
1948
1949
1950
1951
1952
1953
1954
1955
1956
1957
1958
1959
1960
1961
1962
1963
1964
1965
1966
1967
1968
1969
1970
1971
1972
1973
1974
1975
1976
1977
1978
1979
bitSize :: a -> Int
isSigned :: a -> GHC.Types.Bool
shiftL :: a -> Int -> a
unsafeShiftL :: a -> Int -> a
shiftR :: a -> Int -> a
unsafeShiftR :: a -> Int -> a
rotateL :: a -> Int -> a
rotateR :: a -> Int -> a
popCount :: a -> Int
{-# MINIMAL (.&.), (.|.), xor, complement, (shift | (shiftL, shiftR)), (rotate | (rotateL, rotateR)), bitSize, bitSizeMaybe, isSigned, testBit, bit, popCount #-}
type FinalizerEnvPtr :: * -> * -> *
type FinalizerEnvPtr env a = FunPtr (Ptr env -> Ptr a -> GHC.Types.IO ())
type FinalizerPtr :: * -> *
type FinalizerPtr a = FunPtr (Ptr a -> GHC.Types.IO ())
type FiniteBits :: * -> Constraint
class Bits b => FiniteBits b where
finiteBitSize :: b -> Int
countLeadingZeros :: b -> Int
countTrailingZeros :: b -> Int
{-# MINIMAL finiteBitSize #-}
type role ForeignPtr phantom
type ForeignPtr :: * -> *
data ForeignPtr a = ...
type role FunPtr phantom
type FunPtr :: * -> *
data FunPtr a = ...
type Iff :: * -> *
newtype Iff a = Iff {getIff :: a}
type Int :: *
data Int = ...
type Int16 :: *
data Int16 = ...
type Int32 :: *
data Int32 = ...
type Int64 :: *
data Int64 = ...
type Int8 :: *
data Int8 = ...
type IntPtr :: *
newtype IntPtr = IntPtr Int
type Ior :: * -> *
newtype Ior a = Ior {getIor :: a}
type Pool :: *
newtype Pool = ...
type role Ptr phantom
type Ptr :: * -> *
data Ptr a = ...
type StablePtr :: * -> *
data StablePtr a = ...
type Storable :: * -> Constraint
class Storable a where
sizeOf :: a -> Int
alignment :: a -> Int
peekElemOff :: Ptr a -> Int -> GHC.Types.IO a
pokeElemOff :: Ptr a -> Int -> a -> GHC.Types.IO ()
peekByteOff :: forall b. Ptr b -> Int -> GHC.Types.IO a
pokeByteOff :: forall b. Ptr b -> Int -> a -> GHC.Types.IO ()
peek :: Ptr a -> GHC.Types.IO a
poke :: Ptr a -> a -> GHC.Types.IO ()
{-# MINIMAL sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff) #-}
type Word :: *
data Word = ...
type Word16 :: *
data Word16 = ...
type Word32 :: *
data Word32 = ...
type Word64 :: *
data Word64 = ...
type Word8 :: *
data Word8 = ...
type WordPtr :: *
newtype WordPtr = WordPtr Word
type Xor :: * -> *
newtype Xor a = Xor {getXor :: a}
addForeignPtrFinalizer :: forall a. FinalizerPtr a -> ForeignPtr a -> GHC.Types.IO ()
addForeignPtrFinalizerEnv :: forall env a. FinalizerEnvPtr env a -> Ptr env -> ForeignPtr a -> GHC.Types.IO ()
advancePtr :: forall a. Storable a => Ptr a -> Int -> Ptr a
alignPtr :: forall a. Ptr a -> Int -> Ptr a
alloca :: forall a b. Storable a => (Ptr a -> GHC.Types.IO b) -> GHC.Types.IO b
allocaArray :: forall a b. Storable a => Int -> (Ptr a -> GHC.Types.IO b) -> GHC.Types.IO b
allocaArray0 :: forall a b. Storable a => Int -> (Ptr a -> GHC.Types.IO b) -> GHC.Types.IO b
allocaBytes :: forall a b. Int -> (Ptr a -> GHC.Types.IO b) -> GHC.Types.IO b
allocaBytesAligned :: forall a b. Int -> Int -> (Ptr a -> GHC.Types.IO b) -> GHC.Types.IO b
bitDefault :: forall a. (Bits a, GHC.Internal.Num.Num a) => Int -> a
bitReverse16 :: Word16 -> Word16
bitReverse32 :: Word32 -> Word32
bitReverse64 :: Word64 -> Word64
bitReverse8 :: Word8 -> Word8
byteSwap16 :: Word16 -> Word16
byteSwap32 :: Word32 -> Word32
byteSwap64 :: Word64 -> Word64
calloc :: forall a. Storable a => GHC.Types.IO (Ptr a)
callocArray :: forall a. Storable a => Int -> GHC.Types.IO (Ptr a)
callocArray0 :: forall a. Storable a => Int -> GHC.Types.IO (Ptr a)
callocBytes :: forall a. Int -> GHC.Types.IO (Ptr a)
castForeignPtr :: forall a b. ForeignPtr a -> ForeignPtr b
castFunPtr :: forall a b. FunPtr a -> FunPtr b
castFunPtrToPtr :: forall a b. FunPtr a -> Ptr b
castPtr :: forall a b. Ptr a -> Ptr b
castPtrToFunPtr :: forall a b. Ptr a -> FunPtr b
castPtrToStablePtr :: forall a. Ptr () -> StablePtr a
castStablePtrToPtr :: forall a. StablePtr a -> Ptr ()
copyArray :: forall a. Storable a => Ptr a -> Ptr a -> Int -> GHC.Types.IO ()
copyBytes :: forall a. Ptr a -> Ptr a -> Int -> GHC.Types.IO ()