Safe Haskell | None |
---|---|
Language | Haskell2010 |
Dino.AST.Diff
Synopsis
- dropEnd :: Int -> [a] -> [a]
- data Replace a = Replace {}
- data ElemOp a
- = AddElem a
- | RemoveElem a
- | EditElem (Diff a)
- data EndOp a
- data ListOp a = ListOp [Maybe (Diff a)] (Maybe (EndOp a))
- data Edit a
- newtype Monolithic a = Monolithic {
- unMonolithic :: a
- class Diffable a where
- applyDiffWhen :: Diffable a => Maybe (Diff a) -> a -> Maybe a
- prettyEditTuple :: Pretty a => Doc -> Doc -> Doc -> [Maybe a] -> Doc
- prettyEditApp :: Pretty a => NameType -> Text -> [Maybe a] -> Doc
- printEdit :: Show a => Edit a -> IO ()
- diffAsTestResult :: Show a => Maybe (Edit a) -> Doc
Documentation
Types
Edit operations on an optional element
Constructors
AddElem a | |
RemoveElem a | |
EditElem (Diff a) |
Edit operations at the end of a list
Edit operations on lists
Edit operation on a AST
Constructors
Replacement (Replace (AST a)) | |
EditApp Constr [Maybe (Edit a)] | |
EditList (Diff [AST a]) | |
EditLet (Diff (Text, AST a, AST a)) | |
EditRecord (Diff (Mapping Field (AST a))) |
newtype Monolithic a Source #
Wrapper for values that should be regarded as monolithic when diffing
Constructors
Monolithic | |
Fields
|
Instances
Eq a => Diffable (Monolithic a) Source # | |
Defined in Dino.AST.Diff Associated Types type Diff (Monolithic a) Source # Methods diff :: Monolithic a -> Monolithic a -> Maybe (Diff (Monolithic a)) Source # applyDiff :: Diff (Monolithic a) -> Monolithic a -> Maybe (Monolithic a) Source # | |
type Diff (Monolithic a) Source # | |
Defined in Dino.AST.Diff |
Diffing
class Diffable a where Source #
Minimal complete definition
Nothing
Associated Types
Representation of the difference between two values
Methods
Calculate the difference between two values
The result is Nothing
iff. the two values are equal.
The following property holds:
If Just d = diff a b
Then Just b = applyDiff
d a
applyDiff :: Diff a -> a -> Maybe a Source #
Apply an Edit
to a Value
This function is mostly intended for testing. It succeeds iff. the edit makes sense.
Instances
Diffable Bool Source # | |
Diffable Double Source # | |
Diffable Float Source # | |
Diffable Int Source # | |
Diffable Integer Source # | |
Diffable Rational Source # | |
Diffable () Source # | |
Diffable Text Source # | |
Diffable a => Diffable [a] Source # | Matches element-wise from the start of the lists, and detects additions/removals at the end. |
Diffable a => Diffable (Maybe a) Source # | |
Eq a => Diffable (AST a) Source # | |
Eq a => Diffable (Monolithic a) Source # | |
Defined in Dino.AST.Diff Associated Types type Diff (Monolithic a) Source # Methods diff :: Monolithic a -> Monolithic a -> Maybe (Diff (Monolithic a)) Source # applyDiff :: Diff (Monolithic a) -> Monolithic a -> Maybe (Monolithic a) Source # | |
(Diffable a, Diffable b) => Diffable (a, b) Source # | |
(Eq k, Hashable k, Diffable a) => Diffable (Mapping k a) Source # | |
(Diffable a, Diffable b, Diffable c) => Diffable (a, b, c) Source # | |
Rendering
prettyEditTuple :: Pretty a => Doc -> Doc -> Doc -> [Maybe a] -> Doc Source #
Pretty print for edits on tuple-like collections (where elements are identified by position)
prettyEditApp :: Pretty a => NameType -> Text -> [Maybe a] -> Doc Source #
Pretty print EditApp
for "named" constructors