Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
Synopsis
- newtype Hide a = Hide {
- fromHide :: a
- data Trigger a = Trigger {
- trigger :: Bool
- fromTrigger :: a
- data Invariant a = Invariant {
- invariant :: a -> a
- fromInvariant :: a
- data Map k v
- fromMap :: Map k v -> Map k v
- toMap :: Ord k => Map k v -> Map k v
- data Set k
- fromSet :: Set k -> Set k
- toSet :: Ord k => Set k -> Set k
- data IntMap v
- fromIntMap :: IntMap v -> IntMap v
- toIntMap :: IntMap v -> IntMap v
- data IntSet
- fromIntSet :: IntSet -> IntSet
- toIntSet :: IntSet -> IntSet
Documentation
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.
Instances
Functor Hide Source # | |
Eq a => Eq (Hide a) Source # | |
Typeable a => Data (Hide a) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Hide a -> c (Hide a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Hide a) # toConstr :: Hide a -> Constr # dataTypeOf :: Hide a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Hide a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Hide a)) # gmapT :: (forall b. Data b => b -> b) -> Hide a -> Hide a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Hide a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Hide a -> r # gmapQ :: (forall d. Data d => d -> u) -> Hide a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Hide a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Hide a -> m (Hide a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Hide a -> m (Hide a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Hide a -> m (Hide a) # | |
Ord a => Ord (Hide a) Source # | |
Read a => Read (Hide a) Source # | |
Show a => Show (Hide a) Source # | |
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.
Trigger | |
|
Instances
Functor Trigger Source # | |
Eq a => Eq (Trigger a) Source # | |
(Data a, Typeable a) => Data (Trigger a) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Trigger a -> c (Trigger a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Trigger a) # toConstr :: Trigger a -> Constr # dataTypeOf :: Trigger a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Trigger a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Trigger a)) # gmapT :: (forall b. Data b => b -> b) -> Trigger a -> Trigger a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Trigger a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Trigger a -> r # gmapQ :: (forall d. Data d => d -> u) -> Trigger a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Trigger a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Trigger a -> m (Trigger a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Trigger a -> m (Trigger a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Trigger a -> m (Trigger a) # | |
Ord a => Ord (Trigger a) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances | |
Read a => Read (Trigger a) Source # | |
Show a => Show (Trigger a) Source # | |
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.
Invariant | |
|
Instances
(Data a, Typeable a) => Data (Invariant a) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Invariant a -> c (Invariant a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Invariant a) # toConstr :: Invariant a -> Constr # dataTypeOf :: Invariant a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Invariant a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Invariant a)) # gmapT :: (forall b. Data b => b -> b) -> Invariant a -> Invariant a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Invariant a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Invariant a -> r # gmapQ :: (forall d. Data d => d -> u) -> Invariant a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Invariant a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Invariant a -> m (Invariant a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Invariant a -> m (Invariant a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Invariant a -> m (Invariant a) # | |
Show a => Show (Invariant a) Source # | |
Invariant preserving version of Map
from the containers
packages, suitable for use with Uniplate
.
Use toMap
to construct values, and fromMap
to deconstruct values.
Instances
(Eq k, Eq v) => Eq (Map k v) Source # | |
(Data k, Data v) => Data (Map k v) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map k v -> c (Map k v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Map k v) # toConstr :: Map k v -> Constr # dataTypeOf :: Map k v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Map k v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k v)) # gmapT :: (forall b. Data b => b -> b) -> Map k v -> Map k v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map k v -> r # gmapQ :: (forall d. Data d => d -> u) -> Map k v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Map k v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map k v -> m (Map k v) # | |
(Ord k, Ord v) => Ord (Map k v) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances | |
(Show k, Show v) => Show (Map k v) Source # | |
Invariant preserving version of Set
from the containers
packages, suitable for use with Uniplate
.
Use toSet
to construct values, and fromSet
to deconstruct values.
Instances
Eq k => Eq (Set k) Source # | |
Data k => Data (Set k) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Set k -> c (Set k) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Set k) # dataTypeOf :: Set k -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Set k)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Set k)) # gmapT :: (forall b. Data b => b -> b) -> Set k -> Set k # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Set k -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Set k -> r # gmapQ :: (forall d. Data d => d -> u) -> Set k -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Set k -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Set k -> m (Set k) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Set k -> m (Set k) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Set k -> m (Set k) # | |
Ord k => Ord (Set k) Source # | |
Show k => Show (Set k) Source # | |
Invariant preserving version of IntMap
from the containers
packages, suitable for use with Uniplate
.
Use toIntMap
to construct values, and fromIntMap
to deconstruct values.
Instances
Eq v => Eq (IntMap v) Source # | |
Data v => Data (IntMap v) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntMap v -> c (IntMap v) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (IntMap v) # toConstr :: IntMap v -> Constr # dataTypeOf :: IntMap v -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (IntMap v)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (IntMap v)) # gmapT :: (forall b. Data b => b -> b) -> IntMap v -> IntMap v # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntMap v -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntMap v -> r # gmapQ :: (forall d. Data d => d -> u) -> IntMap v -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntMap v -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntMap v -> m (IntMap v) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap v -> m (IntMap v) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntMap v -> m (IntMap v) # | |
Ord v => Ord (IntMap v) Source # | |
Defined in Data.Generics.Uniplate.Data.Instances | |
Show v => Show (IntMap v) Source # | |
Invariant preserving version of IntSet
from the containers
packages, suitable for use with Uniplate
.
Use toIntSet
to construct values, and fromIntSet
to deconstruct values.
Instances
Eq IntSet Source # | |
Data IntSet Source # | |
Defined in Data.Generics.Uniplate.Data.Instances gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IntSet -> c IntSet # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IntSet # toConstr :: IntSet -> Constr # dataTypeOf :: IntSet -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c IntSet) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IntSet) # gmapT :: (forall b. Data b => b -> b) -> IntSet -> IntSet # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IntSet -> r # gmapQ :: (forall d. Data d => d -> u) -> IntSet -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> IntSet -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IntSet -> m IntSet # | |
Ord IntSet Source # | |
Show IntSet Source # | |