| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.TreeDiff.Class
Contents
Description
A ToExpr class.
Documentation
ediff :: ToExpr a => a -> a -> Edit EditExpr Source #
Difference between two ToExpr values.
>>>let x = (1, Just 2) :: (Int, Maybe Int)>>>let y = (1, Nothing)>>>prettyEditExpr (ediff x y)_×_ 1 -(Just 2) +Nothing
>>>data Foo = Foo { fooInt :: Either Char Int, fooBool :: [Maybe Bool], fooString :: String } deriving (Eq, Generic)>>>instance ToExpr Foo
>>>prettyEditExpr $ ediff (Foo (Right 2) [Just True] "fo") (Foo (Right 3) [Just True] "fo")Foo {fooBool = [Just True], fooInt = Right -2 +3, fooString = "fo"}
>>>prettyEditExpr $ ediff (Foo (Right 42) [Just True, Just False] "old") (Foo (Right 42) [Nothing, Just False, Just True] "new")Foo {fooBool = [-Just True, +Nothing, Just False, +Just True], fooInt = Right 42, fooString = -"old" +"new"}
ediff' :: (ToExpr a, ToExpr b) => a -> b -> Edit EditExpr Source #
Compare different types.
Note: Use with care as you can end up comparing apples with oranges.
>>>prettyEditExpr $ ediff' ["foo", "bar"] [Just "foo", Nothing][-"foo", +Just "foo", -"bar", +Nothing]
toExpr converts a Haskell value into
untyped Haskell-like syntax tree, Expr.
>>>toExpr ((1, Just 2) :: (Int, Maybe Int))App "_\215_" [App "1" [],App "Just" [App "2" []]]
Methods
toExpr :: (Generic a, All2 ToExpr (GCode a), GFrom a, GDatatypeInfo a) => a -> Expr Source #
listToExpr :: [a] -> Expr Source #
Instances
defaultExprViaShow :: Show a => a -> Expr Source #
An alternative implementation for literal types. We use show
representation of them.