edit-1.0.0.0: A monad for rewriting things.

Copyright(c) Varun Gandhi 2018
LicenseBSD-style (see the file LICENSE)
Maintainertheindigamer15@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Data.Edit

Contents

Description

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:

  1. You probably want to import this module qualified to avoid a name collision with Data.Maybe's fromMaybe.
  2. We re-export the composition operators from Control.Monad for convenience.
Synopsis

Edit type and basic operations

data Edit a Source #

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:

  1. pure = Clean = return.
  2. The result of <*> is Clean if and only if both the arguments are Clean.
  3. If you bind a Clean value, you may get anything depending on the function involved. However, if you bind a Dirty value, you will definitely get a Dirty value back.

If you're familiar with the Writer monad, Edit is isomorphic to Writer Any (Any is Bool with (<>) = (||)).

Constructors

Dirty a

A value that has been modified.

Clean a

A value that has not been modified.

Instances
Monad Edit Source # 
Instance details

Defined in Data.Edit

Methods

(>>=) :: Edit a -> (a -> Edit b) -> Edit b #

(>>) :: Edit a -> Edit b -> Edit b #

return :: a -> Edit a #

fail :: String -> Edit a #

Functor Edit Source # 
Instance details

Defined in Data.Edit

Methods

fmap :: (a -> b) -> Edit a -> Edit b #

(<$) :: a -> Edit b -> Edit a #

Applicative Edit Source # 
Instance details

Defined in Data.Edit

Methods

pure :: a -> Edit a #

(<*>) :: Edit (a -> b) -> Edit a -> Edit b #

liftA2 :: (a -> b -> c) -> Edit a -> Edit b -> Edit c #

(*>) :: Edit a -> Edit b -> Edit b #

(<*) :: Edit a -> Edit b -> Edit a #

Foldable Edit Source # 
Instance details

Defined in Data.Edit

Methods

fold :: Monoid m => Edit m -> m #

foldMap :: Monoid m => (a -> m) -> Edit a -> m #

foldr :: (a -> b -> b) -> b -> Edit a -> b #

foldr' :: (a -> b -> b) -> b -> Edit a -> b #

foldl :: (b -> a -> b) -> b -> Edit a -> b #

foldl' :: (b -> a -> b) -> b -> Edit a -> b #

foldr1 :: (a -> a -> a) -> Edit a -> a #

foldl1 :: (a -> a -> a) -> Edit a -> a #

toList :: Edit a -> [a] #

null :: Edit a -> Bool #

length :: Edit a -> Int #

elem :: Eq a => a -> Edit a -> Bool #

maximum :: Ord a => Edit a -> a #

minimum :: Ord a => Edit a -> a #

sum :: Num a => Edit a -> a #

product :: Num a => Edit a -> a #

Traversable Edit Source # 
Instance details

Defined in Data.Edit

Methods

traverse :: Applicative f => (a -> f b) -> Edit a -> f (Edit b) #

sequenceA :: Applicative f => Edit (f a) -> f (Edit a) #

mapM :: Monad m => (a -> m b) -> Edit a -> m (Edit b) #

sequence :: Monad m => Edit (m a) -> m (Edit a) #

Arbitrary1 Edit Source # 
Instance details

Defined in Data.Edit

Methods

liftArbitrary :: Gen a -> Gen (Edit a) #

liftShrink :: (a -> [a]) -> Edit a -> [Edit a] #

Eq1 Edit Source # 
Instance details

Defined in Data.Edit

Methods

liftEq :: (a -> b -> Bool) -> Edit a -> Edit b -> Bool #

Read1 Edit Source # 
Instance details

Defined in Data.Edit

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Edit a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Edit a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Edit a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Edit a] #

Show1 Edit Source # 
Instance details

Defined in Data.Edit

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Edit a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Edit a] -> ShowS #

MonadZip Edit Source # 
Instance details

Defined in Data.Edit

Methods

mzip :: Edit a -> Edit b -> Edit (a, b) #

mzipWith :: (a -> b -> c) -> Edit a -> Edit b -> Edit c #

munzip :: Edit (a, b) -> (Edit a, Edit b) #

Comonad Edit Source # 
Instance details

Defined in Data.Edit

Methods

extract :: Edit a -> a #

duplicate :: Edit a -> Edit (Edit a) #

extend :: (Edit a -> b) -> Edit a -> Edit b #

ComonadApply Edit Source # 
Instance details

Defined in Data.Edit

Methods

(<@>) :: Edit (a -> b) -> Edit a -> Edit b #

(@>) :: Edit a -> Edit b -> Edit b #

(<@) :: Edit a -> Edit b -> Edit a #

Eq a => Eq (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

(==) :: Edit a -> Edit a -> Bool #

(/=) :: Edit a -> Edit a -> Bool #

Data a => Data (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Edit a -> c (Edit a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Edit a) #

toConstr :: Edit a -> Constr #

dataTypeOf :: Edit a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Edit a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Edit a)) #

gmapT :: (forall b. Data b => b -> b) -> Edit a -> Edit a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Edit a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Edit a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Edit a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Edit a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Edit a -> m (Edit a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Edit a -> m (Edit a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Edit a -> m (Edit a) #

Read a => Read (Edit a) Source # 
Instance details

Defined in Data.Edit

Show a => Show (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

showsPrec :: Int -> Edit a -> ShowS #

show :: Edit a -> String #

showList :: [Edit a] -> ShowS #

Generic (Edit a) Source # 
Instance details

Defined in Data.Edit

Associated Types

type Rep (Edit a) :: * -> * #

Methods

from :: Edit a -> Rep (Edit a) x #

to :: Rep (Edit a) x -> Edit a #

Semigroup a => Semigroup (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

(<>) :: Edit a -> Edit a -> Edit a #

sconcat :: NonEmpty (Edit a) -> Edit a #

stimes :: Integral b => b -> Edit a -> Edit a #

Monoid a => Monoid (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

mempty :: Edit a #

mappend :: Edit a -> Edit a -> Edit a #

mconcat :: [Edit a] -> Edit a #

Arbitrary a => Arbitrary (Edit a) Source #

arbitrary is biased towards producing more Dirty values. shrink shrinks the generator towards Clean values.

Instance details

Defined in Data.Edit

Methods

arbitrary :: Gen (Edit a) #

shrink :: Edit a -> [Edit a] #

NFData a => NFData (Edit a) Source # 
Instance details

Defined in Data.Edit

Methods

rnf :: Edit a -> () #

type Rep (Edit a) Source # 
Instance details

Defined in Data.Edit

fromEdit :: Edit a -> a Source #

Extract the final value after having done some edits.

Unlike Maybe's fromMaybe, this function doesn't require a default value for totality as both constructors have a value in them.

isClean :: Edit a -> Bool Source #

Return True iff the argument has the form Clean _.

isDirty :: Edit a -> Bool Source #

Returns True iff the argument has the form Dirty _.

extract :: Comonad w => w a -> a #

extract . fmap f = f . extract

duplicate :: Comonad w => w a -> w (w a) #

extend :: Comonad w => (w a -> b) -> w a -> w b #

Conversions to and from base types

toMaybe :: Edit a -> Maybe a Source #

Was an edit made (is the value Dirty)? If yes, returns Just otherwise Nothing.

>>> toMaybe (Clean "Good morning.")
Nothing
>>> toMaybe (Dirty "Wink, wink.")
Just "Wink, wink."

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)

toEither :: Edit a -> Either a a Source #

A Dirty value becomes a Left and a Clean value becomes a Right.

Mnemonic: having things clean is usually the right situation to be in.

fromEither :: Either a a -> Edit a Source #

A Left value becomes a Dirty and a Right value becomes a Clean.

Mnemonic: having things clean is usually the right situation to be in.

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 #

Dirty values are put on the left and Clean values are put on the right.

partitionEdits = partitionEithers . map toEither

Forceful conversions

clean :: Edit a -> Edit a Source #

Forcibly make the value Clean. You probably do not want to use this function unless you're implementing some class instance for Edit.

dirty :: Edit a -> Edit a Source #

Forcibly make the value Dirty. You probably do not want to use this function unless you're implementing some class instance for Edit.

Re-exports from Control.Monad

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right Kleisli composition of monads.

(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c infixr 1 #

Right-to-left Kleisli composition of monads. (>=>), with the arguments flipped.

Note how this operator resembles function composition (.):

(.)   ::            (b ->   c) -> (a ->   b) -> a ->   c
(<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c