Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module is analogous to RoseTreeTH
,
but we use no Template Haskell here.
Non-standard Rose-Tree datatype
Suppose we we have a mutually recursive family consisting of RoseTree's with some redundant constructor:
Non-standard Rose-tree datatype.
Family Structure
The R Int
family has many components, that must be encoded in
the generics-mrsop format. These are:
type FamRose = '[[R Int], R Int] Source #
The types corresponding the the codes in CodesRose
appear in the same order.
Family
Instance
Which in turn, allows us to write the Family
instance for
R Int
. The instance Family Singl FamRose CodesRose
states that
the types in FamRose
follow the codes in CodesRose
with
its opaque parts represented by Singl
Check the source code for more details
on the instance.
It is worth mentioning that deriveFamily
will derive
this code automatically.
instance Family Singl FamRose CodesRose where sfrom' (SS SZ) (El (a :>: as)) = Rep $ Here (NA_K (SInt a) :* NA_I (El as) :* Nil) sfrom' (SS SZ) (El (Leaf a)) = Rep $ There (Here (NA_K (SInt a) :* Nil)) sfrom' SZ (El []) = Rep $ Here Nil sfrom' SZ (El (x:xs)) = Rep $ There (Here (NA_I (El x) :* NA_I (El xs) :* Nil)) sfrom' _ _ = error "unreachable" sto' SZ (Rep (Here Nil)) = El [] sto' SZ (Rep (There (Here (NA_I (El x) :* NA_I (El xs) :* Nil)))) = El (x : xs) sto' (SS SZ) (Rep (Here (NA_K (SInt a) :* NA_I (El as) :* Nil))) = El (a :>: as) sto' (SS SZ) (Rep (There (Here (NA_K (SInt a) :* Nil)))) = El (Leaf a) sto' _ _ = error "unreachable"
Generic Combinators
Next, we showcase some of the simpler generic combinators provided out of the box with generics-mrsop
We can use generic equality out of the box:
instance Eq (R Int) where (==) = geq eqSingl `on` (into @FamRose)
If we run testEq
it must return True
, naturally.
normalize :: R Int -> R Int Source #
Here is an example of compos
; used to substitute the redundant Leaf
constructor by its standard rose tree representation.
normalize :: R Int -> R Int normalize = unEl . go (SS SZ) . into where go :: forall iy. (IsNat iy) => SNat iy -> El FamRose iy -> El FamRose iy go (SS SZ) (El (Leaf a)) = El (a :>: []) -- (SS SZ) is the index of 'R Int' in 'CodesRose' go _ x = compos go x
Then, for example,
normalize (42 :>: [Leaf 10 , 15 :>: [Leaf 20]]) == 42 :>: [10 :>: [] , 15 :>: [20 :>: []]]