generic-diff
Safe HaskellSafe-Inferred
LanguageHaskell2010

Generics.Diff

Description

Generic detailed comparisons, without boilerplate.

The simplest way in Haskell that we can use to compare two values of the same type is using Eq. The (==) operator gives us a simple Boolean response: True if the values are equal, or False otherwise. Slightly more informative is Ord: the compare function (or operators (<=), (>) etc) tells us, if two values are different, which one can be considered as "less than" or "more than" the other.

One situation in which these might not be enough is testing. Say you have a pair of (de)serialisation functions (which we'll imagine are total, for simplicity), and which we expect to be inverses:

serialise   :: (Serialise a) => a      -> String
deserialise :: (Serialise a) => String -> a

Let's imagine we have some (Hspec) tests, e.g.:

unitTest :: (Serialise a) => a -> Spec
unitTest value =
  let serialised = serialise value
      deserailised = deserialise serialised
  in  it "Serialisation should satisfy the round-trip property" $ deserialised `shouldBe` value

What happens if the test fails? If we're dealing with a simple type like Int, the error will be very easy to debug:

  1) Serialisation should satisfy the round-trip property
       expected: 2
        but got: 1

But what if our type is much more complicated, with lots of constructors, fields, nesting... Especially if the type has a derived show instance, the output can be very dense, littered with parentheses, and overall very difficult to play "spot the difference" with.

That's where this library comes in handy. Using the Diff typeclass, we can identify precisely where two values differ. A "top-level" diff will tell you at which constructor and which field the values are different; if the types of those fields also have useful Diff instances, we can recurse into them to pinpoint the error even more accurately. Even better, we can derive our Diff instances completely automatically as long as our types have instances for Generic (and HasDatatypeInfo) from generics-sop. In fact, we use the types NP and NS extensively to define the types we use for representing diffs.

Understanding

To aid understanding (both for this library and for generics-sop), I think it helps to think of an ADT as a grid:

data MyType
  = Con1 Char (Either Int String)
  | Con2 [Bool]

This corresponds to a grid with one row per constructor, one column per field:

ConstructorFields
Con1CharEither Int String
Con2[Bool]N / A

A value of type MyType can be thought of as being one row of the grid, with one value for each column in the row.

Now, if we have two values of type MyType, there's too main ways they can differ. If they inhabit different rows of the grid, they're clearly not equal, and all we can say is "this one uses this constructor, that one uses that constructor" (see WrongConstructor). In other words we just report the names of the two rows. If they inhabit the same row of the grid, we have to go column by column, comparing each pair of values (we'll get to how we compare them in a second). If they're all pairwise equal, we can conclude the two values are Equal; if one pair fails the comparison test, we stop checking and say "the types differ at this constructor, in this field" (see FieldMismatch). Effectively, we point to a single cell of the grid and say "that's where the inequality is".

You might note that this process is very similar to how a stock-derived Eq instance works. All we've added so far is an extra dimension to the output, detailing not just that two values differ, but where in the grid they differ. Where things get interesting is how we do the pairwise comparison between fields. If the comparison test is (==), then it's as above: we find out that two values are either equal, or not equal; and if they're not equal, we find out at which field that inequality happens. However, as in MyType above, types often refer to other types! Either Int String also has its own grid:

-- excuse the pseudo-Haskell
type Either Int String
  = Left Int
  | Right String

Similar to above, we have:

ConstructorFields
LeftInt
RightString

In fact, if we squint a bit, this grid actually exists inside the cell of the MyType grid:

Con1 Char LeftInt
RightString
Con2[Bool]N / A

This gives us an extra level of granularity: when we get to the pair of Either Int String fields, rather than just delegating to Eq, we can go through the same procedure as above. Then instead of "the two values differ at the Either Int String field of the Con1 constructor", we can say "the two values differ at the Either Int String field of the Con1 constructor, and those two field differs because one uses the Left constructor and the other uses the Right constructor"! And of course, once we have one step of recursion, we have as many as we want...

Implementing instances

The Diff class encapsulates the above behaviour with diff. It's very strongly recommended that you don't implement diff yourself, but use the default implementation using Generic, which is just gdiff. In the rare case you might want to implement diff yourself, there are two other functions you might want to use.

  • eqDiff simply delegates the entire process to (==), and will only ever give Equal or TopLevelNotEqual. This is no more useful than Eq, and should only be used for primitive types (e.g. all numeric types like Char and Int) use eqDiff, since they don't really have ADTs or recursion. This is the only implementation that doesn't require an instance of Generic.
  • gdiffTopLevel does the above process, but without recursion. In other words each pair of fields is compared using (==). This is definitely better than Eq, by one "level". One situation when this might be useful is when your type refers to types from other libraries, and you want to avoid orphan Diff instances for those types. Another is when the types of the fields are "small" enough that we don't care about recursing into them. For example:
data HttpVersion
  = Http1
  | Http2
  deriving (Eq)

data Request = Request
  { host :: String
  , port :: Int
  -- there's no instance of Diff for Map, so just compare for equality using (==)
  , parameters :: Map String String
  -- Diff doesn't really add anything over Eq for enum types, so Eq is fine
  , httpVersion :: HttpVersion
  }
  deriving stock (GHC.Generics.Generic)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)

instance Diff Request where
  diff = gdiffTopLevel

For completeness, we also provide one more implementation function: gdiffWith lets you provide a set of Differs (comparison functions) to use for each pair of fields (one per cell of the grid). I'm not sure in what situation you'd want this, but there you go.

Synopsis

Class

class Diff a where Source #

A type with an instance of Diff permits a more nuanced comparison than Eq or Ord. If two values are not equal, diff will tell you exactly where they differ ("in this contructor, at that field"). The granularity of the pinpointing of the difference (how many "levels" of Diff we can "descend" through) depends on the implementation of the instance.

For user-defined types, it's strongly recommended you derive your Diff instance using Generic from generics-sop. If those types refer to other types, those will need Diff instances too. For example:

{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}

import qualified GHC.Generics as G
import qualified Generics.SOP as SOP

data BinOp = Plus | Minus
  deriving stock (Show, G.Generic)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo, Diff)

data Expr
  = Atom Int
  | Bin {left :: Expr, op :: BinOp, right :: Expr}
  deriving stock (Show, G.Generic)
  deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo, Diff)

Now that we have our instances, we can diff values to find out exactly where they differ:

-- If two values are equal, diff should always return Equal.
ghci> diff Plus Plus
Equal

ghci> diff Plus Minus
Error (Nested (WrongConstructor (Z (Constructor "Plus")) (S (Z (Constructor "Minus")))))

ghci> diff (Atom 1) (Atom 2)
Error (Nested (FieldMismatch (AtLoc (Z (Constructor "Atom" :*: Z (Nested TopLevelNotEqual))))))

ghci> diff (Bin (Atom 1) Plus (Atom 1)) (Atom 2)
Error (Nested (WrongConstructor (S (Z (Constructor "Bin"))) (Z (Constructor "Atom"))))

ghci> diff (Bin (Atom 1) Plus (Atom 1)) (Bin (Atom 1) Minus (Atom 1))
Error (Nested (FieldMismatch (AtLoc (S (Z (Constructor "Bin" :*: S (Z (Nested (WrongConstructor (Z (Constructor "Plus")) (S (Z (Constructor "Minus"))))))))))))

ghci> diff (Bin (Atom 1) Plus (Atom 1)) (Bin (Atom 1) Plus (Atom 2))
Error (Nested (FieldMismatch (DiffAtField (S (Z (Record "Bin" (FieldInfo "left" :* FieldInfo "op" :* FieldInfo "right" :* Nil) :*: S (S (Z (Nested (FieldMismatch (DiffAtField (Z (Constructor "Atom" :*: Z TopLevelNotEqual)))))))))))))

Of course, these are just as difficult to understand as derived Show instances, or more so. Fortunately we can use the functions in Generics.Diff.Render to get a nice, intuitive representation of the diffs:

ghci> printDiffResult $ diff Plus Plus
Equal

ghci> printDiffResult $ diff Plus Minus
Wrong constructor
Constructor of left value: Plus
Constructor of right value: Minus

ghci> printDiffResult $ diff (Atom 1) (Atom 2)
Both values use constructor Atom but fields don't match
In field 0 (0-indexed):
  Not equal

ghci> printDiffResult $ diff (Bin (Atom 1) Plus (Atom 1)) (Atom 2)
Wrong constructor
Constructor of left value: Bin
Constructor of right value: Atom

ghci> printDiffResult $ diff (Bin (Atom 1) Plus (Atom 1)) (Bin (Atom 1) Minus (Atom 1))
Both values use constructor Bin but fields don't match
In field op:
  Wrong constructor
  Constructor of left value: Plus
  Constructor of right value: Minus

ghci> printDiffResult $ diff (Bin (Atom 1) Plus (Atom 1)) (Bin (Atom 1) Plus (Atom 2))
Both values use constructor Bin but fields don't match
In field right:
  Both values use constructor Atom but fields don't match
  In field 0 (0-indexed):
    Not equal

Laws

For type a with instance Diff a, and values x, y :: a, the following should hold:

x == y   <=>  x `diff` y == Equal

Minimal complete definition

Nothing

Methods

diff :: a -> a -> DiffResult a Source #

Detailed comparison of two values. It is strongly recommended to only use the default implementation, or one of eqDiff or gdiffTopLevel.

default diff :: (Generic a, HasDatatypeInfo a, All2 Diff (Code a)) => a -> a -> DiffResult a Source #

diffList :: [a] -> [a] -> DiffResult [a] Source #

Compare two lists of values. This mostly exists so that we can define a custom instance for String, in a similar vein to showList.

Instances

Instances details
Diff ByteArray Source # 
Instance details

Defined in Generics.Diff.Instances

Diff DataRep Source # 
Instance details

Defined in Generics.Diff.Instances

Diff E0 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E0 -> E0 -> DiffResult E0 Source #

diffList :: [E0] -> [E0] -> DiffResult [E0] Source #

Diff E1 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E1 -> E1 -> DiffResult E1 Source #

diffList :: [E1] -> [E1] -> DiffResult [E1] Source #

Diff E12 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E12 -> E12 -> DiffResult E12 Source #

diffList :: [E12] -> [E12] -> DiffResult [E12] Source #

Diff E2 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E2 -> E2 -> DiffResult E2 Source #

diffList :: [E2] -> [E2] -> DiffResult [E2] Source #

Diff E3 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E3 -> E3 -> DiffResult E3 Source #

diffList :: [E3] -> [E3] -> DiffResult [E3] Source #

Diff E6 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E6 -> E6 -> DiffResult E6 Source #

diffList :: [E6] -> [E6] -> DiffResult [E6] Source #

Diff E9 Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: E9 -> E9 -> DiffResult E9 Source #

diffList :: [E9] -> [E9] -> DiffResult [E9] Source #

Diff All Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: All -> All -> DiffResult All Source #

diffList :: [All] -> [All] -> DiffResult [All] Source #

Diff Any Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Any -> Any -> DiffResult Any Source #

diffList :: [Any] -> [Any] -> DiffResult [Any] Source #

Diff TypeRep Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Unique Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Version Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Errno Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CBool Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CChar Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CClock Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CDouble Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CFloat Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CInt Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CIntMax Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CIntPtr Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CLLong Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CLong Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CPtrdiff Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CSChar Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CSUSeconds Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CShort Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CSigAtomic Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CSize Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CTime Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUChar Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUInt Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUIntMax Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUIntPtr Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CULLong Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CULong Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUSeconds Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CUShort Source # 
Instance details

Defined in Generics.Diff.Instances

Diff CWchar Source # 
Instance details

Defined in Generics.Diff.Instances

Diff IntPtr Source # 
Instance details

Defined in Generics.Diff.Instances

Diff WordPtr Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Void Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ByteOrder Source # 
Instance details

Defined in Generics.Diff.Instances

Diff BlockReason Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ThreadId Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ThreadStatus Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Event Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Lifetime Source # 
Instance details

Defined in Generics.Diff.Instances

Diff FdKey Source # 
Instance details

Defined in Generics.Diff.Instances

Diff TimeoutKey Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ErrorCall Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ArithException Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Fingerprint Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Associativity Source # 
Instance details

Defined in Generics.Diff.Instances

Diff DecidedStrictness Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Fixity Source # 
Instance details

Defined in Generics.Diff.Instances

Diff MaskingState Source # 
Instance details

Defined in Generics.Diff.Instances

Diff BufferState Source # 
Instance details

Defined in Generics.Diff.Instances

Diff IODeviceType Source # 
Instance details

Defined in Generics.Diff.Instances

Diff SeekMode Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ArrayException Source # 
Instance details

Defined in Generics.Diff.Instances

Diff AsyncException Source # 
Instance details

Defined in Generics.Diff.Instances

Diff ExitCode Source # 
Instance details

Defined in Generics.Diff.Instances

Diff IOErrorType Source # 
Instance details

Defined in Generics.Diff.Instances

Diff IOException Source # 
Instance details

Defined in Generics.Diff.Instances

Diff HandlePosn Source # 
Instance details

Defined in Generics.Diff.Instances

Diff BufferMode Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Handle Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Newline Source # 
Instance details

Defined in Generics.Diff.Instances

Diff NewlineMode Source # 
Instance details

Defined in Generics.Diff.Instances

Diff IOMode Source # 
Instance details

Defined in Generics.Diff.Instances

Diff InfoProv Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Int16 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Int32 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Int64 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Int8 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff StackEntry Source # 
Instance details

Defined in Generics.Diff.Instances

Diff SrcLoc Source # 
Instance details

Defined in Generics.Diff.Instances

Diff SomeChar Source # 
Instance details

Defined in Generics.Diff.Instances

Diff SomeSymbol Source # 
Instance details

Defined in Generics.Diff.Instances

Diff SomeNat Source # 
Instance details

Defined in Generics.Diff.Instances

Diff GeneralCategory Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Word16 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Word32 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Word64 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Word8 Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Timeout Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Lexeme Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Ordering Source # 
Instance details

Defined in Generics.Diff.Instances

Diff TrName Source # 
Instance details

Defined in Generics.Diff.Instances

Diff TyCon Source # 
Instance details

Defined in Generics.Diff.Instances

Diff UnicodeException Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Text Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Builder Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Text Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Integer Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Natural Source # 
Instance details

Defined in Generics.Diff.Instances

Diff () Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: () -> () -> DiffResult () Source #

diffList :: [()] -> [()] -> DiffResult [()] Source #

Diff Bool Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Char Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Double Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Float Source # 
Instance details

Defined in Generics.Diff.Instances

Diff Int Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Int -> Int -> DiffResult Int Source #

diffList :: [Int] -> [Int] -> DiffResult [Int] Source #

Diff Word Source # 
Instance details

Defined in Generics.Diff.Instances

Diff (Chan a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Chan a -> Chan a -> DiffResult (Chan a) Source #

diffList :: [Chan a] -> [Chan a] -> DiffResult [Chan a] Source #

Diff (MutableByteArray a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (Complex a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (Identity a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (First a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: First a -> First a -> DiffResult (First a) Source #

diffList :: [First a] -> [First a] -> DiffResult [First a] Source #

Diff a => Diff (Last a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Last a -> Last a -> DiffResult (Last a) Source #

diffList :: [Last a] -> [Last a] -> DiffResult [Last a] Source #

Diff a => Diff (Down a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Down a -> Down a -> DiffResult (Down a) Source #

diffList :: [Down a] -> [Down a] -> DiffResult [Down a] Source #

Diff a => Diff (First a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: First a -> First a -> DiffResult (First a) Source #

diffList :: [First a] -> [First a] -> DiffResult [First a] Source #

Diff a => Diff (Last a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Last a -> Last a -> DiffResult (Last a) Source #

diffList :: [Last a] -> [Last a] -> DiffResult [Last a] Source #

Diff a => Diff (Max a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Max a -> Max a -> DiffResult (Max a) Source #

diffList :: [Max a] -> [Max a] -> DiffResult [Max a] Source #

Diff a => Diff (Min a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Min a -> Min a -> DiffResult (Min a) Source #

diffList :: [Min a] -> [Min a] -> DiffResult [Min a] Source #

Diff a => Diff (WrappedMonoid a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (Dual a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Dual a -> Dual a -> DiffResult (Dual a) Source #

diffList :: [Dual a] -> [Dual a] -> DiffResult [Dual a] Source #

Diff a => Diff (Product a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (Sum a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Sum a -> Sum a -> DiffResult (Sum a) Source #

diffList :: [Sum a] -> [Sum a] -> DiffResult [Sum a] Source #

Diff (ConstPtr a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (NonEmpty a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff (TVar a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: TVar a -> TVar a -> DiffResult (TVar a) Source #

diffList :: [TVar a] -> [TVar a] -> DiffResult [TVar a] Source #

Diff (ForeignPtr a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff (IORef a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: IORef a -> IORef a -> DiffResult (IORef a) Source #

diffList :: [IORef a] -> [IORef a] -> DiffResult [IORef a] Source #

Diff (MVar a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: MVar a -> MVar a -> DiffResult (MVar a) Source #

diffList :: [MVar a] -> [MVar a] -> DiffResult [MVar a] Source #

Diff (FunPtr a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: FunPtr a -> FunPtr a -> DiffResult (FunPtr a) Source #

diffList :: [FunPtr a] -> [FunPtr a] -> DiffResult [FunPtr a] Source #

Diff (Ptr a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Ptr a -> Ptr a -> DiffResult (Ptr a) Source #

diffList :: [Ptr a] -> [Ptr a] -> DiffResult [Ptr a] Source #

Eq a => Diff (Ratio a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Ratio a -> Ratio a -> DiffResult (Ratio a) Source #

diffList :: [Ratio a] -> [Ratio a] -> DiffResult [Ratio a] Source #

Diff (StablePtr a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff (StableName a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff a => Diff (I a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: I a -> I a -> DiffResult (I a) Source #

diffList :: [I a] -> [I a] -> DiffResult [I a] Source #

Diff a => Diff (Maybe a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Maybe a -> Maybe a -> DiffResult (Maybe a) Source #

diffList :: [Maybe a] -> [Maybe a] -> DiffResult [Maybe a] Source #

Diff a => Diff [a] Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: [a] -> [a] -> DiffResult [a] Source #

diffList :: [[a]] -> [[a]] -> DiffResult [[a]] Source #

(Diff a, Diff b) => Diff (Either a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Either a b -> Either a b -> DiffResult (Either a b) Source #

diffList :: [Either a b] -> [Either a b] -> DiffResult [Either a b] Source #

(HasDatatypeInfo (Fixed a), All2 Diff (Code (Fixed a))) => Diff (Fixed a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Fixed a -> Fixed a -> DiffResult (Fixed a) Source #

diffList :: [Fixed a] -> [Fixed a] -> DiffResult [Fixed a] Source #

Diff (Proxy a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Proxy a -> Proxy a -> DiffResult (Proxy a) Source #

diffList :: [Proxy a] -> [Proxy a] -> DiffResult [Proxy a] Source #

(Diff a, Diff b) => Diff (Arg a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Arg a b -> Arg a b -> DiffResult (Arg a b) Source #

diffList :: [Arg a b] -> [Arg a b] -> DiffResult [Arg a b] Source #

Diff (TypeRep a) Source # 
Instance details

Defined in Generics.Diff.Instances

Diff (IOArray i e) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: IOArray i e -> IOArray i e -> DiffResult (IOArray i e) Source #

diffList :: [IOArray i e] -> [IOArray i e] -> DiffResult [IOArray i e] Source #

Diff (STRef s a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: STRef s a -> STRef s a -> DiffResult (STRef s a) Source #

diffList :: [STRef s a] -> [STRef s a] -> DiffResult [STRef s a] Source #

(Diff a, Diff b) => Diff (a, b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b) -> (a, b) -> DiffResult (a, b) Source #

diffList :: [(a, b)] -> [(a, b)] -> DiffResult [(a, b)] Source #

(HasDatatypeInfo (Const a b), All2 Diff (Code (Const a b))) => Diff (Const a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Const a b -> Const a b -> DiffResult (Const a b) Source #

diffList :: [Const a b] -> [Const a b] -> DiffResult [Const a b] Source #

(HasDatatypeInfo (Ap f a), All2 Diff (Code (Ap f a))) => Diff (Ap f a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Ap f a -> Ap f a -> DiffResult (Ap f a) Source #

diffList :: [Ap f a] -> [Ap f a] -> DiffResult [Ap f a] Source #

(HasDatatypeInfo (Alt f a), All2 Diff (Code (Alt f a))) => Diff (Alt f a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Alt f a -> Alt f a -> DiffResult (Alt f a) Source #

diffList :: [Alt f a] -> [Alt f a] -> DiffResult [Alt f a] Source #

Diff (Coercion a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Coercion a b -> Coercion a b -> DiffResult (Coercion a b) Source #

diffList :: [Coercion a b] -> [Coercion a b] -> DiffResult [Coercion a b] Source #

Diff (OrderingI a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: OrderingI a b -> OrderingI a b -> DiffResult (OrderingI a b) Source #

diffList :: [OrderingI a b] -> [OrderingI a b] -> DiffResult [OrderingI a b] Source #

Diff (STArray s i a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: STArray s i a -> STArray s i a -> DiffResult (STArray s i a) Source #

diffList :: [STArray s i a] -> [STArray s i a] -> DiffResult [STArray s i a] Source #

(HasDatatypeInfo (K a b), All2 Diff (Code (K a b))) => Diff (K a b) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: K a b -> K a b -> DiffResult (K a b) Source #

diffList :: [K a b] -> [K a b] -> DiffResult [K a b] Source #

(Diff a, Diff b, Diff c) => Diff (a, b, c) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c) -> (a, b, c) -> DiffResult (a, b, c) Source #

diffList :: [(a, b, c)] -> [(a, b, c)] -> DiffResult [(a, b, c)] Source #

(HasDatatypeInfo (Product f g a), All2 Diff (Code (Product f g a))) => Diff (Product f g a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Product f g a -> Product f g a -> DiffResult (Product f g a) Source #

diffList :: [Product f g a] -> [Product f g a] -> DiffResult [Product f g a] Source #

(HasDatatypeInfo (Sum f g a), All2 Diff (Code (Sum f g a))) => Diff (Sum f g a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Sum f g a -> Sum f g a -> DiffResult (Sum f g a) Source #

diffList :: [Sum f g a] -> [Sum f g a] -> DiffResult [Sum f g a] Source #

(Diff a, Diff b, Diff c, Diff d) => Diff (a, b, c, d) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d) -> (a, b, c, d) -> DiffResult (a, b, c, d) Source #

diffList :: [(a, b, c, d)] -> [(a, b, c, d)] -> DiffResult [(a, b, c, d)] Source #

(HasDatatypeInfo (Compose f g a), All2 Diff (Code (Compose f g a))) => Diff (Compose f g a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: Compose f g a -> Compose f g a -> DiffResult (Compose f g a) Source #

diffList :: [Compose f g a] -> [Compose f g a] -> DiffResult [Compose f g a] Source #

(HasDatatypeInfo ((f :.: g) a), All2 Diff (Code ((f :.: g) a))) => Diff ((f :.: g) a) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (f :.: g) a -> (f :.: g) a -> DiffResult ((f :.: g) a) Source #

diffList :: [(f :.: g) a] -> [(f :.: g) a] -> DiffResult [(f :.: g) a] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e) => Diff (a, b, c, d, e) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e) -> (a, b, c, d, e) -> DiffResult (a, b, c, d, e) Source #

diffList :: [(a, b, c, d, e)] -> [(a, b, c, d, e)] -> DiffResult [(a, b, c, d, e)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f) => Diff (a, b, c, d, e, f) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> DiffResult (a, b, c, d, e, f) Source #

diffList :: [(a, b, c, d, e, f)] -> [(a, b, c, d, e, f)] -> DiffResult [(a, b, c, d, e, f)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g) => Diff (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> DiffResult (a, b, c, d, e, f, g) Source #

diffList :: [(a, b, c, d, e, f, g)] -> [(a, b, c, d, e, f, g)] -> DiffResult [(a, b, c, d, e, f, g)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h) => Diff (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> DiffResult (a, b, c, d, e, f, g, h) Source #

diffList :: [(a, b, c, d, e, f, g, h)] -> [(a, b, c, d, e, f, g, h)] -> DiffResult [(a, b, c, d, e, f, g, h)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i) => Diff (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> DiffResult (a, b, c, d, e, f, g, h, i) Source #

diffList :: [(a, b, c, d, e, f, g, h, i)] -> [(a, b, c, d, e, f, g, h, i)] -> DiffResult [(a, b, c, d, e, f, g, h, i)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j) => Diff (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> DiffResult (a, b, c, d, e, f, g, h, i, j) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j)] -> [(a, b, c, d, e, f, g, h, i, j)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k) => Diff (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> [(a, b, c, d, e, f, g, h, i, j, k)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l) => Diff (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> [(a, b, c, d, e, f, g, h, i, j, k, l)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u, Diff v) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u, Diff v, Diff w) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u, Diff v, Diff w, Diff x) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u, Diff v, Diff w, Diff x, Diff y) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y)] Source #

(Diff a, Diff b, Diff c, Diff d, Diff e, Diff f, Diff g, Diff h, Diff i, Diff j, Diff k, Diff l, Diff m, Diff n, Diff o, Diff p, Diff q, Diff r, Diff s, Diff t, Diff u, Diff v, Diff w, Diff x, Diff y, Diff z) => Diff (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source # 
Instance details

Defined in Generics.Diff.Instances

Methods

diff :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) -> DiffResult (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) Source #

diffList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)] -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)] -> DiffResult [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z)] Source #

Implementing diff

gdiff :: forall a. (Generic a, HasDatatypeInfo a, All2 Diff (Code a)) => a -> a -> DiffResult a Source #

The default implementation of diff. Follows the procedure described above. We keep recursing into the Diff instances of the field types, as far as we can.

gdiffTopLevel :: forall a. (Generic a, HasDatatypeInfo a, All2 Eq (Code a)) => a -> a -> DiffResult a Source #

Alternate implementation of diff - basically one level of gdiff. To compare individual fields of the top-level values, we just use (==).

gdiffWith :: forall a. (Generic a, HasDatatypeInfo a) => POP Differ (Code a) -> a -> a -> DiffResult a Source #

Follow the same algorithm as gdiff, but the caller can provide their own POP grid of Differs specifying how to compare each field we might come across.

eqDiff :: Eq a => a -> a -> DiffResult a Source #

The most basic Differ possible. If the two values are equal, return Equal; otherwise, return TopLevelNotEqual.

Types

data DiffResult a Source #

The result of a diff.

Constructors

Error (DiffError a)

There's a diff, here it is

Equal

No diff, inputs are equal

Instances

Instances details
Show (DiffResult a) Source # 
Instance details

Defined in Generics.Diff.Type

Eq (DiffResult a) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

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

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

data DiffError a where Source #

A GADT representing an error during the diff algorithm - i.e. this tells us where and how two values differ.

The special constructors for list are so that we can treat these types a bit uniquely. See ListDiffError.

Constructors

TopLevelNotEqual :: DiffError a

All we can say is that the values being compared are not equal.

Nested :: DiffErrorNested (Code a) -> DiffError a

We've identified a diff at a certain constructor or field

DiffList :: ListDiffError a -> DiffError [a]

Special case for lists

DiffNonEmpty :: ListDiffError a -> DiffError (NonEmpty a)

Special case for non-empty lists

Instances

Instances details
Show (DiffError a) Source # 
Instance details

Defined in Generics.Diff.Type

Eq (DiffError a) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

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

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

data DiffErrorNested xss Source #

This is where we actually detail the difference between two values, and where in their structure the difference is.

Constructors

WrongConstructor (NS ConstructorInfo xss) (NS ConstructorInfo xss)

The two input values use different constructor, which are included.

FieldMismatch (DiffAtField xss)

The inputs use the same constructor, but differ at one of the fields. DiffAtField will tell us where and how.

Instances

Instances details
Show (DiffErrorNested xss) Source # 
Instance details

Defined in Generics.Diff.Type

Eq (DiffErrorNested xss) Source # 
Instance details

Defined in Generics.Diff.Type

data ListDiffError a Source #

If we did a normal gdiff on a linked list, we'd have to recurse through one "level" of Diffs for each element of the input lists. The output would be really hard to read or understand. Therefore this type lets us treat lists as a special case, depending on how they differ.

Constructors

DiffAtIndex Int (DiffError a)

If we find a difference when comparing the two lists pointwise, we report the index of the error and the error caused by the elements at that index of the input lists.

WrongLengths Int Int

The two lists have different lengths. If we get a WrongLengths instead of an Equal or a DiffAtIndex , we know that one of the lists must be a subset of the other.

Instances

Instances details
Show (ListDiffError a) Source # 
Instance details

Defined in Generics.Diff.Type

Eq (ListDiffError a) Source # 
Instance details

Defined in Generics.Diff.Type

newtype DiffAtField xss Source #

In the case that two values have the same constructor but differ at a certain field, we want two report two things: what the DiffError is at that field, and exactly where that field is. Careful use of NS gives us both of those things.

Instances

Instances details
Show (DiffAtField xss) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

showsPrec :: Int -> DiffAtField xss -> ShowS #

show :: DiffAtField xss -> String #

showList :: [DiffAtField xss] -> ShowS #

Eq (DiffAtField xss) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

(==) :: DiffAtField xss -> DiffAtField xss -> Bool #

(/=) :: DiffAtField xss -> DiffAtField xss -> Bool #

data (f :*: g) a infixr 6 Source #

Lifted product of functors. We could have used Product, but this is more concise.

Constructors

(f a) :*: (g a) infixr 6 

Instances

Instances details
(Show (f a), Show (g a)) => Show ((f :*: g) a) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

showsPrec :: Int -> (f :*: g) a -> ShowS #

show :: (f :*: g) a -> String #

showList :: [(f :*: g) a] -> ShowS #

(Eq (f a), Eq (g a)) => Eq ((f :*: g) a) Source # 
Instance details

Defined in Generics.Diff.Type

Methods

(==) :: (f :*: g) a -> (f :*: g) a -> Bool #

(/=) :: (f :*: g) a -> (f :*: g) a -> Bool #

newtype Differ x Source #

A newtype wrapping a binary function producing a DiffResult. The only reason for this newtype is so that we can use it as a functor with the types from generic-sop.

Constructors

Differ (x -> x -> DiffResult x)