uniplate-1.6.10: Help writing simple, concise and fast generic operations.

Safe HaskellSafe-Inferred

Data.Generics.Uniplate.Data.Instances

Description

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

Documentation

newtype Hide a Source

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.

Constructors

Hide 

Fields

fromHide :: a
 

Instances

Functor Hide 
Typeable1 Hide 
Eq a => Eq (Hide a) 
(Typeable (Hide a), Typeable a) => Data (Hide a) 
(Eq (Hide a), Ord a) => Ord (Hide a) 
Read a => Read (Hide a) 
Show a => Show (Hide a) 

data Trigger 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.

Constructors

Trigger 

Fields

trigger :: Bool
 
fromTrigger :: a
 

Instances

Functor Trigger 
Typeable1 Trigger 
Eq a => Eq (Trigger a) 
(Typeable (Trigger a), Data a, Typeable a) => Data (Trigger a) 
(Eq (Trigger a), Ord a) => Ord (Trigger a) 
Read a => Read (Trigger a) 
Show a => Show (Trigger a) 

data Invariant 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.

Constructors

Invariant 

Fields

invariant :: a -> a
 
fromInvariant :: a
 

data Map k v 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

Typeable2 Map 
(Eq k, Eq v) => Eq (Map k v) 
(Typeable (Map k v), Data k, Data v) => Data (Map k v) 
(Eq (Map k v), Ord k, Ord v) => Ord (Map k v) 
(Show k, Show v) => Show (Map k v) 

fromMap :: Map k v -> Map k vSource

Deconstruct a value of type Map.

toMap :: Ord k => Map k v -> Map k vSource

Construct a value of type Map.

data Set k 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

Typeable1 Set 
Eq k => Eq (Set k) 
(Typeable (Set k), Data k) => Data (Set k) 
(Eq (Set k), Ord k) => Ord (Set k) 
Show k => Show (Set k) 

fromSet :: Set k -> Set kSource

Deconstruct a value of type Set.

toSet :: Ord k => Set k -> Set kSource

Construct a value of type Set.

data IntMap v 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

Typeable1 IntMap 
Eq v => Eq (IntMap v) 
(Typeable (IntMap v), Data v) => Data (IntMap v) 
(Eq (IntMap v), Ord v) => Ord (IntMap v) 
Show v => Show (IntMap v) 

fromIntMap :: IntMap v -> IntMap vSource

Deconstruct a value of type IntMap.

toIntMap :: IntMap v -> IntMap vSource

Construct a value of type IntMap.

data IntSet 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.

fromIntSet :: IntSet -> IntSetSource

Deconstruct a value of type IntSet.

toIntSet :: IntSet -> IntSetSource

Construct a value of type IntSet.