Copyright | (c) Varun Gandhi 2018 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | theindigamer15@gmail.com |
Stability | experimental |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
The Edit
type for working with rewriting systems, with associated
operations.
To see a high-level overview of some use cases and a detailed example, check the Data.Edit.Tutorial module.
Usage notes:
- You probably want to import this module qualified to avoid a name
collision with Data.Maybe's
fromMaybe
. - We re-export the composition operators from Control.Monad for convenience.
- data Edit a
- fromEdit :: Edit a -> a
- isClean :: Edit a -> Bool
- isDirty :: Edit a -> Bool
- extract :: Edit a -> a
- duplicate :: Edit a -> Edit (Edit a)
- extend :: (Edit a -> b) -> Edit a -> Edit b
- toMaybe :: Edit a -> Maybe a
- fromMaybe :: a -> Maybe a -> Edit a
- edits :: (a -> Maybe a) -> a -> Edit a
- toEither :: Edit a -> Either a a
- fromEither :: Either a a -> Edit a
- polish :: (a -> Edit a) -> a -> a
- iterations :: (a -> Edit a) -> a -> [a]
- partitionEdits :: [Edit a] -> ([a], [a])
- clean :: Edit a -> Edit a
- dirty :: Edit a -> Edit a
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
Edit type and basic operations
The Edit
type encapsulates rewriting.
Since Edit
is also a monad, it allows you to easily "bubble up" information
on whether changes were made when working with nested data structures. This
is helpful when you want to save the fact that you've reaching a fixed point
while rewriting, instead of, say re-computing it after the fact using an Eq
instance on the underlying data-type.
For example,
>>>
halveEvens x = if x `mod` 2 == 0 then (Dirty $ x `div` 2) else (Clean x)
>>>
traverse halveEvens [1, 2, 3]
Dirty [1,1,3]>>>
traverse halveEvens [1, 3, 5]
Clean [1,3,5]
To support this behaviour, the Applicative
and Monad
instances have
"polluting" semantics:
pure
=Clean
=return
.- The result of
<*>
isClean
if and only if both the arguments areClean
. - If you bind a
Clean
value, you may get anything depending on the function involved. However, if you bind aDirty
value, you will definitely get aDirty
value back.
If you're familiar with the Writer monad, Edit
is equivalent to
a Writer monad where w
is isomorphic to Bool
with (<>) = (||)
.
If you like comonads, you can use the comonad_instance
package flag to,
erm, get a legit
Comonad
instance, instead of just having the extract
, duplicate
and extend
functions.
Monad Edit Source # | |
Functor Edit Source # | |
Applicative Edit Source # | |
Foldable Edit Source # | |
Traversable Edit Source # | |
Eq1 Edit Source # | |
Read1 Edit Source # | |
Show1 Edit Source # | |
MonadZip Edit Source # | |
Eq a => Eq (Edit a) Source # | |
Data a => Data (Edit a) Source # | |
Read a => Read (Edit a) Source # | |
Show a => Show (Edit a) Source # | |
Generic (Edit a) Source # | |
Semigroup a => Semigroup (Edit a) Source # | |
(Semigroup a, Monoid a) => Monoid (Edit a) Source # | |
NFData a => NFData (Edit a) Source # | |
type Rep (Edit a) Source # | |
duplicate :: Edit a -> Edit (Edit a) Source #
Wraps the value according to its current status. Like father, like son.
extend :: (Edit a -> b) -> Edit a -> Edit b Source #
Keep track of changes while utilizing an extraction map.
extend f = fmap f . duplicate
Conversions to and from base types
fromMaybe :: a -> Maybe a -> Edit a Source #
Takes a clean value and a possibly dirty value and makes an Edit
.
>>>
fromMaybe "Hi" Nothing
Clean "Hi">>>
defaultValue = 1000
>>>
correctedValue = Just 1024
>>>
fromMaybe defaultValue correctedValue
Dirty 1024
edits :: (a -> Maybe a) -> a -> Edit a Source #
Takes a function that may dirty a value, and returns another which saves the default value if no modification is done.
f `edits` x == fromMaybe x (f x)
fromEither :: Either a a -> Edit a Source #
Finding a fixed point
polish :: (a -> Edit a) -> a -> a Source #
Keep editing till the result is Clean
(find the fixed point).
>>>
g x = if x >= 10 then Clean x else Dirty (x + 2)
>>>
polish g 3
11
Conceptually,
polish f x = last $ iterations f x
iterations :: (a -> Edit a) -> a -> [a] Source #
Keep editing till the result is Clean
, recording iterations.
Similar to polish
but gets the entire list of arguments tested instead of
just the final result. The result is guaranteed to be non-empty because
the first element will always be included. If the list is finite, the last
element gives a Clean
result.
>>>
g x = if x >= 10 then Clean x else Dirty (x + 2)
>>>
iterations g 3
[3,5,7,9,11]
This can be helpful in debugging your transformation function. For example,
[ (before, after) | let xs = iterations f start , (before, after) <- zip xs (tail xs) , sanityCheck before && not (sanityCheck after)) ]
Operations with lists
partitionEdits :: [Edit a] -> ([a], [a]) Source #