Copyright | (c) Andrew Seniuk, 2014 |
---|---|
License | BSD-style (see the LICENSE file) |
Maintainer | rasfar@gmail.com |
Stability | experimental |
Portability | non-portable (uses Data.Generics.Basics) |
Safe Haskell | None |
Language | Haskell2010 |
This package provides SYB shape support: generic mapping to homogeneous types, and related features. Complements existing Uniplate and TH shape libraries. See http://www.fremissant.net/shape-syb for more information.
The present module provides the main types and functions.
- type Homo r = Rose r
- type Hetero = Homo Dynamic
- type Bi r = Homo (Dynamic, r)
- type Shape = Homo ()
- type HomoM r = Homo (Maybe r)
- type BiM r = Bi (Maybe r)
- type Rose = Tree
- ghom :: forall r d. Data d => GenericQ r -> d -> Homo r
- ghomK :: forall r d. Data d => (r -> r -> r) -> GenericQ r -> d -> Homo r
- ghomDyn :: forall d. Data d => d -> Hetero
- ghomBi :: forall r d. Data d => GenericQ r -> d -> Bi r
- unGhomDyn :: Typeable a => Hetero -> a
- unGhomBi :: Typeable a => Bi r -> a
- biToHomo :: Bi r -> Homo r
- biToHetero :: Bi r -> Hetero
- heteroToBi :: forall r d. (Data d, Typeable d, Typeable r) => r -> (d -> r) -> Hetero -> Bi r
- liftHomoM :: Homo r -> HomoM r
- liftBiM :: Bi r -> BiM r
- unliftHomoM :: r -> HomoM r -> Homo r
- unliftBiM :: r -> BiM r -> Bi r
- gempty :: forall r d. (Typeable r, Data d) => d -> BiM r
- grefine :: forall r d. (Typeable r, Data d, Typeable d) => (d -> Maybe r) -> BiM r -> BiM r
- gaccum :: forall r d. (Typeable r, Data d, Typeable d) => (r -> r -> r) -> (d -> Maybe r) -> BiM r -> BiM r
- shapeOf :: forall d. Data d => d -> Shape
- sizeOf :: forall d. Data d => d -> Int
- symmorphic :: forall d1 d2. (Data d1, Data d2) => d1 -> d2 -> Bool
- (~~) :: forall d1 d2. (Data d1, Data d2) => d1 -> d2 -> Bool
- weightedShapeOf :: forall d. Data d => d -> Homo Int
- weightedRose :: Rose r -> Rose (r, Int)
- weightedRoseJust :: Rose (Maybe r) -> Rose (Maybe r, Int)
- sizeOfRose :: Rose a -> Int
- zipRose :: Rose r -> Rose s -> Rose (r, s)
- unzipRose :: Rose (r, s) -> (Rose r, Rose s)
- zipBi :: Bi r -> Bi s -> Bi (r, s)
- unzipBi :: Bi (r, s) -> (Bi r, Bi s)
- zip :: (Applicative f, Functor f) => (f a, f b) -> f (a, b)
- unzip :: Functor f => f (a, b) -> (f a, f b)
- showHomo :: Show r => Rose r -> String
- showHomoM :: Show r => Rose (Maybe r) -> String
- showAsParens :: Homo r -> String
- showAsParensBool :: Homo Bool -> String
- showAsParensEnriched :: Show r => Homo r -> String
- showAsParensEnrichedM :: Show r => HomoM r -> String
- showDyn :: Dynamic -> String
- showHetero :: Hetero -> String
- showBi :: Show r => Bi r -> String
- data Tree a :: * -> * = Node a (Forest a)
- type Forest a = [Tree a]
Types
Rose Tree Type
Homomorphisms
ghom :: forall r d. Data d => GenericQ r -> d -> Homo r Source
Map an arbitrary data constructor application expression to
a homogeneous representation preserving structure.
This is a one-way trip; what value information is preserved
depends on the mapping function you provide.
Use ghomDyn
or ghomBi
if you need to be able
to recover the original, heterogeneous data.
ghomK :: forall r d. Data d => (r -> r -> r) -> GenericQ r -> d -> Homo r Source
Like ghom, but use a custom combining function, instead of
the default (\r _->r)
.
ghomDyn :: forall d. Data d => d -> Hetero Source
Uses Data.Dynamic to support mutiple types homogeneously.
Unlike ghom
, this is invertible (unGhomDyn
).
Inverses where possible
Conversions
These conversion functions should obey at least the following laws.
ghom
f =biToHomo
.ghomBi
f
biToHetero
.ghomBi
g =biToHetero
.ghomBi
f
ghomBi
f =heteroToBi
f .ghomDyn
ghomBi
g =heteroToBi
g .biToHetero
.ghomBi
f
biToHetero :: Bi r -> Hetero Source
Drops the homogeneous component (type r
).
heteroToBi :: forall r d. (Data d, Typeable d, Typeable r) => r -> (d -> r) -> Hetero -> Bi r Source
Conversions concerning lifted types
unliftHomoM :: r -> HomoM r -> Homo r Source
unliftBiM :: r -> BiM r -> Bi r Source
Analogous to unliftHomoM
.
Progressive refinement and accumulation
gempty :: forall r d. (Typeable r, Data d) => d -> BiM r Source
Sets up a
using a default BiM
rGenericQ
which
assigns all values to Nothing
.
Use an expression type signature at the call site, to constrain
the type r
(the usual trick)
( gempty x :: BiM ( Int , Data.IntMap Text , [Float] ) )
so your choice type r
is a triple, but the
value
returned contains BiM
rNothing
at every node. This prepares it
for refinement and accumulation.
grefine :: forall r d. (Typeable r, Data d, Typeable d) => (d -> Maybe r) -> BiM r -> BiM r Source
Given a monomorphic function you provide, returning r,
automatically makes a
from this. It then maps
the generic query over the source polytypic tree, the latter
being recovered from the GenericQ
rDynamic
component of the BiM
.
The target is updated with write-once semantics enforced;
that is to say, grefine
will throw an exception if it finds
a Just
already present at any place in the result tree that
it would update.
gaccum :: forall r d. (Typeable r, Data d, Typeable d) => (r -> r -> r) -> (d -> Maybe r) -> BiM r -> BiM r Source
Like grefine
, but rather than throw exception, it
takes a combining function argument to cope with that situation.
For convenience
shapeOf :: forall d. Data d => d -> Shape Source
Trivial homomorphism that discards all value information.
symmorphic :: forall d1 d2. (Data d1, Data d2) => d1 -> d2 -> Bool Source
Compare two general polytypic values for shape equality.
(~~) :: forall d1 d2. (Data d1, Data d2) => d1 -> d2 -> Bool Source
Operator synonymous with symmorphic
.
weightedShapeOf :: forall d. Data d => d -> Homo Int Source
Weight of a node is defined as the number of descendants, plus 1.
weightedRose :: Rose r -> Rose (r, Int) Source
sizeOfRose :: Rose a -> Int Source
Number of nodes in a rose tree.
zipRose :: Rose r -> Rose s -> Rose (r, s) Source
Combine two rose trees with identical shape, by tupling their values.
zip :: (Applicative f, Functor f) => (f a, f b) -> f (a, b) Source
Showing values
Pretty-printing of rose trees, including compact representations. Also, show functions for a subset of Dynamic values, which show the value and not just <<
type>>
.
showAsParens :: Homo r -> String Source
showAsParensBool :: Homo Bool -> String Source
showAsParensEnriched :: Show r => Homo r -> String Source
showAsParensEnrichedM :: Show r => HomoM r -> String Source
showHetero :: Hetero -> String Source
Re-exported from Data.Tree
data Tree a :: * -> *
Multi-way trees, also known as rose trees.