Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
class PairMappings (as :: LoT k) (bs :: LoT k) where Source #
pairMappings :: Mappings as bs (ZipLoT as bs) Source #
Instances
PairMappings 'LoT0 'LoT0 Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
PairMappings as bs => PairMappings (a ':&&: as :: LoT (Type -> ks)) (b ':&&: bs :: LoT (Type -> ks)) Source # | |
Defined in Control.Monad.Free.Foil.Generic |
class ApplyMappings (v :: TyVar d Type) where Source #
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
ApplyMappings ('VZ :: TyVar (Type -> tys) Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic 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 # | |
Defined in Control.Monad.Free.Foil.Generic 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 #
Nothing
zipMatchWithK :: forall (as :: LoT k) (bs :: LoT k) (cs :: LoT k). Mappings as bs cs -> (f :@@: as) -> (f :@@: bs) -> Maybe (f :@@: 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 #
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
GZipMatch (U1 :: LoT k -> Type) Source # | |
GZipMatch (V1 :: LoT k -> Type) Source # | |
ZipMatchFields t => GZipMatch (Field t :: LoT k -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
(GZipMatch f, GZipMatch g) => GZipMatch (f :*: g :: LoT k -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
(GZipMatch f, GZipMatch g) => GZipMatch (f :+: g :: LoT k -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
GZipMatch f => GZipMatch (c :=>: f :: LoT k -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
(TypeError ('Text "Existentials are not supported") :: Constraint) => GZipMatch (Exists k2 f :: LoT k1 -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
GZipMatch f => GZipMatch (M1 i c f :: LoT k -> Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic |
class ZipMatchFields (t :: Atom d Type) where Source #
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
(TypeError ('Text "Atom :=>>: is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields (c ':=>>: a :: Atom d Type) Source # | |
(TypeError ('Text "Atom Eval is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields ('Eval a :: Atom d Type) Source # | |
(TypeError ('Text "Atom ForAll is not supported by ZipMatchFields") :: Constraint) => ZipMatchFields ('ForAll a :: Atom d Type) Source # | |
ZipMatchK k => ZipMatchFields ('Kon k :: Atom d Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic | |
ApplyMappings v => ZipMatchFields ('Var v :: Atom d Type) Source # | |
(ZipMatchFields t1, ZipMatchFields t2, ZipMatchK k) => ZipMatchFields ((('Kon k :: Atom d (Type -> Type -> Type)) ':@: t1) ':@: t2 :: Atom d Type) Source # | |
Defined in Control.Monad.Free.Foil.Generic 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 # | |
Defined in Control.Monad.Free.Foil.Generic 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 # | |