simplistic-generics-2.0.0: Generic programming without too many type classes
Safe HaskellNone
LanguageHaskell2010

Generics.Simplistic.Deep

Description

Deep representation for SRep

Synopsis

(Co)Free (Co)Monad and its cousins

data HolesAnn kappa fam ann h a where Source #

The cofree comonad and free monad on the same type; this allows us to use the same recursion operator for everything.

Constructors

Hole' 

Fields

  • :: ann a

    Annotation

  • -> h a
     
  • -> HolesAnn kappa fam ann h a
     
Prim' 

Fields

Roll' 

Fields

Instances

Instances details
(All Eq kappa, EqHO h) => EqHO (Holes kappa fam h :: Type -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

eqHO :: forall (k :: ki). Holes kappa fam h k -> Holes kappa fam h k -> Bool Source #

(All Eq kappa, EqHO h) => Eq (Holes kappa fam h t) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

(==) :: Holes kappa fam h t -> Holes kappa fam h t -> Bool #

(/=) :: Holes kappa fam h t -> Holes kappa fam h t -> Bool #

(forall x. NFData (ann x), forall x. NFData (h x)) => NFData (HolesAnn kappa fam ann h f) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

rnf :: HolesAnn kappa fam ann h f -> () #

type SFix kappa fam = HolesAnn kappa fam U1 V1 Source #

Deep representations are easily achieved by forbiding the Hole' constructor and providing unit annotations.

pattern SFix :: () => CompoundCnstr kappa fam a => SRep (SFix kappa fam) (Rep a) -> SFix kappa fam a Source #

pattern Prim :: () => PrimCnstr kappa fam a => a -> Holes kappa fam h a Source #

type SFixAnn kappa fam ann = HolesAnn kappa fam ann V1 Source #

Annotated fixpoints are also easy; forbid the Hole' constructor but add something to every Roll of the representation.

pattern SFixAnn :: () => CompoundCnstr kappa fam a => ann a -> SRep (SFixAnn kappa fam ann) (Rep a) -> SFixAnn kappa fam ann a Source #

pattern PrimAnn :: () => PrimCnstr kappa fam a => ann a -> a -> SFixAnn kappa fam ann a Source #

type Holes kappa fam = HolesAnn kappa fam U1 Source #

A tree with holes has unit annotations

pattern Roll :: () => CompoundCnstr kappa fam a => SRep (Holes kappa fam h) (Rep a) -> Holes kappa fam h a Source #

pattern Hole :: h a -> Holes kappa fam h a Source #

Constraints

type CompoundCnstr kappa fam a = (Elem a fam, NotElem a kappa, Generic a) Source #

type PrimCnstr kappa fam b = (Elem b kappa, NotElem b fam) Source #

Coercions

holesToSFix :: Holes kappa fam V1 at -> SFix kappa fam at Source #

sfixToHoles :: SFix kappa fam at -> Holes kappa fam h at Source #

Maps, zips and folds

holesMapAnn :: (forall x. f x -> g x) -> (forall x. ann x -> phi x) -> HolesAnn kappa fam ann f a -> HolesAnn kappa fam phi g a Source #

Maps over holes and annotations in a HolesAnn

holesMap :: (forall x. f x -> g x) -> HolesAnn kappa fam ann f a -> HolesAnn kappa fam ann g a Source #

Maps over the holes in a HolesAnn

holesMapM :: Monad m => (forall x. f x -> m (g x)) -> HolesAnn kappa fam ann f a -> m (HolesAnn kappa fam ann g a) Source #

Maps over HolesAnn maintaining annotations intact.

holesMapAnnM Source #

Arguments

:: Monad m 
=> (forall x. f x -> m (g x))

Function to transform holes

-> (forall x. ann x -> m (psi x))

Function to transform annotations

-> HolesAnn kappa fam ann f a 
-> m (HolesAnn kappa fam psi g a) 

Maps over a HolesAnn treating annotations and holes independently.

getAnn :: HolesAnn kappa fam ann h a -> ann a Source #

Retrieves the annotation inside a HolesAnn; this is the counit of the comonad.

holesJoin :: HolesAnn kappa fam ann (HolesAnn kappa fam ann f) a -> HolesAnn kappa fam ann f a Source #

Monadic multiplication

holesSize :: HolesAnn kappa fam ann h a -> Int Source #

Counts how many Prims and Rolls are inside a HolesAnn.

holesHolesList :: HolesAnn kappa fam ann f a -> [Exists f] Source #

Computes the list of holes in a HolesAnn

holesRefineM :: Monad m => (forall b. f b -> m (Holes kappa fam g b)) -> (forall b. PrimCnstr kappa fam b => b -> m (Holes kappa fam g b)) -> Holes kappa fam f a -> m (Holes kappa fam g a) Source #

Refine holes and primitives

holesRefineHoles :: (forall b. f b -> Holes kappa fam g b) -> Holes kappa fam f a -> Holes kappa fam g a Source #

Refine holes with a simple action

holesRefineHolesM :: Monad m => (forall b. f b -> m (Holes kappa fam g b)) -> Holes kappa fam f a -> m (Holes kappa fam g a) Source #

Refines holes using a monadic action

synthesize :: (forall b. CompoundCnstr kappa fam b => ann b -> SRep phi (Rep b) -> phi b) -> (forall b. PrimCnstr kappa fam b => ann b -> b -> phi b) -> (forall b. ann b -> h b -> phi b) -> HolesAnn kappa fam ann h a -> HolesAnn kappa fam phi h a Source #

Simpler version of synthesizeM working over the Identity monad.

synthesizeM Source #

Arguments

:: Monad m 
=> (forall b. CompoundCnstr kappa fam b => ann b -> SRep phi (Rep b) -> m (phi b))

How to handle recursion

-> (forall b. PrimCnstr kappa fam b => ann b -> b -> m (phi b))

How to handle primitives

-> (forall b. ann b -> h b -> m (phi b))

How to handle holes

-> HolesAnn kappa fam ann h a 
-> m (HolesAnn kappa fam phi h a) 

Synthetization of attributes

cataM Source #

Arguments

:: Monad m 
=> (forall b. CompoundCnstr kappa fam b => ann b -> SRep phi (Rep b) -> m (phi b))

How to handle recursion

-> (forall b. PrimCnstr kappa fam b => ann b -> b -> m (phi b))

How to handle primitivies

-> (forall b. ann b -> h b -> m (phi b))

How to handle holes

-> HolesAnn kappa fam ann h a 
-> m (phi a) 

Catamorphism over HolesAnn

Anti-Unification

lgg :: forall kappa fam h i a. All Eq kappa => Holes kappa fam h a -> Holes kappa fam i a -> Holes kappa fam (Holes kappa fam h :*: Holes kappa fam i) a Source #

Computes the least general generalization of two trees.

Conversion

class CompoundCnstr kappa fam a => Deep kappa fam a where Source #

Minimal complete definition

Nothing

Methods

dfrom :: a -> SFix kappa fam a Source #

default dfrom :: GDeep kappa fam (Rep a) => a -> SFix kappa fam a Source #

dto :: SFix kappa fam a -> a Source #

default dto :: GDeep kappa fam (Rep a) => SFix kappa fam a -> a Source #

class GDeep kappa fam f where Source #

Methods

gdfrom :: f x -> SRep (SFix kappa fam) f Source #

gdto :: SRep (SFix kappa fam) f -> f x Source #

Instances

Instances details
GDeep kappa fam (U1 :: k -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

gdfrom :: forall (x :: k0). U1 x -> SRep (SFix kappa fam) U1 Source #

gdto :: forall (x :: k0). SRep (SFix kappa fam) U1 -> U1 x Source #

(GDeep kappa fam f, GDeep kappa fam g) => GDeep kappa fam (f :+: g :: k -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

gdfrom :: forall (x :: k0). (f :+: g) x -> SRep (SFix kappa fam) (f :+: g) Source #

gdto :: forall (x :: k0). SRep (SFix kappa fam) (f :+: g) -> (f :+: g) x Source #

(GDeep kappa fam f, GDeep kappa fam g) => GDeep kappa fam (f :*: g :: k -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

gdfrom :: forall (x :: k0). (f :*: g) x -> SRep (SFix kappa fam) (f :*: g) Source #

gdto :: forall (x :: k0). SRep (SFix kappa fam) (f :*: g) -> (f :*: g) x Source #

GDeepAtom kappa fam (IsElem a kappa) a => GDeep kappa fam (K1 R a :: k -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

gdfrom :: forall (x :: k0). K1 R a x -> SRep (SFix kappa fam) (K1 R a) Source #

gdto :: forall (x :: k0). SRep (SFix kappa fam) (K1 R a) -> K1 R a x Source #

(GMeta i c, GDeep kappa fam f) => GDeep kappa fam (M1 i c f :: k -> Type) Source # 
Instance details

Defined in Generics.Simplistic.Deep

Methods

gdfrom :: forall (x :: k0). M1 i c f x -> SRep (SFix kappa fam) (M1 i c f) Source #

gdto :: forall (x :: k0). SRep (SFix kappa fam) (M1 i c f) -> M1 i c f x Source #

Orphan instances

NFData (V1 x) Source # 
Instance details

Methods

rnf :: V1 x -> () #

NFData (U1 x) Source # 
Instance details

Methods

rnf :: U1 x -> () #