free-foil-0.2.0: Efficient Type-Safe Capture-Avoiding Substitution for Free (Scoped Monads)
Safe HaskellNone
LanguageHaskell2010

Control.Monad.Free.Foil.Generic

Documentation

type family ZipLoT (as :: LoT k) (bs :: LoT k) :: LoT k where ... Source #

Equations

ZipLoT 'LoT0 'LoT0 = 'LoT0 
ZipLoT (a ':&&: as :: LoT (Type -> ks)) (b ':&&: bs :: LoT (Type -> ks)) = (a, b) ':&&: ZipLoT as bs 

data Mappings (as :: LoT k) (bs :: LoT k) (cs :: LoT k) where Source #

Constructors

M0 :: Mappings 'LoT0 'LoT0 'LoT0 
(:^:) :: forall {k1} a b c (as1 :: LoT k1) (bs1 :: LoT k1) (cs1 :: LoT k1). (a -> b -> Maybe c) -> Mappings as1 bs1 cs1 -> Mappings (a ':&&: as1) (b ':&&: bs1) (c ':&&: cs1) 

class PairMappings (as :: LoT k) (bs :: LoT k) where Source #

Methods

pairMappings :: Mappings as bs (ZipLoT as bs) Source #

Instances

Instances details
PairMappings 'LoT0 'LoT0 Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

PairMappings as bs => PairMappings (a ':&&: as :: LoT (Type -> ks)) (b ':&&: bs :: LoT (Type -> ks)) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

pairMappings :: Mappings (a ':&&: as) (b ':&&: bs) (ZipLoT (a ':&&: as) (b ':&&: bs)) Source #

class ApplyMappings (v :: TyVar d Type) where Source #

Methods

applyMappings :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). Mappings as bs cs -> Interpret ('Var v) as -> Interpret ('Var v) bs -> Maybe (Interpret ('Var v) cs) Source #

Instances

Instances details
ApplyMappings ('VZ :: TyVar (Type -> tys) Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

applyMappings :: forall (as :: LoT (Type -> tys)) (bs :: LoT (Type -> tys)) (cs :: LoT (Type -> tys)). Mappings as bs cs -> Interpret ('Var ('VZ :: TyVar (Type -> tys) Type)) as -> Interpret ('Var ('VZ :: TyVar (Type -> tys) Type)) bs -> Maybe (Interpret ('Var ('VZ :: TyVar (Type -> tys) Type)) cs) Source #

ApplyMappings v => ApplyMappings ('VS v :: TyVar (ty -> tys) Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

applyMappings :: forall (as :: LoT (ty -> tys)) (bs :: LoT (ty -> tys)) (cs :: LoT (ty -> tys)). Mappings as bs cs -> Interpret ('Var ('VS v :: TyVar (ty -> tys) Type)) as -> Interpret ('Var ('VS v :: TyVar (ty -> tys) Type)) bs -> Maybe (Interpret ('Var ('VS v :: TyVar (ty -> tys) Type)) cs) Source #

genericZipMatchK :: forall {k} (f :: k) (as :: LoT k) (bs :: LoT k). (GenericK f, GZipMatch (RepK f), ReqsZipMatch (RepK f) as bs, PairMappings as bs) => (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: ZipLoT as bs) Source #

genericZipMatchWithK :: forall {k} (f :: k) (as :: LoT k) (bs :: LoT k) (cs :: LoT k). (GenericK f, GZipMatch (RepK f), ReqsZipMatchWith (RepK f) as bs cs) => Mappings as bs cs -> (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: cs) Source #

genericZipMatch2 :: forall sig scope scope' term term'. (GenericK sig, GZipMatch (RepK sig), ReqsZipMatch (RepK sig) (scope ':&&: (term ':&&: 'LoT0)) (scope' ':&&: (term' ':&&: 'LoT0))) => sig scope term -> sig scope' term' -> Maybe (sig (scope, scope') (term, term')) Source #

zipMatchK :: forall {k} (f :: k) (as :: LoT k) (bs :: LoT k). (ZipMatchK f, PairMappings as bs) => (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: ZipLoT as bs) Source #

class ZipMatchK (f :: k) where Source #

Minimal complete definition

Nothing

Methods

zipMatchWithK :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). Mappings as bs cs -> (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: cs) Source #

default zipMatchWithK :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). (GenericK f, GZipMatch (RepK f), ReqsZipMatchWith (RepK f) as bs cs) => Mappings as bs cs -> (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: cs) Source #

Instances

Instances details
ZipMatchK Either Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchWithK :: forall (as :: LoT (Type -> Type -> Type)) (bs :: LoT (Type -> Type -> Type)) (cs :: LoT (Type -> Type -> Type)). Mappings as bs cs -> (Either :@@: as) -> (Either :@@: bs) -> Maybe (Either :@@: cs) Source #

ZipMatchK Maybe Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchWithK :: forall (as :: LoT (Type -> Type)) (bs :: LoT (Type -> Type)) (cs :: LoT (Type -> Type)). Mappings as bs cs -> (Maybe :@@: as) -> (Maybe :@@: bs) -> Maybe (Maybe :@@: cs) Source #

ZipMatchK [] Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchWithK :: forall (as :: LoT (Type -> Type)) (bs :: LoT (Type -> Type)) (cs :: LoT (Type -> Type)). Mappings as bs cs -> ([] :@@: as) -> ([] :@@: bs) -> Maybe ([] :@@: cs) Source #

ZipMatchK a => ZipMatchK (Either a :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchWithK :: forall (as :: LoT (Type -> Type)) (bs :: LoT (Type -> Type)) (cs :: LoT (Type -> Type)). Mappings as bs cs -> (Either a :@@: as) -> (Either a :@@: bs) -> Maybe (Either a :@@: cs) Source #

zipMatchViaEq :: forall {k} a (as :: LoT k) (bs :: LoT k) (cs :: LoT k). Eq a => Mappings as bs cs -> a -> a -> Maybe a Source #

zipMatchViaChooseLeft :: forall {k} (as :: LoT k) (bs :: LoT k) (cs :: LoT k) a. Mappings as bs cs -> a -> a -> Maybe a Source #

type ReqsZipMatch (f :: LoT k -> Type) (as :: LoT k) (bs :: LoT k) = ReqsZipMatchWith f as bs (ZipLoT as bs) Source #

class GZipMatch (f :: LoT k -> Type) where Source #

Associated Types

type ReqsZipMatchWith (f :: LoT k -> Type) (as :: LoT k) (bs :: LoT k) (cs :: LoT k) Source #

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith f as bs cs => Mappings as bs cs -> f as -> f bs -> Maybe (f cs) Source #

Instances

Instances details
GZipMatch (U1 :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (U1 :: LoT k -> Type) as bs cs => Mappings as bs cs -> U1 as -> U1 bs -> Maybe (U1 cs) Source #

GZipMatch (V1 :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (V1 :: LoT k -> Type) as bs cs => Mappings as bs cs -> V1 as -> V1 bs -> Maybe (V1 cs) Source #

ZipMatchFields t => GZipMatch (Field t :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (Field t) as bs cs => Mappings as bs cs -> Field t as -> Field t bs -> Maybe (Field t cs) Source #

(GZipMatch f, GZipMatch g) => GZipMatch (f :*: g :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (f :*: g) as bs cs => Mappings as bs cs -> (f :*: g) as -> (f :*: g) bs -> Maybe ((f :*: g) cs) Source #

(GZipMatch f, GZipMatch g) => GZipMatch (f :+: g :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (f :+: g) as bs cs => Mappings as bs cs -> (f :+: g) as -> (f :+: g) bs -> Maybe ((f :+: g) cs) Source #

GZipMatch f => GZipMatch (c :=>: f :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (c :=>: f) as bs cs => Mappings as bs cs -> (c :=>: f) as -> (c :=>: f) bs -> Maybe ((c :=>: f) cs) Source #

(TypeError ('Text "Existentials are not supported") :: Constraint) => GZipMatch (Exists k2 f :: LoT k1 -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k1) (bs :: LoT k1) (cs :: LoT k1). ReqsZipMatchWith (Exists k2 f) as bs cs => Mappings as bs cs -> Exists k2 f as -> Exists k2 f bs -> Maybe (Exists k2 f cs) Source #

GZipMatch f => GZipMatch (M1 i c f :: LoT k -> Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

gzipMatchWith :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). ReqsZipMatchWith (M1 i c f) as bs cs => Mappings as bs cs -> M1 i c f as -> M1 i c f bs -> Maybe (M1 i c f cs) Source #

class ZipMatchFields (t :: Atom d Type) where Source #

Associated Types

type ReqsZipMatchFieldsWith (t :: Atom d Type) (as :: LoT d) (bs :: LoT d) (cs :: LoT d) Source #

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith t as bs cs => Mappings as bs cs -> Field t as -> Field t bs -> Maybe (Field t cs) Source #

Instances

Instances details
(TypeError ('Text "Atom :=>>: is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields (c ':=>>: a :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith (c ':=>>: a) as bs cs => Mappings as bs cs -> Field (c ':=>>: a) as -> Field (c ':=>>: a) bs -> Maybe (Field (c ':=>>: a) cs) Source #

(TypeError ('Text "Atom Eval is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields ('Eval a :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith ('Eval a) as bs cs => Mappings as bs cs -> Field ('Eval a) as -> Field ('Eval a) bs -> Maybe (Field ('Eval a) cs) Source #

(TypeError ('Text "Atom ForAll is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields ('ForAll a :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith ('ForAll a) as bs cs => Mappings as bs cs -> Field ('ForAll a) as -> Field ('ForAll a) bs -> Maybe (Field ('ForAll a) cs) Source #

ZipMatchK k => ZipMatchFields ('Kon k :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith ('Kon k :: Atom d Type) as bs cs => Mappings as bs cs -> Field ('Kon k :: Atom d Type) as -> Field ('Kon k :: Atom d Type) bs -> Maybe (Field ('Kon k :: Atom d Type) cs) Source #

ApplyMappings v => ZipMatchFields ('Var v :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith ('Var v) as bs cs => Mappings as bs cs -> Field ('Var v) as -> Field ('Var v) bs -> Maybe (Field ('Var v) cs) Source #

(ZipMatchFields t1, ZipMatchFields t2, ZipMatchK k) => ZipMatchFields ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2 :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2) as bs cs => Mappings as bs cs -> Field ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2) as -> Field ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2) bs -> Maybe (Field ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2) cs) Source #

(ZipMatchFields t, ZipMatchK k) => ZipMatchFields (('Kon k :: Atom d (Type -> Type)) ':@: t :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith (('Kon k :: Atom d (Type -> Type)) ':@: t) as bs cs => Mappings as bs cs -> Field (('Kon k :: Atom d (Type -> Type)) ':@: t) as -> Field (('Kon k :: Atom d (Type -> Type)) ':@: t) bs -> Maybe (Field (('Kon k :: Atom d (Type -> Type)) ':@: t) cs) Source #

(TypeError ('Text "Atom :@: is not supported by ZipMatchFields is a general form") :: Constraint) => ZipMatchFields (f ':@: t :: Atom d Type) Source # 
Instance details

Defined in Control.Monad.Free.Foil.Generic

Methods

zipMatchFieldsWith :: forall (as :: LoT d) (bs :: LoT d) (cs :: LoT d). ReqsZipMatchFieldsWith (f ':@: t) as bs cs => Mappings as bs cs -> Field (f ':@: t) as -> Field (f ':@: t) bs -> Maybe (Field (f ':@: t) cs) Source #