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

Copyright(c) Fumiaki Kinoshita 2018
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Dictionary

Contents

Description

Reification of constraints using extensible data types. Also includes orphan instances.

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 (c :: k2 -> Constraint) (h :: k1 -> k2) (x :: k1) Source # 
Instance details

Defined in Data.Extensible.Dictionary

class (f x, g x) => And f g x Source #

Instances
(f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) Source # 
Instance details

Defined in Data.Extensible.Dictionary

Orphan instances

Unbox a => Vector Vector (Identity a) Source # 
Instance details

Unbox a => MVector MVector (Identity a) Source # 
Instance details

WrapForall Unbox h (x ': xs) => Vector Vector (h :* (x ': xs)) Source # 
Instance details

Methods

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

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

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

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

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

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

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

WrapForall Unbox h (x ': xs) => MVector MVector (h :* (x ': xs)) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

Unbox a => Unbox (Identity a) Source # 
Instance details

WrapForall Bounded h xs => Bounded (h :* xs) Source # 
Instance details

Methods

minBound :: h :* xs #

maxBound :: h :* xs #

WrapForall Eq h xs => Eq (h :| xs) Source # 
Instance details

Methods

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

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

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

Methods

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

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

(Eq (h :| xs), WrapForall Ord h xs) => Ord (h :| xs) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

WrapForall Show h xs => Show (h :| xs) Source # 
Instance details

Methods

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

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

showList :: [h :| xs] -> ShowS #

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

Methods

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

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

showList :: [h :* xs] -> ShowS #

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

Methods

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

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

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

(WrapForall Semigroup h xs, WrapForall Monoid h xs) => Monoid (h :* xs) Source # 
Instance details

Methods

mempty :: h :* xs #

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

mconcat :: [h :* xs] -> h :* xs #

WrapForall Lift h xs => Lift (h :| xs) Source # 
Instance details

Methods

lift :: (h :| xs) -> Q Exp #

WrapForall Lift h xs => Lift (h :* xs) Source # 
Instance details

Methods

lift :: (h :* xs) -> Q Exp #

WrapForall Arbitrary h xs => Arbitrary (h :| xs) Source # 
Instance details

Methods

arbitrary :: Gen (h :| xs) #

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

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

Methods

arbitrary :: Gen (h :* xs) #

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

WrapForall Hashable h xs => Hashable (h :| xs) Source # 
Instance details

Methods

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

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

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

Methods

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

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

Forall (KeyValue KnownSymbol (Instance1 ToJSON h)) xs => ToJSON (Nullable (Field h :: Assoc Symbol v -> Type) :* xs) Source # 
Instance details

Methods

toJSON :: (Nullable (Field h) :* xs) -> Value #

toEncoding :: (Nullable (Field h) :* xs) -> Encoding #

toJSONList :: [Nullable (Field h) :* xs] -> Value #

toEncodingList :: [Nullable (Field h) :* xs] -> Encoding #

Forall (KeyValue KnownSymbol (Instance1 ToJSON h)) xs => ToJSON ((Field h :: Assoc Symbol v -> Type) :* xs) Source # 
Instance details

Methods

toJSON :: (Field h :* xs) -> Value #

toEncoding :: (Field h :* xs) -> Encoding #

toJSONList :: [Field h :* xs] -> Value #

toEncodingList :: [Field h :* xs] -> Encoding #

Forall (KeyValue KnownSymbol (Instance1 FromJSON h)) xs => FromJSON (Nullable (Field h :: Assoc Symbol v -> Type) :* xs) Source # 
Instance details

Forall (KeyValue KnownSymbol (Instance1 FromJSON h)) xs => FromJSON ((Field h :: Assoc Symbol v -> Type) :* xs) Source #

parseJSON Null is called for missing fields.

Instance details

Methods

parseJSON :: Value -> Parser (Field h :* xs) #

parseJSONList :: Value -> Parser [Field h :* xs] #

WrapForall FromField h xs => FromRecord (h :* xs) Source # 
Instance details

Methods

parseRecord :: Record -> Parser (h :* xs) #

WrapForall ToField h xs => ToRecord (h :* xs) Source # 
Instance details

Methods

toRecord :: (h :* xs) -> Record #

Forall (KeyValue KnownSymbol (Instance1 FromField h)) xs => FromNamedRecord ((Field h :: Assoc Symbol v -> Type) :* xs) Source # 
Instance details

Forall (KeyValue KnownSymbol (Instance1 ToField h)) xs => ToNamedRecord ((Field h :: Assoc Symbol v -> Type) :* xs) Source # 
Instance details

Methods

toNamedRecord :: (Field h :* xs) -> NamedRecord #

WrapForall NFData h xs => NFData (h :| xs) Source # 
Instance details

Methods

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

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

Methods

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

WrapForall Pretty h xs => Pretty (h :| xs) Source # 
Instance details

Methods

pretty :: (h :| xs) -> Doc ann #

prettyList :: [h :| xs] -> Doc ann #

WrapForall Pretty h xs => Pretty (h :* xs) Source # 
Instance details

Methods

pretty :: (h :* xs) -> Doc ann #

prettyList :: [h :* xs] -> Doc ann #

WrapForall Unbox h (x ': xs) => Unbox (h :* (x ': xs)) Source # 
Instance details