PEZ is a generic zipper library. It uses lenses from the fclabels package to
reference a "location" to move to in the zipper. The zipper is restricted to
types in the Typeable
class, allowing the user to "move up" through complex
data structures such as mutually-recursive types, where the compiler could not
otherwise type-check the program.
.
Both the Typeable class and fclabels lenses can be derived in GHC, making it
easy for the programmer to use a zipper with a minimum of boilerplate.
- data Zipper a b
- zipper :: a -> Zipper a a
- close :: Zipper a b -> Maybe a
- class Exception (ThrownBy mot) => Motion mot where
- newtype Up c b = Up {}
- data UpCasting c b = UpCasting
- data To a b
- to :: (Typeable a, Typeable b) => (a :~> b) -> To a b
- data ZipperException
- data UpErrors
- data ToErrors = LensGetterFailed
- moveWhile :: (Failure (ThrownBy mot) m, Motion mot, Typeable c) => (c -> Bool) -> mot c c -> Zipper a c -> m (Zipper a c)
- moveUntil :: (Failure (ThrownBy mot) m, Motion mot, Typeable c) => (c -> Bool) -> mot c c -> Zipper a c -> m (Zipper a c)
- moveFloor :: (Motion m, Typeable a, Typeable b) => m b b -> Zipper a b -> Zipper a b
- focus :: forall (~>) a b. Arrow ~> => Lens ~> (Zipper a b) b
- viewf :: Zipper a b -> b
- setf :: b -> Zipper a b -> Zipper a b
- modf :: (b -> b) -> Zipper a b -> Zipper a b
- atTop :: Zipper a b -> Bool
- level :: Zipper a b -> Int
- class Motion m => LevelDelta m where
- save :: Zipper a b -> To a b
- closeSaving :: Zipper a b -> (To a b, Maybe a)
- restore :: (Typeable a, Typeable b, Failure ToErrors m) => To a b -> a -> m (Zipper a b)
- flatten :: (Typeable a, Typeable b) => To a b -> a :~> b
- type Zipper1 a = Zipper a a
- class Typeable a where
- mkLabels :: [Name] -> Q [Dec]
- type :~> f a = MaybeLens f a
- class Monad f => Failure e f where
- failure :: e -> f v
- class (Typeable e, Show e) => Exception e where
- toException :: e -> SomeException
- fromException :: SomeException -> Maybe e
Usage
First import the library, which brings in the Typeable and fclabels modules.
You will also want to enable a few extensions:
TemplateHaskell
, DeriveDataTypeable
, TypeOperators
module Main where import Data.Label.Zipper
Create a datatype, deriving an instance of the Typeable class, and generate a lens using Template Haskell functionality from fclabels:
data Tree a = Node { _leftNode :: Tree a , _val :: a , _rightNode :: Tree a } | Nil deriving (Typeable,Show) $(mkLabels [''Tree])
Now we can go crazy using Tree in a Zipper
:
treeBCD = Node (Node Nil 'b' Nil) 'c' (Node Nil 'd' Nil) descendLeft :: (Typeable a)=> Zipper1 (Tree a) -> Zipper1 (Tree a) descendLeft = moveFloor (to leftNode) -- stops at Nil constructor insertLeftmost :: (Typeable a)=> a -> Tree a -> Maybe (Tree a) insertLeftmost a = close . setf newNode . descendLeft . zipper where newNode = Node Nil a Nil treeABCD = insertLeftmost 'a' treeBCD
Because of the flexibility of fclabels, this zipper library can be used to express moving about in reversible computations simply by defining such a lens, for instance:
stringRep :: (Show b, Read b) => b :-> String stringRep = lens show (const . read)
Another exciting possibility are zippers that can perform validation,
refusing to close
if a field is rejected.
Zipper functionality
Encapsulates a data type a
at a focus b
, supporting various Motion
operations
A note on failure in zipper operations:
Most operations on a Zipper
return a result in a Failure
class
monad, throwing various types of failures. Here is a list of failure
scenarios:
- a
move
Up arrives at a type that could not be cast to the type expected - a
move (Up 1)
when alreadyatTop
, i.e. we cannot ascend anymore - a
move
to a label (e.g.foo :: FooBar :~> FooBar
) causes a failure in the getter function of the lens, usually because thefocus
was the wrong constructor for the lens - a
move (Up n)
causes the setter of the lens we used to arrive at the current focus to fail on the value of the current focus. This is not something that happens for normal lenses, but is desirable for structures that enforce extra-type-system constraints. - a
close
cannot re-build the structure because some setter failed, as above. Again, this does not occur for TH'generated lenses.
See the failure package for details.
Creating and closing Zippers
close :: Zipper a b -> Maybe aSource
re-assembles the data structure from the top level, returning Nothing
if
the structure cannot be re-assembled.
Note: For standard lenses produced with mkLabels
this will never fail.
However setters defined by hand with lens
can be used to enforce arbitrary
constraints on a data structure, e.g. that a type Odd Int
can only hold an
odd integer. This function returns Nothing
in such cases, which
corresponds to the LensSetterFailed
constructor of UpErrors
Moving around
class Exception (ThrownBy mot) => Motion mot whereSource
Types of the Motion class describe "paths" up or down (so to speak)
through a datatype. The exceptions thrown by each motion are enumerated in
the associated type ThrownBy mot
. The Motion
type that will return the
focus to the last location after doing a 'moveSaving is given by Returning mot
.
move :: (Typeable b, Typeable c, Failure (ThrownBy mot) m) => mot b c -> Zipper a b -> m (Zipper a c)Source
Move to a new location in the zipper, either returning the new zipper,
or throwing err
in some Failure
class type (from the failure pkg.)
The return type can be treated as Maybe
for simple exception handling
or one can even use something like control-monad-exception to get
powerful typed, checked exceptions.
moveSaving :: (Typeable b, Typeable c, Failure (ThrownBy mot) m) => mot b c -> Zipper a b -> m (Returning mot c b, Zipper a c)Source
like move
but saves the Motion
that will return us back to the
location we started from in the passed zipper.
a Motion
upwards in the data type. e.g. move (Up 2)
would move up to
the grandparent level, as long as the type of the focus after moving is
b
. Inline type signatures are often helpful to avoid ambiguity, e.g.
(Up 2 :: Up Char (Tree Char))
read as "up two levels, from a focus of
type Char
to Tree Char
".
A Motion
type describing an incremental path "down" through a data
structure. Use to
to move to a location specified by a fclabels lens.
Use restore
to return to a previously-visited location in a zipper, with
previous history intact, so:
(\(l,ma)-> move l <$> ma) (closeSaving z) == Just z
Use flatten
to turn this into a standard fclabels lens, flattening the
incremental move steps.
Throws errors of type ToErrors
:
to :: (Typeable a, Typeable b) => (a :~> b) -> To a bSource
use a fclabels label to define a Motion "down" into a data type.
Error types
Every defined Motion
has an associated error type, thrown in a
Failure
class monad (see failure). These types are also part of a
small Exception
hierarchy.
data ZipperException Source
The root of the exception hierarchy for Zipper move
operations:
Repeating movements
moveWhile :: (Failure (ThrownBy mot) m, Motion mot, Typeable c) => (c -> Bool) -> mot c c -> Zipper a c -> m (Zipper a c)Source
Apply a motion each time the focus matches the predicate, raising an error
in m
otherwise
moveUntil :: (Failure (ThrownBy mot) m, Motion mot, Typeable c) => (c -> Bool) -> mot c c -> Zipper a c -> m (Zipper a c)Source
Apply a motion zero or more times until the focus matches the predicate
moveUntil p = moveWhile (not . p)
moveFloor :: (Motion m, Typeable a, Typeable b) => m b b -> Zipper a b -> Zipper a bSource
Apply the given Motion to a zipper until the Motion fails, returning the
last location visited. For instance moveFloor (to left) z
might return
the left-most node of a zipper
ed tree z
.
moveFloor m z = maybe z (moveFloor m) $ move m z
The zipper focus
a fclabels lens for setting, getting, and modifying the zipper's
focus. Note: a zipper may fail to close
if the lens used to reach the
current focus performed some validation.
Querying Zippers and Motions
class Motion m => LevelDelta m whereSource
Motion types which alter a Zipper by a knowable integer quantity. Concretly, the following should hold:
level (move m z) == level z + delta m
For motions upwards this returns a negative value.
Saving and recalling positions in a Zipper
closeSaving :: Zipper a b -> (To a b, Maybe a)Source
Close the zipper, returning the saved path back down to the zipper's
focus. See close
restore :: (Typeable a, Typeable b, Failure ToErrors m) => To a b -> a -> m (Zipper a b)Source
Enter a zipper using the specified Motion
.
Saving and restoring lets us for example: find some location within our
structure using a Zipper
, save the location, fmap
over the entire structure,
and then return to where we were safely, even if the "shape" of our
structure has changed.
restore s = move s . zipper
Convenience operators, types, and exports
type Zipper1 a = Zipper a aSource
a simple type synonym for a Zipper
where the type at the focus is the
same as the type of the outer (unzippered) type. Cleans up type signatures
for simple recursive types:
Re-exports
These re-exported functions should be sufficient for the most common - zipper functionality
class Typeable a where
The class Typeable
allows a concrete representation of a type to
be calculated.
Derive lenses including type signatures for all the record selectors in a datatype. The types will be polymorphic and can be used in an arbitrary context.
type :~> f a = MaybeLens f a
Lens type for situations in which the accessor functions can fail. This is useful, for example, when accessing fields in datatypes with multiple constructors.
class (Typeable e, Show e) => Exception e where
Any type that you wish to throw or catch as an exception must be an
instance of the Exception
class. The simplest case is a new exception
type directly below the root:
data MyException = ThisException | ThatException deriving (Show, Typeable) instance Exception MyException
The default method definitions in the Exception
class do what we need
in this case. You can now throw and catch ThisException
and
ThatException
as exceptions:
*Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) Caught ThisException
In more complicated examples, you may wish to define a whole hierarchy of exceptions:
--------------------------------------------------------------------- -- Make the root exception type for all the exceptions in a compiler data SomeCompilerException = forall e . Exception e => SomeCompilerException e deriving Typeable instance Show SomeCompilerException where show (SomeCompilerException e) = show e instance Exception SomeCompilerException compilerExceptionToException :: Exception e => e -> SomeException compilerExceptionToException = toException . SomeCompilerException compilerExceptionFromException :: Exception e => SomeException -> Maybe e compilerExceptionFromException x = do SomeCompilerException a <- fromException x cast a --------------------------------------------------------------------- -- Make a subhierarchy for exceptions in the frontend of the compiler data SomeFrontendException = forall e . Exception e => SomeFrontendException e deriving Typeable instance Show SomeFrontendException where show (SomeFrontendException e) = show e instance Exception SomeFrontendException where toException = compilerExceptionToException fromException = compilerExceptionFromException frontendExceptionToException :: Exception e => e -> SomeException frontendExceptionToException = toException . SomeFrontendException frontendExceptionFromException :: Exception e => SomeException -> Maybe e frontendExceptionFromException x = do SomeFrontendException a <- fromException x cast a --------------------------------------------------------------------- -- Make an exception type for a particular frontend compiler exception data MismatchedParentheses = MismatchedParentheses deriving (Typeable, Show) instance Exception MismatchedParentheses where toException = frontendExceptionToException fromException = frontendExceptionFromException
We can now catch a MismatchedParentheses
exception as
MismatchedParentheses
, SomeFrontendException
or
SomeCompilerException
, but not other types, e.g. IOException
:
*Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) Caught MismatchedParentheses *Main> throw MismatchedParenthesescatch
e -> putStrLn ("Caught " ++ show (e :: IOException)) *** Exception: MismatchedParentheses
toException :: e -> SomeException
fromException :: SomeException -> Maybe e