-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Help writing simple, concise and fast generic operations. -- -- Uniplate is library for writing simple and concise generic operations. -- Uniplate has similar goals to the original Scrap Your Boilerplate -- work, but is substantially simpler and faster. The Uniplate manual is -- available at -- http://community.haskell.org/~ndm/darcs/uniplate/uniplate.htm. -- -- To get started with Uniplate you should import one of the three -- following modules: -- -- -- -- In addition, some users may want to make use of the following modules: -- -- @package uniplate @version 1.6.7 -- | In some cases, Data instances for abstract types are incorrect, -- and fail to work correctly with Uniplate. This module defines three -- helper types (Hide, Trigger and Invariant) to -- assist when writing instances for abstract types. The Hide type -- is useful when you want to mark some part of your data type as being -- ignored by Data.Generics.Uniplate.Data (and any other -- Data based generics libraries, such as syb). -- -- Using the helper types, this module defines wrappers for types in the -- containers package, namely Map, Set, -- IntMap and IntSet. The standard containers -- Data instances all treat the types as abstract, but the wrapper -- types allow you to traverse within the data types, ensuring the -- necessary invariants are maintained. In particular, if you do not -- modify the keys reconstruct will be O(n) instead of O(n log -- n). -- -- As an example of how to implement your own abstract type wrappers, the -- Map data type is defined as: -- --
--   newtype Map k v = Map (Invariant (Trigger [k], Trigger [v], Hide (Map.Map k v)))
--      deriving (Data, Typeable)
--   
-- -- The Map type is defined as an Invariant of three -- components - the keys, the values, and the underlying Map. We -- use Invariant to ensure that the keysvaluesmap always -- remain in sync. We use Trigger on the keys and values to ensure -- that whenever the keys or values change we rebuild the Map, -- but if they don't, we reuse the previous Map. The -- fromMap function is implemented by pattern matching on the -- Map type: -- --
--   fromMap (Map (Invariant _ (_,_,Hide x))) = x
--   
-- -- The toMap function is slightly harder, as we need to come up -- with an invariant restoring function: -- --
--   toMap :: Ord k => Map.Map k v -> Map k v
--   toMap x = Map $ Invariant inv $ create x
--       where
--           create x = (Trigger False ks, Trigger False vs, Hide x)
--               where (ks,vs) = unzip $ Map.toAscList x
--   
--           inv (ks,vs,x)
--               | trigger ks = create $ Map.fromList $ zip (fromTrigger ks) (fromTrigger vs)
--               | trigger vs = create $ Map.fromDistinctAscList $ zip (fromTrigger ks) (fromTrigger vs)
--               | otherwise = (ks,vs,x)
--   
-- -- The create function creates a value from a Map, -- getting the correct keys and values. The inv function looks -- at the triggers on the keys/values. If the keys trigger has been -- tripped, then we reconstruct the Map using fromList. -- If the values trigger has been tripped, but they keys trigger has not, -- we can use fromDistinctAscList, reducing the complexity of -- constructing the Map. If nothing has changed we can reuse the -- previous value. -- -- The end result is that all Uniplate (or syb) traversals over -- Map result in a valid value, which has had all appropriate -- transformations applied. module Data.Generics.Uniplate.Data.Instances -- | The Hide data type has a Data instance which reports -- having no constructors, as though the type was defined as using the -- extension EmptyDataDecls: -- --
--   data Hide a
--   
-- -- This type is suitable for defining regions that are avoided by -- Uniplate traversals. As an example: -- --
--   transformBi (+1) (1, 2, Hide 3, Just 4) == (2, 3, Hide 3, Just 4)
--   
-- -- As a result of having no constructors, any calls to the methods -- toConstr or gunfold will raise an error. newtype Hide a Hide :: a -> Hide a fromHide :: Hide a -> a -- | The Trigger data type has a Data instance which reports -- as being defined: -- --
--   data Trigger a = Trigger a
--   
-- -- However, whenever a gfoldl or gunfold constructs a new -- value, it will have the trigger field set to True. The -- trigger information is useful to indicate whether any invariants have -- been broken, and thus need fixing. As an example: -- --
--   data SortedList a = SortedList (Trigger [a]) deriving (Data,Typeable)
--   toSortedList xs = SortedList $ Trigger False $ sort xs
--   fromSortedList (SortedList (Trigger t xs)) = if t then sort xs else xs
--   
-- -- This data type represents a sorted list. When constructed the items -- are initially sorted, but operations such as gmapT could break -- that invariant. The Trigger type is used to detect when the -- Data operations have been performed, and resort the list. -- -- The Trigger type is often used in conjunction with -- Invariant, which fixes the invariants. data Trigger a Trigger :: Bool -> a -> Trigger a trigger :: Trigger a -> Bool fromTrigger :: Trigger a -> a -- | The Invariant data type as a Data instance which reports -- as being defined: -- --
--   data Invariant a = Invariant a
--   
-- -- However, whenever a gfoldl constructs a new value, it will have -- the function in the invariant field applied to it. As an -- example: -- --
--   data SortedList a = SortedList (Invariant [a]) deriving (Data,Typeable)
--   toSortedList xs = SortedList $ Invariant sort (sort xs)
--   fromSortedList (SortedList (Invariant _ xs)) = xs
--   
-- -- Any time an operation such as gmapT is applied to the data -- type, the invariant function is applied to the result. The -- fromSortedList function can then rely on this invariant. -- -- The gunfold method is partially implemented - all constructed -- values will have an undefined value for all fields, regardless of -- which function is passed to fromConstrB. If you only use -- fromConstr (as Uniplate does) then the gunfold method is -- sufficient. data Invariant a Invariant :: (a -> a) -> a -> Invariant a invariant :: Invariant a -> a -> a fromInvariant :: Invariant a -> a -- | Invariant preserving version of Map from the -- containers packages, suitable for use with Uniplate. -- Use toMap to construct values, and fromMap to -- deconstruct values. data Map k v -- | Deconstruct a value of type Map. fromMap :: Map k v -> Map k v -- | Construct a value of type Map. toMap :: Ord k => Map k v -> Map k v -- | Invariant preserving version of Set from the -- containers packages, suitable for use with Uniplate. -- Use toSet to construct values, and fromSet to -- deconstruct values. data Set k -- | Deconstruct a value of type Set. fromSet :: Set k -> Set k -- | Construct a value of type Set. toSet :: Ord k => Set k -> Set k -- | Invariant preserving version of IntMap from the -- containers packages, suitable for use with Uniplate. -- Use toIntMap to construct values, and fromIntMap to -- deconstruct values. data IntMap v -- | Deconstruct a value of type IntMap. fromIntMap :: IntMap v -> IntMap v -- | Construct a value of type IntMap. toIntMap :: IntMap v -> IntMap v -- | Invariant preserving version of IntSet from the -- containers packages, suitable for use with Uniplate. -- Use toIntSet to construct values, and fromIntSet to -- deconstruct values. data IntSet -- | Deconstruct a value of type IntSet. fromIntSet :: IntSet -> IntSet -- | Construct a value of type IntSet. toIntSet :: IntSet -> IntSet instance Typeable1 Hide instance Typeable1 Trigger instance Typeable1 Invariant instance Typeable2 Map instance Typeable1 Set instance Typeable1 IntMap instance Typeable IntSet instance Read a => Read (Hide a) instance Ord a => Ord (Hide a) instance Eq a => Eq (Hide a) instance Read a => Read (Trigger a) instance Ord a => Ord (Trigger a) instance Eq a => Eq (Trigger a) instance Show a => Show (Trigger a) instance (Data k, Data v) => Data (Map k v) instance Data k => Data (Set k) instance Data v => Data (IntMap v) instance Data IntSet instance Ord IntSet instance Eq IntSet instance Show IntSet instance Ord v => Ord (IntMap v) instance Eq v => Eq (IntMap v) instance Show v => Show (IntMap v) instance Ord k => Ord (Set k) instance Eq k => Eq (Set k) instance Show k => Show (Set k) instance (Ord k, Ord v) => Ord (Map k v) instance (Eq k, Eq v) => Eq (Map k v) instance (Show k, Show v) => Show (Map k v) instance (Data a, Typeable a) => Data (Invariant a) instance Show a => Show (Invariant a) instance (Data a, Typeable a) => Data (Trigger a) instance Functor Trigger instance Typeable a => Data (Hide a) instance Functor Hide instance Show a => Show (Hide a) -- | DEPRECATED Use Data.Generics.Uniplate.Operations -- instead. -- -- This is the main Uniplate module, which defines all the essential -- operations in a Haskell 98 compatible manner. -- -- Most functions have an example of a possible use for the function. To -- illustate, I have used the Expr type as below: -- --
--   data Expr = Val Int
--             | Neg Expr
--             | Add Expr Expr
--   
module Data.Generics.Uniplate -- | The type of replacing all the children of a node -- -- Taking a value, the function should return all the immediate children -- of the same type, and a function to replace them. type UniplateType on = on -> ([on], [on] -> on) -- | The standard Uniplate class, all operations require this class Uniplate on uniplate :: Uniplate on => UniplateType on -- | Get all the children of a node, including itself and all children. -- --
--   universe (Add (Val 1) (Neg (Val 2))) =
--       [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]
--   
-- -- This method is often combined with a list comprehension, for example: -- --
--   vals x = [i | Val i <- universe x]
--   
universe :: Uniplate on => on -> [on] -- | Get the direct children of a node. Usually using universe is -- more appropriate. -- --
--   children = fst . uniplate
--   
children :: Uniplate on => on -> [on] -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
--   negLits = transform f
--      where f (Neg (Lit i)) = Lit (negate i)
--            f x = x
--   
transform :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of transform transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewrite r x = all (isNothing . r) (universe (rewrite r x))
--   
-- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct f mplus g -- which performs both rewrites until a fixed point. rewrite :: Uniplate on => (on -> Maybe on) -> on -> on -- | Monadic variant of rewrite rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on -- | Perform a transformation on all the immediate children, then combine -- them back. This operation allows additional information to be passed -- downwards, and can be used to provide a top-down transformation. descend :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of descend descendM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Return all the contexts and holes. -- --
--   propUniverse x = universe x == map fst (contexts x)
--   propId x = all (== x) [b a | (a,b) <- contexts x]
--   
contexts :: Uniplate on => on -> [(on, on -> on)] -- | The one depth version of contexts -- --
--   propChildren x = children x == map fst (holes x)
--   propId x = all (== x) [b a | (a,b) <- holes x]
--   
holes :: Uniplate on => on -> [(on, on -> on)] -- | Perform a fold-like computation on each value, technically a -- paramorphism para :: Uniplate on => (on -> [r] -> r) -> on -> r -- | DEPRECATED: Use Data.Generics.Uniplate.Operations -- instead. -- -- This module retained Haskell 98 compatability, but users who are happy -- with multi-parameter type classes should look towards -- Data.Generics.Biplate. -- -- The only function missing from Data.Generics.Uniplate is -- fold, as it can be constructed from children and has -- little meaning in a multi-typed setting. -- -- All operations, apart from childrenOn should perform -- identically to their non On counterparts. module Data.Generics.UniplateOn -- | Return all the top most children of type to within -- from. -- -- If from == to then this function should return the root as -- the single child. type BiplateType from to = from -> ([to], [to] -> from) universeOn :: Uniplate to => BiplateType from to -> from -> [to] -- | Return the children of a type. If to == from then it returns -- the original element (in contrast to children) childrenOn :: Uniplate to => BiplateType from to -> from -> [to] transformOn :: Uniplate to => BiplateType from to -> (to -> to) -> from -> from transformOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m to) -> from -> m from rewriteOn :: Uniplate to => BiplateType from to -> (to -> Maybe to) -> from -> from rewriteOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m (Maybe to)) -> from -> m from descendOn :: Uniplate to => BiplateType from to -> (to -> to) -> from -> from descendOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m to) -> from -> m from holesOn :: Uniplate to => BiplateType from to -> from -> [(to, to -> from)] contextsOn :: Uniplate to => BiplateType from to -> from -> [(to, to -> from)] -- | Used for defining instances UniplateFoo a => UniplateFoo -- [a] uniplateOnList :: BiplateType a b -> BiplateType [a] b -- | This module provides the Str data type, which is used by the -- underlying uniplate and biplate methods. It should -- not be used directly under normal circumstances. module Data.Generics.Str data Str a Zero :: Str a One :: a -> Str a Two :: (Str a) -> (Str a) -> Str a -- | Take the type of the method, will crash if called strType :: Str a -> a -- | Convert a Str to a list, assumes the value was created with -- listStr strList :: Str a -> [a] -- | Convert a list to a Str listStr :: [a] -> Str a -- | Transform a Str to a list, and back again, in a structure -- preserving way. The output and input lists must be equal in length. strStructure :: Str a -> ([a], [a] -> Str a) instance Show a => Show (Str a) instance Traversable Str instance Foldable Str instance Functor Str instance Eq a => Eq (Str a) -- | Definitions of Uniplate and Biplate classes, along with -- all the standard operations. -- -- Import this module directly only if you are defining new Uniplate -- operations, otherwise import one of -- Data.Generics.Uniplate.Direct, -- Data.Generics.Uniplate.Typeable or -- Data.Generics.Uniplate.Data. -- -- Most functions have an example of a possible use for the function. To -- illustate, I have used the Expr type as below: -- --
--   data Expr = Val Int
--             | Neg Expr
--             | Add Expr Expr
--   
module Data.Generics.Uniplate.Operations -- | The standard Uniplate class, all operations require this. All -- definitions must define uniplate, while descend and -- descendM are optional. class Uniplate on where descend f x = generate $ fmap f current where (current, generate) = uniplate x descendM f x = liftM generate $ mapM f current where (current, generate) = uniplate x uniplate :: Uniplate on => on -> (Str on, Str on -> on) descend :: Uniplate on => (on -> on) -> on -> on descendM :: (Uniplate on, Monad m) => (on -> m on) -> on -> m on -- | Children are defined as the top-most items of type to starting at -- the root. All instances must define biplate, while -- descendBi and descendBiM are optional. class Uniplate to => Biplate from to where descendBi f x = generate $ fmap f current where (current, generate) = biplate x descendBiM f x = liftM generate $ mapM f current where (current, generate) = biplate x biplate :: Biplate from to => from -> (Str to, Str to -> from) descendBi :: Biplate from to => (to -> to) -> from -> from descendBiM :: (Biplate from to, Monad m) => (to -> m to) -> from -> m from -- | Get all the children of a node, including itself and all children. -- --
--   universe (Add (Val 1) (Neg (Val 2))) =
--       [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]
--   
-- -- This method is often combined with a list comprehension, for example: -- --
--   vals x = [i | Val i <- universe x]
--   
universe :: Uniplate on => on -> [on] -- | Get the direct children of a node. Usually using universe is -- more appropriate. children :: Uniplate on => on -> [on] -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
--   negLits = transform f
--      where f (Neg (Lit i)) = Lit (negate i)
--            f x = x
--   
transform :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of transform transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewrite r x = all (isNothing . r) (universe (rewrite r x))
--   
-- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct f mplus -- g which performs both rewrites until a fixed point. rewrite :: Uniplate on => (on -> Maybe on) -> on -> on -- | Monadic variant of rewrite rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on -- | Return all the contexts and holes. -- --
--   universe x == map fst (contexts x)
--   all (== x) [b a | (a,b) <- contexts x]
--   
contexts :: Uniplate on => on -> [(on, on -> on)] -- | The one depth version of contexts -- --
--   children x == map fst (holes x)
--   all (== x) [b a | (a,b) <- holes x]
--   
holes :: Uniplate on => on -> [(on, on -> on)] -- | Perform a fold-like computation on each value, technically a -- paramorphism para :: Uniplate on => (on -> [r] -> r) -> on -> r universeBi :: Biplate from to => from -> [to] -- | Return the children of a type. If to == from then it returns -- the original element (in contrast to children) childrenBi :: Biplate from to => from -> [to] transformBi :: Biplate from to => (to -> to) -> from -> from transformBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> from rewriteBiM :: (Monad m, Biplate from to) => (to -> m (Maybe to)) -> from -> m from contextsBi :: Biplate from to => from -> [(to, to -> from)] holesBi :: Biplate from to => from -> [(to, to -> from)] -- | Compos compatibility layer. This module serves as a drop-in -- replacement in some situations for some of the Compos operations. Only -- the single-type traversals are supported, on normal algebraic data -- types. Users should also import either -- Data.Generics.Uniplate.Data or -- Data.Generics.Uniplate.Direct. -- -- Compos is described in the paper: "A Pattern for Almost Compositional -- Functions" by Bjorn Bringert and Aarne Ranta. -- -- module Data.Generics.Compos -- | If you want to keep an existing type class class Uniplate a => Compos a -- |
--   composOp == descend
--   
composOp :: Uniplate a => (a -> a) -> a -> a -- |
--   composOpM == descendM
--   
composOpM :: (Uniplate a, Monad m) => (a -> m a) -> a -> m a -- |
--   composOpM_ == composOpFold (return ()) (>>)
--   
composOpM_ :: (Uniplate a, Monad m) => (a -> m ()) -> a -> m () -- |
--   composOpMonoid = composOpFold mempty mappend
--   
composOpMonoid :: (Uniplate a, Monoid m) => (a -> m) -> a -> m -- |
--   composOpMPlus = composOpFold mzero mplus
--   
composOpMPlus :: (Uniplate a, MonadPlus m) => (a -> m b) -> a -> m b -- | Probably replace with universe, perhaps para composOpFold :: Uniplate a => b -> (b -> b -> b) -> (a -> b) -> a -> b -- | SYB compatibility layer. This module serves as a drop-in replacement -- in some situations for some of the SYB operations. Users should also -- import Data.Generics.Uniplate.Data. -- -- SYB is described in the paper: "Scrap your boilerplate: a practical -- design pattern for generic programming" by Ralf Lammel and Simon -- Peyton Jones. -- -- module Data.Generics.SYB -- |
--   gmapT == descend
--   
gmapT :: Uniplate a => (a -> a) -> a -> a -- | Use children and foldl gmapQl :: Uniplate a => (r -> r' -> r) -> r -> (a -> r') -> a -> r -- | Use children and foldr gmapQr :: Uniplate a => (r' -> r -> r) -> r -> (a -> r') -> a -> r -- | Use children gmapQ :: Uniplate a => (a -> u) -> a -> [u] -- | Use children and !! gmapQi :: Uniplate a => Int -> (a -> u) -> a -> u -- |
--   gmapM == descendM
--   
gmapM :: (Uniplate a, Monad m) => (a -> m a) -> a -> m a -- |
--   mkT == id
--   
mkT :: (a -> a) -> (a -> a) -- |
--   everywhere == transformBi
--   
everywhere :: Biplate b a => (a -> a) -> b -> b -- |
--   mkM == id
--   
mkM :: Monad m => (a -> m a) -> a -> m a -- |
--   everywhereM == transformBiM
--   
everywhereM :: (Biplate b a, Monad m) => (a -> m a) -> b -> m b -- | Only for use with everything mkQ :: r -> (a -> r) -> (r, a -> r) -- | Use universe or universeBi, perhaps followed by a fold. -- -- Not an exact equivalent to the SYB everything, as the -- operators may be applied in different orders. everything :: Biplate b a => (r -> r -> r) -> (r, a -> r) -> b -> r -- | This module defines Uniplate / Biplate instances for -- every type with a Data instance. Using GHC, Data can be derived -- automatically with: -- --
--   data Expr = Var Int | Neg Expr | Add Expr Expr
--               deriving (Data,Typeable)
--   
-- -- All the Uniplate operations defined in -- Data.Generics.Uniplate.Operations can be used. If you are -- working with abstract data types, such as Map or Set -- from the containers package, you may also need to use the -- data types defined in Data.Generics.Uniplate.Data.Instances. -- -- For faster performance (5x faster, but requires writing instances) -- switch to Data.Generics.Uniplate.Direct. If you get instance -- conflicts when using both Data and Direct, switch to -- Data.Generics.Uniplate.DataOnly. -- -- The instances are faster than GHC because they precompute a table of -- useful information, then use this information when performing the -- traversals. Sometimes it is not possible to compute the table, in -- which case this library will perform about the same speed as SYB. -- -- Setting the environment variable $UNIPLATE_VERBOSE has the -- following effects: -- -- -- -- The $UNIPLATE_VERBOSE environment variable must be set before -- the first call to uniplate. module Data.Generics.Uniplate.Data -- | Apply a sequence of transformations in order. This function obeys the -- equivalence: -- --
--   transformBis [[transformer f],[transformer g],...] == transformBi f . transformBi g . ...
--   
-- -- Each item of type [Transformer] is applied in turn, right to -- left. Within each [Transformer], the individual -- Transformer values may be interleaved. -- -- The implementation will attempt to perform fusion, and avoid walking -- any part of the data structure more than necessary. To further improve -- performance, you may wish to partially apply the first argument, which -- will calculate information about the relationship between the -- transformations. transformBis :: Data a => [[Transformer]] -> a -> a data Transformer -- | Wrap up a (a -> a) transformation function, to use with -- transformBis transformer :: Data a => (a -> a) -> Transformer instance (Data a, Data b, Uniplate b) => Biplate a b instance Data a => Uniplate a -- | This module functions identically to -- Data.Generics.Uniplate.Data, but instead of using the standard -- Uniplate / Biplate classes defined in -- Data.Generics.Uniplate.Operations it uses a local copy. -- -- Only use this module if you are using both Data and -- Direct instances in the same project and they are -- conflicting. module Data.Generics.Uniplate.DataOnly -- | The standard Uniplate class, all operations require this. All -- definitions must define uniplate, while descend and -- descendM are optional. class Uniplate on where descend f x = generate $ fmap f current where (current, generate) = uniplate x descendM f x = liftM generate $ mapM f current where (current, generate) = uniplate x uniplate :: Uniplate on => on -> (Str on, Str on -> on) descend :: Uniplate on => (on -> on) -> on -> on descendM :: (Uniplate on, Monad m) => (on -> m on) -> on -> m on -- | Children are defined as the top-most items of type to starting at -- the root. All instances must define biplate, while -- descendBi and descendBiM are optional. class Uniplate to => Biplate from to where descendBi f x = generate $ fmap f current where (current, generate) = biplate x descendBiM f x = liftM generate $ mapM f current where (current, generate) = biplate x biplate :: Biplate from to => from -> (Str to, Str to -> from) descendBi :: Biplate from to => (to -> to) -> from -> from descendBiM :: (Biplate from to, Monad m) => (to -> m to) -> from -> m from -- | Get all the children of a node, including itself and all children. -- --
--   universe (Add (Val 1) (Neg (Val 2))) =
--       [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]
--   
-- -- This method is often combined with a list comprehension, for example: -- --
--   vals x = [i | Val i <- universe x]
--   
universe :: Uniplate on => on -> [on] -- | Get the direct children of a node. Usually using universe is -- more appropriate. children :: Uniplate on => on -> [on] -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
--   negLits = transform f
--      where f (Neg (Lit i)) = Lit (negate i)
--            f x = x
--   
transform :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of transform transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewrite r x = all (isNothing . r) (universe (rewrite r x))
--   
-- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct f mplus -- g which performs both rewrites until a fixed point. rewrite :: Uniplate on => (on -> Maybe on) -> on -> on -- | Monadic variant of rewrite rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on -- | Return all the contexts and holes. -- --
--   universe x == map fst (contexts x)
--   all (== x) [b a | (a,b) <- contexts x]
--   
contexts :: Uniplate on => on -> [(on, on -> on)] -- | The one depth version of contexts -- --
--   children x == map fst (holes x)
--   all (== x) [b a | (a,b) <- holes x]
--   
holes :: Uniplate on => on -> [(on, on -> on)] -- | Perform a fold-like computation on each value, technically a -- paramorphism para :: Uniplate on => (on -> [r] -> r) -> on -> r universeBi :: Biplate from to => from -> [to] -- | Return the children of a type. If to == from then it returns -- the original element (in contrast to children) childrenBi :: Biplate from to => from -> [to] transformBi :: Biplate from to => (to -> to) -> from -> from transformBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> from rewriteBiM :: (Monad m, Biplate from to) => (to -> m (Maybe to)) -> from -> m from contextsBi :: Biplate from to => from -> [(to, to -> from)] holesBi :: Biplate from to => from -> [(to, to -> from)] -- | Apply a sequence of transformations in order. This function obeys the -- equivalence: -- --
--   transformBis [[transformer f],[transformer g],...] == transformBi f . transformBi g . ...
--   
-- -- Each item of type [Transformer] is applied in turn, right to -- left. Within each [Transformer], the individual -- Transformer values may be interleaved. -- -- The implementation will attempt to perform fusion, and avoid walking -- any part of the data structure more than necessary. To further improve -- performance, you may wish to partially apply the first argument, which -- will calculate information about the relationship between the -- transformations. transformBis :: Data a => [[Transformer]] -> a -> a data Transformer -- | Wrap up a (a -> a) transformation function, to use with -- transformBis transformer :: Data a => (a -> a) -> Transformer instance (Data a, Data b, Uniplate b) => Biplate a b instance Data a => Uniplate a -- | This module supplies a method for writing Uniplate and -- Biplate instances. This moulde gives the highest performance, -- but requires many instance definitions. The instances can be generated -- using Derive: http://community.haskell.org/~ndm/derive/. -- -- To take an example: -- --
--   data Expr = Var Int | Pos Expr String | Neg Expr | Add Expr Expr
--   data Stmt = Seq [Stmt] | Sel [Expr] | Let String Expr
--   
--   instance Uniplate Expr where
--       uniplate (Var x  ) = plate Var |- x
--       uniplate (Pos x y) = plate Pos |* x |- y
--       uniplate (Neg x  ) = plate Neg |* x
--       uniplate (Add x y) = plate Add |* x |* y
--   
--   instance Biplate Expr Expr where
--       biplate = plateSelf
--   
--   instance Uniplate Stmt where
--       uniplate (Seq x  ) = plate Seq ||* x
--       uniplate (Sel x  ) = plate Sel ||+ x
--       uniplate (Let x y) = plate Let |-  x |- y
--   
--   instance Biplate Stmt Stmt where
--       biplate = plateSelf
--   
--   instance Biplate Stmt Expr where
--       biplate (Seq x  ) = plate Seq ||+ x
--       biplate (Sel x  ) = plate Sel ||* x
--       biplate (Let x y) = plate Let |-  x |* y
--   
-- -- To define instances for abstract data types, such as Map or -- Set from the containers package, use -- plateProject. -- -- This module provides a few monomorphic instances of Uniplate / -- Biplate for common types available in the base library, but -- does not provide any polymorphic instances. Given only monomorphic -- instances it is trivial to ensure that all instances are disjoint, -- making it easier to add your own instances. -- -- When defining polymorphic instances, be carefully to mention all -- potential children. Consider Biplate Int (Int, a) - this -- instance cannot be correct because it will fail to return both -- Int values on (Int,Int). There are some legitimate -- polymorphic instances, such as Biplate a [a] and Biplate -- a a, but take care to avoid overlapping instances. module Data.Generics.Uniplate.Direct -- | The main combinator used to start the chain. -- -- The following rule can be used for optimisation: -- --
--   plate Ctor |- x == plate (Ctor x)
--   
plate :: from -> Type from to -- | Used for Biplate definitions where both types are the same. plateSelf :: to -> Type to to -- | The field to the right may contain the target. (|+) :: Biplate item to => Type (item -> from) to -> item -> Type from to -- | The field to the right does not contain the target. (|-) :: Type (item -> from) to -> item -> Type from to -- | The field to the right is the target. (|*) :: Type (to -> from) to -> to -> Type from to -- | The field to the right is a list of types which may contain the target (||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from to -- | The field to the right is a list of the type of the target (||*) :: Type ([to] -> from) to -> [to] -> Type from to -- | Write an instance in terms of a projection/injection pair. Usually -- used to define instances for abstract containers such as Map: -- --
--   instance Biplate (Map.Map [Char] Int) Char where
--       biplate = plateProject Map.toList Map.fromList
--   
-- -- If the types ensure that no operations will not change the keys we can -- use the fromDistictAscList function to reconstruct the Map: -- --
--   instance Biplate (Map.Map [Char] Int) Int where
--       biplate = plateProject Map.toAscList Map.fromDistinctAscList
--   
plateProject :: Biplate item to => (from -> item) -> (item -> from) -> from -> Type from to instance Biplate (Ratio Integer) Integer instance Biplate (Ratio Integer) (Ratio Integer) instance Uniplate (Ratio Integer) instance Biplate [Char] [Char] instance Biplate [Char] Char instance Uniplate [Char] instance Uniplate () instance Uniplate Float instance Uniplate Double instance Uniplate Integer instance Uniplate Char instance Uniplate Bool instance Uniplate Int -- | RECOMMENDATION: Use Data.Generics.Uniplate.Data instead -- - it usually performs faster (sometimes significantly so) and requires -- no special instance declarations. -- -- This module supplies a method for writing Uniplate / -- Biplate instances. One instance declaration is required for -- each data type you wish to work with. The instances can be generated -- using Derive: http://community.haskell.org/~ndm/derive/. -- -- To take an example: -- --
--   data Expr = Var Int | Neg Expr | Add Expr Expr
--               deriving Typeable
--   
--   instance (Typeable a, Uniplate a) => PlateAll Expr a where
--       plateAll (Var x  ) = plate Var |+ x
--       plateAll (Neg x  ) = plate Neg |+ x
--       plateAll (Add x y) = plate Add |+ x |+ y
--   
module Data.Generics.Uniplate.Typeable -- | This class should be defined for each data type of interest. class PlateAll from to plateAll :: PlateAll from to => from -> Type from to -- | The main combinator used to start the chain. plate :: from -> Type from to -- | The field to the right may contain the target. (|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to -- | The field to the right does not contain the target. This can be -- used as either an optimisation, or more commonly for excluding -- primitives such as Int. (|-) :: Type (item -> from) to -> item -> Type from to -- | Write an instance in terms of a projection/injection pair. Usually -- used to define instances for abstract containers such as Map: -- --
--   instance (Ord a, Typeable a, PlateAll a c, Typeable b, PlateAll b c,
--            Typeable c, PlateAll c c) => PlateAll (Map.Map a b) c where
--       plateAll = plateProject Map.toList Map.fromList
--   
plateProject :: (Typeable item, Typeable to, PlateAll item to) => (from -> item) -> (item -> from) -> from -> Type from to instance (Integral a, PlateAll a to, Typeable a, Typeable to, Uniplate to) => PlateAll (Ratio a) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, PlateAll e to, Typeable e, Typeable to, Uniplate to) => PlateAll (a, b, c, d, e) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, Typeable to, Uniplate to) => PlateAll (a, b, c, d) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, Typeable to, Uniplate to) => PlateAll (a, b, c) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (a, b) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (Either a b) to instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll (Maybe from) to instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll [from] to instance PlateAll () to instance PlateAll Float to instance PlateAll Double to instance PlateAll Integer to instance PlateAll Char to instance PlateAll Bool to instance PlateAll Int to instance PlateAll a a => Uniplate a instance (Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b -- | A zipper is a structure for walking a value and manipulating it in -- constant time. -- -- This module was inspired by the paper: Michael D. Adams. Scrap Your -- Zippers: A Generic Zipper for Heterogeneous Types, Workshop on Generic -- Programming 2010. module Data.Generics.Uniplate.Zipper -- | Zipper structure, whose root type is the first type argument, and -- whose focus type is the second type argument. data Zipper from to -- | Create a zipper, focused on the top-left value. zipper :: Uniplate to => to -> Zipper to to -- | Create a zipper with a different focus type from the outer type. Will -- return Nothing if there are no instances of the focus type -- within the original value. zipperBi :: Biplate from to => from -> Maybe (Zipper from to) -- | From a zipper take the whole structure, including any modifications. fromZipper :: Zipper from to -> from -- | Move one step left from the current position. left :: Zipper from to -> Maybe (Zipper from to) -- | Move one step right from the current position. right :: Zipper from to -> Maybe (Zipper from to) -- | Move one step up from the current position. up :: Zipper from to -> Maybe (Zipper from to) -- | Move one step down from the current position. down :: Uniplate to => Zipper from to -> Maybe (Zipper from to) -- | Retrieve the current focus of the zipper.. hole :: Zipper from to -> to -- | Replace the value currently at the focus of the zipper. replaceHole :: to -> Zipper from to -> Zipper from to instance Eq a => Eq (Diff1 a) instance Eq a => Eq (Zip1 a) instance Eq x => Eq (ZipN x) instance (Eq from, Eq to) => Eq (Zipper from to) -- | DEPRECATED: Use Data.Generics.Uniplate.Operations -- instead. -- -- This is the main Uniplate module, which defines all the essential -- operations in a Haskell 98 compatible manner. -- -- Most functions have an example of a possible use for the function. To -- illustate, I have used the Expr type as below: -- --
--   data Expr = Val Int
--             | Neg Expr
--             | Add Expr Expr
--   
module Data.Generics.UniplateStr -- | The type of replacing all the children of a node -- -- Taking a value, the function should return all the immediate children -- of the same type, and a function to replace them. type UniplateType on = on -> (Str on, Str on -> on) -- | The standard Uniplate class, all operations require this. class Uniplate on uniplate :: Uniplate on => UniplateType on -- | Compatibility method, for direct users of the old list-based -- uniplate function uniplateList :: Uniplate on => on -> ([on], [on] -> on) -- | Get all the children of a node, including itself and all children. -- --
--   universe (Add (Val 1) (Neg (Val 2))) =
--       [Add (Val 1) (Neg (Val 2)), Val 1, Neg (Val 2), Val 2]
--   
-- -- This method is often combined with a list comprehension, for example: -- --
--   vals x = [i | Val i <- universe x]
--   
universe :: Uniplate on => on -> [on] -- | Get the direct children of a node. Usually using universe is -- more appropriate. -- --
--   children = fst . uniplate
--   
children :: Uniplate on => on -> [on] -- | Transform every element in the tree, in a bottom-up manner. -- -- For example, replacing negative literals with literals: -- --
--   negLits = transform f
--      where f (Neg (Lit i)) = Lit (negate i)
--            f x = x
--   
transform :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of transform transformM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Rewrite by applying a rule everywhere you can. Ensures that the rule -- cannot be applied anywhere in the result: -- --
--   propRewrite r x = all (isNothing . r) (universe (rewrite r x))
--   
-- -- Usually transform is more appropriate, but rewrite can -- give better compositionality. Given two single transformations -- f and g, you can construct f mplus g -- which performs both rewrites until a fixed point. rewrite :: Uniplate on => (on -> Maybe on) -> on -> on -- | Monadic variant of rewrite rewriteM :: (Monad m, Uniplate on) => (on -> m (Maybe on)) -> on -> m on -- | Perform a transformation on all the immediate children, then combine -- them back. This operation allows additional information to be passed -- downwards, and can be used to provide a top-down transformation. descend :: Uniplate on => (on -> on) -> on -> on -- | Monadic variant of descend descendM :: (Monad m, Uniplate on) => (on -> m on) -> on -> m on -- | Return all the contexts and holes. -- --
--   propUniverse x = universe x == map fst (contexts x)
--   propId x = all (== x) [b a | (a,b) <- contexts x]
--   
contexts :: Uniplate on => on -> [(on, on -> on)] -- | The one depth version of contexts -- --
--   propChildren x = children x == map fst (holes x)
--   propId x = all (== x) [b a | (a,b) <- holes x]
--   
holes :: Uniplate on => on -> [(on, on -> on)] -- | Perform a fold-like computation on each value, technically a -- paramorphism para :: Uniplate on => (on -> [r] -> r) -> on -> r -- | DEPRECATED: Use Data.Generics.Uniplate.Operations -- instead. -- -- This module retained Haskell 98 compatability, but users who are happy -- with multi-parameter type classes should look towards -- Data.Generics.Biplate. -- -- The only function missing from Data.Generics.Uniplate is -- fold, as it can be constructed from children and has -- little meaning in a multi-typed setting. -- -- All operations, apart from childrenOn, descendOn and -- holesOn should perform identically to their non On -- counterparts. module Data.Generics.UniplateStrOn -- | Return all the top most children of type to within -- from. -- -- If from == to then this function should return the root as -- the single child. type BiplateType from to = from -> (Str to, Str to -> from) universeOn :: Uniplate to => BiplateType from to -> from -> [to] -- | Return the children of a type. If to == from then it returns -- the original element (in contrast to children) childrenOn :: Uniplate to => BiplateType from to -> from -> [to] transformOn :: Uniplate to => BiplateType from to -> (to -> to) -> from -> from transformOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m to) -> from -> m from rewriteOn :: Uniplate to => BiplateType from to -> (to -> Maybe to) -> from -> from rewriteOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m (Maybe to)) -> from -> m from descendOn :: Uniplate to => BiplateType from to -> (to -> to) -> from -> from descendOnM :: (Monad m, Uniplate to) => BiplateType from to -> (to -> m to) -> from -> m from holesOn :: Uniplate to => BiplateType from to -> from -> [(to, to -> from)] contextsOn :: Uniplate to => BiplateType from to -> from -> [(to, to -> from)] -- | Used for defining instances UniplateFoo a => UniplateFoo -- [a] uniplateOnList :: BiplateType a b -> BiplateType [a] b -- | DEPRECATED: Use Data.Generics.Uniplate.Operations -- instead. -- -- Requires multi-parameter type classes, so is no longer Haskell 98. -- These operations are easier to use and construct than the equivalent -- Data.Generics.UniplateStrOn methods, but perform the same -- operation. -- -- It is recommended that instead of importing this module, you import -- one of the following modules, to construct instances: -- -- module Data.Generics.Biplate -- | Children are defined as the top-most items of type to starting at -- the root. class Uniplate to => Biplate from to biplate :: Biplate from to => BiplateType from to -- | Compatibility method, for direct users of the biplate function biplateList :: Biplate from to => from -> ([to], [to] -> from) universeBi :: Biplate from to => from -> [to] childrenBi :: Biplate from to => from -> [to] transformBi :: Biplate from to => (to -> to) -> from -> from transformBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from rewriteBi :: Biplate from to => (to -> Maybe to) -> from -> from rewriteBiM :: (Monad m, Biplate from to) => (to -> m (Maybe to)) -> from -> m from descendBi :: Biplate from to => (to -> to) -> from -> from descendBiM :: (Monad m, Biplate from to) => (to -> m to) -> from -> m from contextsBi :: Biplate from to => from -> [(to, to -> from)] holesBi :: Biplate from to => from -> [(to, to -> from)] -- | DEPRECATED: Use Data.Generics.Uniplate.Direct instead. -- -- This module supplies a method for writing Biplate instances -- more easily. This module requires fewest extensions, highest -- performance, and most instance definitions. -- -- To take an example: -- --
--   data Expr = Var Int | Pos Expr String | Neg Expr | Add Expr Expr
--   data Stmt = Seq [Stmt] | Sel [Expr] | Let String Expr
--   
--   instance Uniplate Expr where
--       uniplate (Var x  ) = plate Var |- x
--       uniplate (Pos x y) = plate Pos |* x |- y
--       uniplate (Neg x  ) = plate Neg |* x
--       uniplate (Add x y) = plate Add |* x |* y
--   
--   instance Biplate Expr Expr where
--       biplate = plateSelf
--   
--   instance Uniplate Stmt where
--       uniplate (Seq x  ) = plate Seq ||* x
--       uniplate (Sel x  ) = plate Sel ||+ x
--       uniplate (Let x y) = plate Let |-  x |- y
--   
--   instance Biplate Stmt Stmt where
--       biplate = plateSelf
--   
--   instance Biplate Stmt Expr where
--       biplate (Seq x  ) = plate Seq ||+ x
--       biplate (Sel x  ) = plate Sel ||* x
--       biplate (Let x y) = plate Let |-  x |* y
--   
module Data.Generics.PlateDirect -- | The main combinator used to start the chain. -- -- The following rule can be used for optimisation: -- --
--   plate Ctor |- x == plate (Ctor x)
--   
plate :: from -> Type from to -- | Used for PlayAll definitions where both types are the same. plateSelf :: to -> Type to to -- | The field to the right may contain the target. (|+) :: Biplate item to => Type (item -> from) to -> item -> Type from to -- | The field to the right does not contain the target. (|-) :: Type (item -> from) to -> item -> Type from to -- | The field to the right is the target. (|*) :: Type (to -> from) to -> to -> Type from to -- | The field to the right is a list of types which may contain the target (||+) :: Biplate item to => Type ([item] -> from) to -> [item] -> Type from to -- | The field to the right is a list of the type of the target (||*) :: Type ([to] -> from) to -> [to] -> Type from to -- | DEPRECATED: Use Data.Generics.Uniplate.Typeable instead. -- -- This module supplies a method for writing Biplate instances -- more easily. -- -- To take an example: -- --
--   data Expr = Var Int | Neg Expr | Add Expr Expr
--   
--   instance Typeable Expr where ...
--   
--   instance (Typeable a, Uniplate a) => PlateAll Expr a where
--     plateAll (Var x  ) = plate Var |- x
--     plateAll (Neg x  ) = plate Neg |+ x
--     plateAll (Add x y) = plate Add |+ x |+ y
--   
--   instance Uniplate Expr where
--     uniplate = uniplateAll
--   
module Data.Generics.PlateTypeable -- | This class represents going from the container type to the target. -- -- This class should only be constructed with plate, |+ and -- |- class PlateAll from to plateAll :: PlateAll from to => from -> Type from to -- | This function is used to write a Uniplate instance from a -- PlateAll one uniplateAll :: PlateAll a b => a -> (Str b, Str b -> a) -- | The main combinator used to start the chain. -- -- The following rule can be used for optimisation: -- --
--   plate Ctor |- x == plate (Ctor x)
--   
plate :: from -> Type from to -- | the field to the right may contain the target. (|+) :: (Typeable item, Typeable to, PlateAll item to) => Type (item -> from) to -> item -> Type from to -- | The field to the right does not contain the target. This can be -- used as either an optimisation, or more commonly for excluding -- primitives such as Int. (|-) :: Type (item -> from) to -> item -> Type from to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, PlateAll e to, Typeable e, Typeable to, Uniplate to) => PlateAll (a, b, c, d, e) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, PlateAll d to, Typeable d, Typeable to, Uniplate to) => PlateAll (a, b, c, d) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, PlateAll c to, Typeable c, Typeable to, Uniplate to) => PlateAll (a, b, c) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (a, b) to instance (PlateAll a to, Typeable a, PlateAll b to, Typeable b, Typeable to, Uniplate to) => PlateAll (Either a b) to instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll (Maybe from) to instance (PlateAll from to, Typeable from, Typeable to, Uniplate to) => PlateAll [from] to instance Uniplate () instance PlateAll () to instance Uniplate Float instance PlateAll Float to instance Uniplate Double instance PlateAll Double to instance Uniplate Integer instance PlateAll Integer to instance Uniplate Char instance PlateAll Char to instance Uniplate Bool instance PlateAll Bool to instance Uniplate Int instance PlateAll Int to instance (Typeable a, Typeable b, Uniplate b, PlateAll a b) => Biplate a b -- | DEPRECATED: Use Data.Generics.Uniplate.Data instead. -- -- This module exports Biplate instances for everything with -- Data defined. Using GHC the Data instances can be -- constructed with deriving Data. module Data.Generics.PlateData instance (Data a, Data b, Uniplate b, Typeable a, Typeable b) => Biplate a b instance (Data a, Typeable a) => Uniplate a