extensible-0.4.6: Extensible, efficient, optics-friendly data types and effects

Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Dictionary

Contents

Synopsis

Documentation

library :: forall c xs. Forall c xs => Comp Dict c :* xs Source #

Reify a collection of dictionaries, as you wish.

type WrapForall c h = Forall (Instance1 c h) Source #

Forall upon a wrapper

class c (h x) => Instance1 c h x Source #

Composition for a class and a wrapper

Instances

c (h x) => Instance1 k k1 c h x Source # 

Orphan instances

Unbox a => Vector Vector (Identity a) Source # 
Unbox a => MVector MVector (Identity a) Source # 
Unbox a => Vector Vector (Const' k a b) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Const' k a b) -> m (Vector (Const' k a b)) #

basicUnsafeThaw :: PrimMonad m => Vector (Const' k a b) -> m (Mutable Vector (PrimState m) (Const' k a b)) #

basicLength :: Vector (Const' k a b) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (Const' k a b) -> Vector (Const' k a b) #

basicUnsafeIndexM :: Monad m => Vector (Const' k a b) -> Int -> m (Const' k a b) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Const' k a b) -> Vector (Const' k a b) -> m () #

elemseq :: Vector (Const' k a b) -> Const' k a b -> b -> b #

WrapForall a * Unbox h ((:) a x xs) => Vector Vector ((:*) a h ((:) a x xs)) Source # 

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) ((a :* h) ((a ': x) xs)) -> m (Vector ((a :* h) ((a ': x) xs))) #

basicUnsafeThaw :: PrimMonad m => Vector ((a :* h) ((a ': x) xs)) -> m (Mutable Vector (PrimState m) ((a :* h) ((a ': x) xs))) #

basicLength :: Vector ((a :* h) ((a ': x) xs)) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector ((a :* h) ((a ': x) xs)) -> Vector ((a :* h) ((a ': x) xs)) #

basicUnsafeIndexM :: Monad m => Vector ((a :* h) ((a ': x) xs)) -> Int -> m ((a :* h) ((a ': x) xs)) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) ((a :* h) ((a ': x) xs)) -> Vector ((a :* h) ((a ': x) xs)) -> m () #

elemseq :: Vector ((a :* h) ((a ': x) xs)) -> (a :* h) ((a ': x) xs) -> b -> b #

Unbox a => MVector MVector (Const' k a b) Source # 

Methods

basicLength :: MVector s (Const' k a b) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (Const' k a b) -> MVector s (Const' k a b) #

basicOverlaps :: MVector s (Const' k a b) -> MVector s (Const' k a b) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Const' k a b)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> Const' k a b -> m (MVector (PrimState m) (Const' k a b)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> Int -> m (Const' k a b) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> Int -> Const' k a b -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> Const' k a b -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> MVector (PrimState m) (Const' k a b) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> MVector (PrimState m) (Const' k a b) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Const' k a b) -> Int -> m (MVector (PrimState m) (Const' k a b)) #

WrapForall a * Unbox h ((:) a x xs) => MVector MVector ((:*) a h ((:) a x xs)) Source # 

Methods

basicLength :: MVector s ((a :* h) ((a ': x) xs)) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s ((a :* h) ((a ': x) xs)) -> MVector s ((a :* h) ((a ': x) xs)) #

basicOverlaps :: MVector s ((a :* h) ((a ': x) xs)) -> MVector s ((a :* h) ((a ': x) xs)) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) ((a :* h) ((a ': x) xs))) #

basicInitialize :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> (a :* h) ((a ': x) xs) -> m (MVector (PrimState m) ((a :* h) ((a ': x) xs))) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> Int -> m ((a :* h) ((a ': x) xs)) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> Int -> (a :* h) ((a ': x) xs) -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> (a :* h) ((a ': x) xs) -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) ((a :* h) ((a ': x) xs)) -> Int -> m (MVector (PrimState m) ((a :* h) ((a ': x) xs))) #

Unbox a => Unbox (Identity a) Source # 
WrapForall k * Bounded h xs => Bounded ((:*) k h xs) Source # 

Methods

minBound :: (k :* h) xs #

maxBound :: (k :* h) xs #

WrapForall k * Eq h xs => Eq ((:*) k h xs) Source # 

Methods

(==) :: (k :* h) xs -> (k :* h) xs -> Bool #

(/=) :: (k :* h) xs -> (k :* h) xs -> Bool #

WrapForall k * Eq h xs => Eq ((:|) k h xs) Source # 

Methods

(==) :: (k :| h) xs -> (k :| h) xs -> Bool #

(/=) :: (k :| h) xs -> (k :| h) xs -> Bool #

(Eq ((:*) k h xs), WrapForall k * Ord h xs) => Ord ((:*) k h xs) Source # 

Methods

compare :: (k :* h) xs -> (k :* h) xs -> Ordering #

(<) :: (k :* h) xs -> (k :* h) xs -> Bool #

(<=) :: (k :* h) xs -> (k :* h) xs -> Bool #

(>) :: (k :* h) xs -> (k :* h) xs -> Bool #

(>=) :: (k :* h) xs -> (k :* h) xs -> Bool #

max :: (k :* h) xs -> (k :* h) xs -> (k :* h) xs #

min :: (k :* h) xs -> (k :* h) xs -> (k :* h) xs #

(Eq ((:|) k h xs), WrapForall k * Ord h xs) => Ord ((:|) k h xs) Source # 

Methods

compare :: (k :| h) xs -> (k :| h) xs -> Ordering #

(<) :: (k :| h) xs -> (k :| h) xs -> Bool #

(<=) :: (k :| h) xs -> (k :| h) xs -> Bool #

(>) :: (k :| h) xs -> (k :| h) xs -> Bool #

(>=) :: (k :| h) xs -> (k :| h) xs -> Bool #

max :: (k :| h) xs -> (k :| h) xs -> (k :| h) xs #

min :: (k :| h) xs -> (k :| h) xs -> (k :| h) xs #

WrapForall k * Show h xs => Show ((:*) k h xs) Source # 

Methods

showsPrec :: Int -> (k :* h) xs -> ShowS #

show :: (k :* h) xs -> String #

showList :: [(k :* h) xs] -> ShowS #

WrapForall k * Show h xs => Show ((:|) k h xs) Source # 

Methods

showsPrec :: Int -> (k :| h) xs -> ShowS #

show :: (k :| h) xs -> String #

showList :: [(k :| h) xs] -> ShowS #

WrapForall k * Semigroup h xs => Semigroup ((:*) k h xs) Source # 

Methods

(<>) :: (k :* h) xs -> (k :* h) xs -> (k :* h) xs #

sconcat :: NonEmpty ((k :* h) xs) -> (k :* h) xs #

stimes :: Integral b => b -> (k :* h) xs -> (k :* h) xs #

WrapForall k * Monoid h xs => Monoid ((:*) k h xs) Source # 

Methods

mempty :: (k :* h) xs #

mappend :: (k :* h) xs -> (k :* h) xs -> (k :* h) xs #

mconcat :: [(k :* h) xs] -> (k :* h) xs #

WrapForall k * Arbitrary h xs => Arbitrary ((:*) k h xs) Source # 

Methods

arbitrary :: Gen ((k :* h) xs) #

shrink :: (k :* h) xs -> [(k :* h) xs] #

WrapForall k * Arbitrary h xs => Arbitrary ((:|) k h xs) Source # 

Methods

arbitrary :: Gen ((k :| h) xs) #

shrink :: (k :| h) xs -> [(k :| h) xs] #

WrapForall k * NFData h xs => NFData ((:*) k h xs) Source # 

Methods

rnf :: (k :* h) xs -> () #

WrapForall k * NFData h xs => NFData ((:|) k h xs) Source # 

Methods

rnf :: (k :| h) xs -> () #

WrapForall k * Hashable h xs => Hashable ((:*) k h xs) Source # 

Methods

hashWithSalt :: Int -> (k :* h) xs -> Int #

hash :: (k :* h) xs -> Int #

WrapForall k * Hashable h xs => Hashable ((:|) k h xs) Source # 

Methods

hashWithSalt :: Int -> (k :| h) xs -> Int #

hash :: (k :| h) xs -> Int #

Unbox a => Unbox (Const' k a b) Source # 
WrapForall a * Unbox h ((:) a x xs) => Unbox ((:*) a h ((:) a x xs)) Source #