primitive-containers-0.3.3: containers backed by arrays

Safe HaskellNone
LanguageHaskell2010

Data.Dependent.Map.Class

Documentation

newtype Apply f a Source #

Constructors

Apply (f a) 
Instances
EqForall f => Eq (Apply f a) Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

(==) :: Apply f a -> Apply f a -> Bool #

(/=) :: Apply f a -> Apply f a -> Bool #

OrdForall f => Ord (Apply f a) Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

compare :: Apply f a -> Apply f a -> Ordering #

(<) :: Apply f a -> Apply f a -> Bool #

(<=) :: Apply f a -> Apply f a -> Bool #

(>) :: Apply f a -> Apply f a -> Bool #

(>=) :: Apply f a -> Apply f a -> Bool #

max :: Apply f a -> Apply f a -> Apply f a #

min :: Apply f a -> Apply f a -> Apply f a #

ApplyUniversally f PrimUnlifted => PrimUnlifted (Apply f a) Source # 
Instance details

Defined in Data.Dependent.Map.Class

PrimForall f => Prim (Apply f a) Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

sizeOf# :: Apply f a -> Int# #

alignment# :: Apply f a -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Apply f a #

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, Apply f a#) #

writeByteArray# :: MutableByteArray# s -> Int# -> Apply f a -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Apply f a -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Apply f a #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, Apply f a#) #

writeOffAddr# :: Addr# -> Int# -> Apply f a -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Apply f a -> State# s -> State# s #

class Universally (f :: k -> Type) (x :: Type -> Constraint) where Source #

Methods

universally :: Proxy f -> Proxy x -> Proxy a -> (x (Apply f a) => y) -> y Source #

Instances
ApplyUniversally f PrimUnlifted => Universally (f :: k -> Type) PrimUnlifted Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

universally :: Proxy f -> Proxy PrimUnlifted -> Proxy a -> (PrimUnlifted (Apply f a) -> y) -> y Source #

Universally (f :: k -> Type) Always Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

universally :: Proxy f -> Proxy Always -> Proxy a -> (Always (Apply f a) -> y) -> y Source #

class ApplyUniversally (f :: k -> Type) (x :: Type -> Constraint) where Source #

Methods

applyUniversallyLifted :: forall a y. Proxy f -> Proxy x -> Proxy a -> (x (f a) => y) -> y Source #

applyUniversallyUnlifted :: forall a (y :: TYPE UnliftedRep). Proxy f -> Proxy x -> Proxy a -> (x (f a) => y) -> y Source #

Instances
ApplyUniversally (f :: k -> Type) Always Source # 
Instance details

Defined in Data.Dependent.Map.Class

Methods

applyUniversallyLifted :: Proxy f -> Proxy Always -> Proxy a -> (Always (f a) -> y) -> y Source #

applyUniversallyUnlifted :: Proxy f -> Proxy Always -> Proxy a -> (Always (f a) -> y) -> y Source #