sai-shape-syb-0.3.3: Obtain homogeneous values from arbitrary values, transforming or culling data

Copyright(c) Andrew Seniuk, 2014
LicenseBSD-style (see the LICENSE file)
Maintainerrasfar@gmail.com
Stabilityexperimental
Portabilitynon-portable (uses Data.Generics.Basics)
Safe HaskellNone
LanguageHaskell2010

SAI.Data.Generics.Shape.SYB

Contents

Description

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.

Synopsis

Types

type Homo r = Rose r Source

type Bi r = Homo (Dynamic, r) Source

type Shape = Homo () Source

type HomoM r = Homo (Maybe r) Source

type BiM r = Bi (Maybe r) Source

Rose Tree Type

type Rose = Tree Source

From Data.Tree we have, essentially

data Tree r = Node r [Tree r]

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).

ghomP :: forall r s d. Data d => GenericQ Bool -> GenericQ r -> d -> Homo r Source

Like ghom, but also filter branches using a generic predicate, retaining the stop nodes. The GenericQ r argument can be specialised for the stop node type(s), for instance to summarise stop branches. (See ghomE for more flexibility.)

ghomE :: forall r s d. Data d => GenericQ Bool -> GenericQ r -> GenericQ s -> d -> Homo (Either r s) Source

Like ghom, but also filter branches using a generic predicate, retaining the stop nodes and summarising their branches in Right values; default values are placed in the non-stop, Left nodes. You can fmap your own function (s -> r) to the result, then collapse from Either r r to r in the obvious way. (The function ghomP is probably sufficient in most cases.)

ghomDyn :: forall d. Data d => d -> Hetero Source

Uses Data.Dynamic to support mutiple types homogeneously. Unlike ghom, this is invertible (unGhomDyn).

ghomBi :: forall r d. Data d => GenericQ r -> d -> Bi r Source

ghomBi f x = zipRose (ghomDyn x) (ghom f x)

Unlike ghom, you can recover the original, polytypic term (unGhomBi).

Inverses where possible

unGhomBi :: Typeable a => Bi r -> a Source

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

biToHomo :: Bi r -> Homo r Source

Drops the Dynamic component.

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

liftHomoM :: Homo r -> HomoM r Source

Conversion from Homo to HomoM by wrapping values in Just.

liftBiM :: Bi r -> BiM r Source

Analogous to liftHomoM.

unliftHomoM :: r -> HomoM r -> Homo r Source

Sometimes it makes sense to replace the Nothing nodes with a default value in type r.

The best default value will often be some function of the filtered, Just items.

unliftHomoM = fmap . flip maybe id

Lineal ordering is preserved among Just nodes.

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 BiM r using a default GenericQ 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 BiM r value returned contains Nothing 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 GenericQ r from this. It then maps the generic query over the source polytypic tree, the latter being recovered from the Dynamic 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.

XXX Still only calls error, when should throw an exception.

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.

shapeOf_ :: forall d. Data d => d -> Shape Source

Stop traversal on Strings.

sizeOf :: forall d. Data d => d -> Int Source

Generic number of nodes in a polytypic term.

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.

weightedShapeOf_ :: forall d. Data d => d -> Homo Int Source

Stop traversal on Strings, using the length of the string as the weight for the node rooting the String. XXX Using 2*length + 1 would be more consistent?

weightedRoseJust :: Rose (Maybe r) -> Rose (Maybe r, Int) Source

Produce a zipped rose tree, where the second component at a node is the number of non-Nothing (i.e. Just) descendants, plus one for itself if it is Just.

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.

unzipRose :: Rose (r, s) -> (Rose r, Rose s) Source

Inverse of zipRose (up to currying).

zipBi :: Bi r -> Bi s -> Bi (r, s) Source

Zip two Bis. It is the caller's responsibility to assure that the Dynamic component is the same in both arguments (in addition to assuring that the shapes are compatible).

unzipBi :: Bi (r, s) -> (Bi r, Bi s) Source

zip :: (Applicative f, Functor f) => (f a, f b) -> f (a, b) Source

unzip :: Functor f => f (a, b) -> (f a, f 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>>.

showHomoWhen :: Show r => (r -> Bool) -> Rose r -> String Source

showAsParens :: Homo r -> String Source

One-line, parentheses language representation of the shape of a Homo r.

showAsParensBool :: Homo Bool -> String Source

One-line, parentheses language representation of the shape of a Homo Bool, enriched by symbols for True (*) and False (.).

(While parentheses around the leaves can in principle be omitted, the loss in readability is not compensated by the shortening.)

showAsParensEnriched :: Show r => Homo r -> String Source

One-line, parentheses language representation of the shape of a Homo r, and nodes adorned with show r.

showAsParensEnrichedWhen :: Show r => (r -> Bool) -> Homo r -> String Source

One-line, parentheses language representation of the shape of a Homo r, and nodes adorned with show r when the predicate holds (and with . otherwise).

showAsParensEnrichedM :: Show r => HomoM r -> String Source

One-line, parentheses language representation of the shape of a HomoM r, with Just nodes designated by show r (and Nothing nodes by .).

showBi :: Show r => Bi r -> String Source

Re-exported from Data.Tree

data Tree a :: * -> *

Multi-way trees, also known as rose trees.

Constructors

Node a (Forest a) 

Instances

Monad Tree 
Functor Tree 
Applicative Tree 
Foldable Tree 
Traversable Tree 
Eq a => Eq (Tree a) 
Data a => Data (Tree a) 
Read a => Read (Tree a) 
Show a => Show (Tree a) 
NFData a => NFData (Tree a) 
Typeable (* -> *) Tree 

type Forest a = [Tree a]