Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SZip ty w f where
- plug :: SZip ty phi f -> phi ty -> SRep phi f
- zipperMap :: (forall x. h x -> g x) -> SZip ty h f -> SZip ty g f
- inr1 :: (x :*: y) t -> (Sum z x :*: y) t
- zipperRepZip :: SZip ty h f -> SRep w f -> Maybe (SRep (Sum ((:~:) ty) h :*: w) f)
- zipSZip :: SZip ty h f -> SZip ty w f -> Maybe (SZip ty (h :*: w) f)
- zipLeavesList :: SZip ty w f -> [Maybe (Exists w)]
- data Zipper c f g t where
- type Zipper' kappa fam ann phi t = Zipper (CompoundCnstr kappa fam t) (HolesAnn kappa fam ann phi) (HolesAnn kappa fam ann phi) t
- zippers :: forall kappa fam ann phi t. (forall a. Elem t fam => phi a -> Maybe (a :~: t)) -> HolesAnn kappa fam ann phi t -> [Zipper' kappa fam ann phi t]
- zipConstructorName :: SZip h w f -> String
Documentation
data SZip ty w f where Source #
A value of type 'SZip ty w f' corresponds to a value of type
'SRep w f' with one of its leaves of type w ty
absent.
This is essentially a zipper for SRep
.
Z_KH :: SZip ty w (K1 i ty) | |
Z_L1 :: SZip ty w f -> SZip ty w (f :+: g) | |
Z_R1 :: SZip ty w g -> SZip ty w (f :+: g) | |
Z_PairL :: SZip ty w f -> SRep w g -> SZip ty w (f :*: g) | |
Z_PairR :: SRep w f -> SZip ty w g -> SZip ty w (f :*: g) | |
Z_M1 :: SMeta i t -> SZip ty w f -> SZip ty w (M1 i t f) |
zipperRepZip :: SZip ty h f -> SRep w f -> Maybe (SRep (Sum ((:~:) ty) h :*: w) f) Source #
Given a z :: SZip ty h f
and a r :: Rep w f
, if z
and r
are made with the same constuctor we return a representation
that contains both h
s and w
s in its leaves, except in one leaf
of type ty
. This is analogous to zipSRep
.
zipSZip :: SZip ty h f -> SZip ty w f -> Maybe (SZip ty (h :*: w) f) Source #
Overlaps two zippers together; only succeeds if both zippers have the same constructor AND hole.
zipLeavesList :: SZip ty w f -> [Maybe (Exists w)] Source #
Analogous to repLeavesList
type Zipper' kappa fam ann phi t = Zipper (CompoundCnstr kappa fam t) (HolesAnn kappa fam ann phi) (HolesAnn kappa fam ann phi) t Source #
Auxiliar type synonym for annotated fixpoints.
zippers :: forall kappa fam ann phi t. (forall a. Elem t fam => phi a -> Maybe (a :~: t)) -> HolesAnn kappa fam ann phi t -> [Zipper' kappa fam ann phi t] Source #
Given a function that checks wheter an arbitrary position
is recursive and a value of t
, returns all possible zippers ove
t
.
zipConstructorName :: SZip h w f -> String Source #
Retrieves the constructor name for a representation.
WARNING; UNSAFE this function only works if f
is the representation of
a type constructed with GHC.Generics builtin mechanisms.