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 fmap 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 limited support for structure-changing transformations, some generic, others on the homogeneous types.
- filterHomoM :: (r -> Bool) -> Homo r -> HomoM r
- filterBiM :: (r -> Bool) -> Bi r -> BiM r
- filterHomoMM :: HomoM r -> HomoM r
- filterBiMM :: BiM r -> BiM r
- filterHomo :: (r -> Bool) -> Homo r -> Homo r
- filterHetero :: Typeable r => (r -> Bool) -> Hetero -> Hetero
- filterBi :: (r -> Bool) -> Bi r -> Bi r
- filterHomoM_ :: HomoM r -> [Homo r]
- filterHomoM_' :: r -> HomoM r -> Homo r
- gfilter :: forall r d. Data d => (forall d. (Data d, Typeable d) => d -> Maybe r) -> d -> [Homo r]
- gfilter_ :: forall r d. Data d => r -> (forall d. (Data d, Typeable d) => d -> Maybe r) -> d -> Homo r
- mkQP :: forall r a b. (Typeable a, Typeable b) => (r -> Bool) -> (b -> Maybe r) -> a -> Maybe r
- shapeOf_ :: forall d. Data d => d -> Shape
Lifted result, but good structure preservation (via glue nodes)
These functions simplify the structure by removing all possible
Nothing
nodes, without disrupting the lineal relations obtaining
between Just
nodes.
Recall that
typeHomoM
r =Homo
(Maybe
r)
and
typeBiM
r =Bi
(Maybe
r) =Homo
(Dynamic
, (Maybe
r))
filterHomoM :: (r -> Bool) -> Homo r -> HomoM r Source
Tolerate lifted nodes in the result, in exchange for better structure preservation.
Lineal ordering is preserved among Just
nodes.
In the end, this is probably the most useful (unless one that takes a generic predicate, and acts on original types obtained via fromDyn[amic]...).
filterBiM :: (r -> Bool) -> Bi r -> BiM r Source
As per filterHomoM
, but we string along the Dynamic
component.
Lifted argument, as well as result; same transformation
Note that these functions don't take a predicate;
the filtering predicate is encoded in the
input.Maybe
r
filterHomoMM :: HomoM r -> HomoM r Source
Tolerate lifted nodes in the result, in exchange for better structure preservation.
Lineal ordering is preserved among Just
nodes.
filterBiMM :: BiM r -> BiM r Source
As per filterHomoMM
, but we string along the Dynamic
component.
Unlifted result, but less structure preserved (no glue nodes)
These filter functions produce trees containing only nodes which satisfy the predicate, and yet which inherit the structure of the argument to some extent.
For each node N, the algorithm acts on all children C of N which fail the predicate. The transformation is to move the grandchildren of N via C into child position, in place of C, which is elided. Recurse to fixed point. (You'd think one of bottom-up or top-down would do it in one pass, but ... maybe I did something wrong...)
Other transformations are possible; see also 'filterHomoM_.
filterHomo :: (r -> Bool) -> Homo r -> Homo r Source
Lifted argument, less structure preservation (no glue nodes)
These don't require a predicate or default values, depending
instead on Nothing
for default, and on the predicate being
encoded as Nothing
/ Just
.
filterHomoM_ :: HomoM r -> [Homo r] Source
filterHomoM_
acts on a lifted type to avoid needing to
specify any default values; however, the root node cannot
be eliminated by this algorithm, so in case the root is
a Nothing
, we need to return its child branches as a forest.
filterHomoM_' :: r -> HomoM r -> Homo r Source
filterHomoM_
plus a root default value in the homogeneous type;
this allows us to always return a single rooted tree in type
.
Compare to Homo
rfilterHomoM_
which, lacking such a root default,
is obliged to return [
.Homo
r]
Experimental...
gfilter :: forall r d. Data d => (forall d. (Data d, Typeable d) => d -> Maybe r) -> d -> [Homo r] Source
Later yet: It didn't quite work out. (However, using Dynamic may be a way to get around?) The trouble is, the user ... actually there's one more thing I can test ... was thinking about this while falling asleep -- how to automatically "lift and extend" a user-defined non-generic function
f :: SomeType -> Result
to
f :: SomeType -> Maybe Result
also automatically providing the default case (which the user can't provide without either lifting their type themself, or constructing some value of type (can use undefined?...) Going to try this possibility first... In a "gfilter2".
Later: Do the following procedure: (Going to try allowing passing of non-generic p and f, first. However, if would have used extQ, this will not allow it...)
- Wrap f to f', which uses Maybe r.
- Do the generic homomorphism to Maybe r, using Nothing for a node iff the predicate fails.
- Call filterHomo on the result (Homo (Maybe a)), with predicate (not . isNothing).
- Unwrap Homo (Maybe a) result of 3., to final Homo a result.
Old comments: Intended for use with fully generic predicate, NOT as a stop condition, but as a structure-modifying tree rewrite as done for filterHomo. Nodes are retained if and only if they satisfy the predicate. An effort is made to preserve structure, it's simple enough to be in the canonical regime, but other transformations are possible. It seems the caller must also call mkQP?
gfilter_ :: forall r d. Data d => r -> (forall d. (Data d, Typeable d) => d -> Maybe r) -> d -> Homo r Source
Analogous to gfilter
, but takes a default value in r
and
returns a single tree (instead of a forest). Uses filterHomoM_'
.
mkQP :: forall r a b. (Typeable a, Typeable b) => (r -> Bool) -> (b -> Maybe r) -> a -> Maybe r Source
Another alternative (may not work): Take non-generic predicate and transform, and do here all of: - lifting to Maybe - providing the default case needed by mkQ - doing mkQ on the predicate and transform This has obvious appeal as the API user need not use and generics functions directly. However, a weakness is, only a single type for predicate, and only a single (possibly other) type for the transform, can be dealt with. So there is also gfilter3 which takes generic predicate and function, so the user can use extQ as needed to cover more than a single type. There may be an even better way, maybe using Data.Dynamic?...
Would like to be able to call this automatically from gfilter, but I think the user code must call it, and pass the result to gfilter...
shapeOf_ :: forall d. Data d => d -> Shape Source
Attempt to stop traversal on String
s.
This should be in Shape.SYB, but it would be cyclical imports
which GHC can't handle.
XXX This seems not to be working.
The stop condition is not being done properly.
Refer to everythingBut (again) to remind how to do...