diff --git a/generic-diff.cabal b/generic-diff.cabal index bb10ac1..1b05339 100644 --- a/generic-diff.cabal +++ b/generic-diff.cabal @@ -74,6 +74,8 @@ library Generics.Diff Generics.Diff.Instances Generics.Diff.Render + Generics.Diff.Special + Generics.Diff.Special.List other-modules: Generics.Diff.Class Generics.Diff.Type diff --git a/src/Generics/Diff.hs b/src/Generics/Diff.hs index 29db80b..a3d10ea 100644 --- a/src/Generics/Diff.hs +++ b/src/Generics/Diff.hs @@ -127,12 +127,11 @@ uses the @Right@ constructor"! And of course, once we have one step of recursion 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 'Generics.SOP.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. +In case you might want to implement 'diff' yourself, there are three 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 'Generics.SOP.Generic'. +use 'eqDiff', since they don't really have ADTs or recursion. - '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 @@ -160,6 +159,9 @@ instance 'Diff' Request where 'diff' = 'gdiffTopLevel' @ +- 'diffWithSpecial' lets us handle edge cases for funky types with unusual 'Eq' instances or preserved +invariants. See "Generics.Diff.Special". + For completeness, we also provide one more implementation function: 'gdiffWith' lets you provide a set of 'Differ's (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. diff --git a/src/Generics/Diff/Class.hs b/src/Generics/Diff/Class.hs index 1ece6eb..8a37911 100644 --- a/src/Generics/Diff/Class.hs +++ b/src/Generics/Diff/Class.hs @@ -1,5 +1,5 @@ {-# LANGUAGE EmptyCase #-} -{-# OPTIONS_GHC -Wno-redundant-constraints #-} +{-# OPTIONS_GHC -Wno-redundant-constraints -Wno-orphans #-} module Generics.Diff.Class ( -- * Class @@ -10,14 +10,21 @@ module Generics.Diff.Class , gdiffTopLevel , gdiffWith , eqDiff + , diffWithSpecial + , gspecialDiffNested + + -- * Special case: lists , diffListWith ) where import Data.SOP import Data.SOP.NP +import qualified GHC.Generics as G +import Generics.Diff.Render import Generics.Diff.Type -import Generics.SOP +import Generics.SOP as SOP +import Generics.SOP.GGP as SOP {- | 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, @@ -27,6 +34,10 @@ 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: +However, in some cases we'll want to use a custom type for representing diffs of user-defined or +third-party types. For example, if we have non-derived `Eq` instances, invariants etc. In that case, +see "Generics.Diff.Special". + @ {\-# LANGUAGE DerivingStrategies #-\} {\-# LANGUAGE DeriveGeneric #-\} @@ -124,20 +135,30 @@ class Diff a where -- | Compare two lists of values. This mostly exists so that we can define a custom instance for 'String', -- in a similar vein to 'showList'. diffList :: [a] -> [a] -> DiffResult [a] - diffList = diffListWith DiffList diff + diffList = diffWithSpecial + +-- | When we have an instance of 'SpecialDiff', we can implement 'diff' using 'DiffSpecial'. +diffWithSpecial :: (SpecialDiff a) => a -> a -> DiffResult a +diffWithSpecial l r = maybe Equal (Error . DiffSpecial) $ specialDiff l r + +instance (Diff a) => SpecialDiff [a] where + type SpecialDiffError [a] = ListDiffError a + specialDiff = diffListWith diff + renderSpecialDiffError = listDiffErrorDoc "list" -{- | Used to implement 'diffList'. Given two lists, a way to 'diff' the elements of the list, and a way -to convert a 'ListDiffError' to a 'DiffError' (e.g. 'DiffList'), return a 'DiffResult' of a list-like type. +{- | Given two lists and a way to 'diff' the elements of the list, +return a 'ListDiffError'. Used to implement 'specialDiff' for list-like types. +See "Generics.Diff.Special" for an example. -} -diffListWith :: (ListDiffError a -> DiffError b) -> (a -> a -> DiffResult a) -> [a] -> [a] -> DiffResult b -diffListWith f d = go 0 +diffListWith :: (a -> a -> DiffResult a) -> [a] -> [a] -> Maybe (ListDiffError a) +diffListWith d = go 0 where - go _ [] [] = Equal - go n [] ys = Error $ f $ WrongLengths n (n + length ys) - go n xs [] = Error $ f $ WrongLengths (n + length xs) n + go _ [] [] = Nothing + go n [] ys = Just $ WrongLengths n (n + length ys) + go n xs [] = Just $ WrongLengths (n + length xs) n go n (x : xs) (y : ys) = case d x y of Equal -> go (n + 1) xs ys - Error err -> Error $ f $ DiffAtIndex n err + Error err -> Just $ DiffAtIndex n err {- | The most basic 'Differ' possible. If the two values are equal, return 'Equal'; otherwise, return 'TopLevelNotEqual'. @@ -192,6 +213,45 @@ gdiffWithPure :: DiffResult a gdiffWithPure ds = gdiffWith $ cpure_POP (Proxy @c) ds +{- | Helper function to implement 'specialDiff' for an instance of "GHC.Generic", with +@SpecialDiffError a = DiffErrorNested xss@. + +For example, say we want to implement 'SpecialDiff' (and then 'Diff') for @Tree@ from @containers@. +We'd ideally like to use a 'SOP.Generic' instance, but we don't have one. Nevertheless we can fake one, +using 'G.Generic' from "GHC.Generics". + +@ +data Tree a = Node + { rootLabel :: a + , subForest :: [Tree a] + } + deriving ('G.Generic') + +instance ('Diff' a) => 'SpecialDiff' (Tree a) where + type 'SpecialDiffError' (Tree a) = 'DiffErrorNested' ('GCode' (Tree a)) + 'specialDiff' = 'gspecialDiffNested' + + 'renderSpecialDiffError' = 'diffErrorNestedDoc' + +instance ('Diff' a) => 'Diff' (Tree a) where + diff = 'diffWithSpecial' +@ +-} +gspecialDiffNested :: + forall a. + ( G.Generic a + , GFrom a + , GDatatypeInfo a + , All2 Diff (GCode a) + ) => + a -> + a -> + Maybe (DiffErrorNested (GCode a)) +gspecialDiffNested l r = gdiff' constructors differs (unSOP $ gfrom l) (unSOP $ gfrom r) + where + differs = unPOP $ hcpure (Proxy @Diff) (Differ diff) + constructors = constructorInfo $ gdatatypeInfo $ Proxy @a + ------------------------------------------------------------ -- Auxiliary functions diff --git a/src/Generics/Diff/Instances.hs b/src/Generics/Diff/Instances.hs index d8bf42f..06fe0ce 100644 --- a/src/Generics/Diff/Instances.hs +++ b/src/Generics/Diff/Instances.hs @@ -41,6 +41,7 @@ import Data.Text.Encoding.Error (UnicodeException) import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy.Builder as TLB import Data.Type.Coercion +import Generics.Diff.Special.List () #if MIN_VERSION_base(4,16,0) import Data.Type.Ord #endif @@ -249,7 +250,7 @@ instance (Diff a) => Diff [a] where diff = diffList instance (Diff a) => Diff (NE.NonEmpty a) where - diff l r = diffListWith DiffNonEmpty diff (NE.toList l) (NE.toList r) + diff = diffWithSpecial -- combinators - typically we'll use gdiff diff --git a/src/Generics/Diff/Render.hs b/src/Generics/Diff/Render.hs index 8c4e935..d4dee01 100644 --- a/src/Generics/Diff/Render.hs +++ b/src/Generics/Diff/Render.hs @@ -22,14 +22,14 @@ module Generics.Diff.Render , renderDiffErrorWith , renderDiffErrorNested , renderDiffErrorNestedWith - , renderListDiffError - , renderListDiffErrorWith -- * Intermediate representation , Doc (..) , diffErrorDoc , renderDoc - , showR + , listDiffErrorDoc + , diffErrorNestedDoc + , showB , linesDoc , makeDoc ) @@ -42,19 +42,6 @@ import qualified Data.Text.Lazy.Builder as TB import qualified Data.Text.Lazy.IO as TL import Generics.Diff.Type import Generics.SOP as SOP -import Numeric.Natural - -{- | Configuration type used to tweak the output of 'renderDiffResultWith'. - -Use 'defaultRenderOpts' and the field accessors below to construct. --} -data RenderOpts = RenderOpts - { indentSize :: Natural - -- ^ How many spaces to indent each new "level" of comparison. - , numberedLevels :: Bool - -- ^ Whether or not to include level numbers in the output. - } - deriving (Show) -- | Sensible rendering defaults. No numbers, 2-space indentation. defaultRenderOpts :: RenderOpts @@ -97,32 +84,11 @@ renderDiffErrorNested = renderDiffErrorNestedWith defaultRenderOpts renderDiffErrorNestedWith :: RenderOpts -> DiffErrorNested xss -> TB.Builder renderDiffErrorNestedWith opts = renderDoc opts 0 . diffErrorNestedDoc --- | Render a 'ListDiffError' using a lazy 'TB.Builder'. -renderListDiffError :: ListDiffError xss -> TB.Builder -renderListDiffError = renderListDiffErrorWith defaultRenderOpts - --- | Render a 'ListDiffError' using a lazy 'TB.Builder', using custom 'RenderOpts'. -renderListDiffErrorWith :: RenderOpts -> ListDiffError xss -> TB.Builder -renderListDiffErrorWith opts = renderDoc opts 0 . listDiffErrorDoc "list" - ------------------------------------------------------------ -- Doc representation -- Rendering a 'DiffResult' happens in two steps: converting our strict SOP types into a much simpler -- intermediate representation, and then laying them out in a nice way. -{- | An intermediate representation for diff output. - -We constrain output to follow a very simple pattern: - -- 'docLines' is a non-empty series of preliminary lines describing the error. -- 'docSubDoc' is an optional 'Doc' representing a nested error, e.g. in 'FieldMismatch'. --} -data Doc = Doc - { docLines :: NonEmpty TB.Builder - , docSubDoc :: Maybe Doc - } - deriving (Show) - -- | Create a 'Doc' with a non-empty list of lines and a nested error. makeDoc :: NonEmpty TB.Builder -> DiffError a -> Doc makeDoc ls err = Doc ls (Just $ diffErrorDoc err) @@ -137,25 +103,45 @@ diffResultDoc = \case Error err -> diffErrorDoc err -- | Convert a 'DiffError' to a 'Doc'. -diffErrorDoc :: DiffError a -> Doc +diffErrorDoc :: forall a. DiffError a -> Doc diffErrorDoc = \case TopLevelNotEqual -> linesDoc (pure "Not equal") Nested err -> diffErrorNestedDoc err - DiffList listErr -> listDiffErrorDoc "list" listErr - DiffNonEmpty listErr -> listDiffErrorDoc "non-empty list" listErr + DiffSpecial err -> renderSpecialDiffError @a err + +{- | Convert a 'ListDiffError' to a 'Doc'. + +The first argument gives us a name for the type of list, for clearer output. +For example: + +@ +ghci> 'TL.putStrLn' . 'TB.toLazyText' . 'renderDoc' 'defaultRenderOpts' 0 . 'listDiffErrorDoc' "list" $ 'DiffAtIndex' 3 'TopLevelNotEqual' +Diff at list index 3 (0-indexed) + Not equal +ghci> TL.putStrLn . TB.toLazyText . renderDoc defaultRenderOpts 0 . listDiffErrorDoc "non-empty list" $ WrongLengths 3 5 +non-empty lists are wrong lengths +Length of left list: 3 +Length of right list: 5 +@ +-} listDiffErrorDoc :: TB.Builder -> ListDiffError a -> Doc listDiffErrorDoc lst = \case DiffAtIndex idx err -> - let lns = pure $ "Diff at " <> lst <> " index " <> showR idx <> " (0-indexed)" + let lns = pure $ "Diff at " <> lst <> " index " <> showB idx <> " (0-indexed)" in makeDoc lns err WrongLengths l r -> linesDoc $ - "Lists are wrong lengths" - :| [ "Length of left list: " <> showR l - , "Length of right list: " <> showR r + (lst <> "s are wrong lengths") + :| [ "Length of left list: " <> showB l + , "Length of right list: " <> showB r ] +{- | Convert a 'DiffErrorNested' to a 'Doc'. + +This is exported in the case that we want to implement an instance of 'Generics.Diff.Diff' for an existing type (e.g. +from a 3rd-party library) that does not have a 'SOP.Generic' instance. +-} diffErrorNestedDoc :: DiffErrorNested xss -> Doc diffErrorNestedDoc = \case WrongConstructor l r -> @@ -227,7 +213,7 @@ unpackAtLocErr cInfo nsErr = renderRField :: RField -> TB.Builder renderRField = \case - IdxField n -> "In field " <> showR n <> " (0-indexed)" + IdxField n -> "In field " <> showB n <> " (0-indexed)" InfixField side -> case side of ILeft -> "In the left-hand field" IRight -> "In the right-hand field" @@ -241,9 +227,9 @@ unlinesB (b : bs) = b <> TB.singleton '\n' <> unlinesB bs unlinesB [] = mempty -- | 'show' a value as a 'TB.Builder'. -showR :: (Show a) => a -> TB.Builder -showR = TB.fromString . show -{-# INLINE showR #-} +showB :: (Show a) => a -> TB.Builder +showB = TB.fromString . show +{-# INLINE showB #-} liftANS :: forall f g xs. (forall a. f a -> g a) -> NS f xs -> NS g xs liftANS f = go @@ -256,7 +242,7 @@ liftANS f = go mkIndent :: RenderOpts -> Bool -> Int -> TB.Builder mkIndent RenderOpts {..} isFirst ind = let spaces = TB.fromText (T.replicate (ind * fromIntegral indentSize) " ") - number = showR (ind + 1) <> ". " + number = showB (ind + 1) <> ". " noNumber = " " withNumber = spaces <> number diff --git a/src/Generics/Diff/Special.hs b/src/Generics/Diff/Special.hs new file mode 100644 index 0000000..83500ef --- /dev/null +++ b/src/Generics/Diff/Special.hs @@ -0,0 +1,86 @@ +{- | 'SpecialDiff' lets us define diff types for edge cases. For example, say we want to use +a type like 'ListDiffError' to diff lists in "one go", rather than recursing into a level of +SOP for each new element we examine. + +Let's take a look at the implementation for lists: + +@ +data 'ListDiffError' a + = 'DiffAtIndex' Int ('DiffError' a) -- there's a diff between two elements at this index + | 'WrongLengths' Int Int -- one list is a (strict) prefix of the other + +instance ('Generics.Diff.Diff' a) => 'SpecialDiff' [a] where + type 'SpecialDiffError' [a] = 'ListDiffError' a + 'specialDiff' = 'diffListWith' 'Generics.Diff.diff' + 'renderSpecialDiffError' = 'Generics.Diff.Render.listDiffErrorDoc' "list" + +'diffListWith' :: (a -> a -> 'DiffResult' a) -> [a] -> [a] -> Maybe ('ListDiffError' a) +'diffListWith' d = go 0 + where + -- we compare each element pairwise. + go :: + -- current index + Int -> + -- remaining input lists + [a] -> [a] -> + Maybe ('ListDiffError' a) + + -- base case: if we've reach the end of both lists, they're equal, return Nothing + go _ [] [] = Nothing + + -- if we reach the end of one list first, return a 'WrongLengths' + go n [] ys = Just $ 'WrongLengths' n (n + length ys) + go n xs [] = Just $ 'WrongLengths' (n + length xs) n + + -- recursive step: comparing the two head elements using the provider differ + go n (x : xs) (y : ys) = case d x y of + 'Equal' -> + -- the head elements are equal, recurse + go (n + 1) xs ys + 'Error' err -> + -- the head elements are not equal, return the error with the index + Just $ 'DiffAtIndex' n err + +-- To construct a 'Doc' we need some lines at the top, and optionally a sub-error. +'Generics.Diff.Render.listDiffErrorDoc' :: 'TB.Builder' -> 'ListDiffError' a -> 'Doc' +'Generics.Diff.Render.listDiffErrorDoc' lst = \case + 'DiffAtIndex' idx err -> + let + -- top line + lns = pure $ "Diff at " <> lst <> " index " <> 'Generics.Diff.Render.showB' idx <> " (0-indexed)" + in + -- 'Generics.Diff.Render.makeDoc' is a smart constructor for a 'Doc' with a sub error + 'Generics.Diff.Render.makeDoc' lns err + 'WrongLengths' l r -> + -- 'Generics.Diff.Render.linesDoc' is a smart constructor for a 'Doc' without a sub error + 'Generics.Diff.Render.linesDoc' $ + (lst <> "s are wrong lengths") + :| [ "Length of left list: " <> 'Generics.Diff.Render.showB' l + , "Length of right list: " <> 'Generics.Diff.Render.showB' r + ] +@ + +Note that 'diffListWith' and 'Generics.Diff.Render.listDiffErrorDoc' are exported functions, rather than +written inline, because there are other list-like types which will have almost identical instances and can +reuse the code. For example, the implementation of 'SpecialDiff' for 'NE.NonEmpty' lists is: + +@ +instance ('Generics.Diff.Diff' a) => 'SpecialDiff' ('NE.NonEmpty' a) where + type 'SpecialDiffError' ('NE.NonEmpty' a) = 'ListDiffError' a + 'specialDiff' l r = 'diffListWith' 'Generics.Diff.diff' ('NE.toList' l) ('NE.toList' r) + 'renderSpecialDiffError' = 'Generics.Diff.Render.listDiffErrorDoc' "non-empty list" +@ +-} +module Generics.Diff.Special + ( SpecialDiff (..) + , diffWithSpecial + , gspecialDiffNested + + -- * Lists + , module List + ) +where + +import Generics.Diff.Class +import Generics.Diff.Special.List as List +import Generics.Diff.Type diff --git a/src/Generics/Diff/Special/List.hs b/src/Generics/Diff/Special/List.hs new file mode 100644 index 0000000..8bbde4c --- /dev/null +++ b/src/Generics/Diff/Special/List.hs @@ -0,0 +1,21 @@ +{-# OPTIONS_GHC -Wno-orphans #-} + +{- | Diffs on lists as a special case. See "Generics.Diff.Special" for a detailed explanation +of the implementation. +-} +module Generics.Diff.Special.List + ( ListDiffError (..) + , diffListWith + ) +where + +import Data.Function (on) +import qualified Data.List.NonEmpty as NE +import Generics.Diff.Class +import Generics.Diff.Render +import Generics.Diff.Type + +instance (Diff a) => SpecialDiff (NE.NonEmpty a) where + type SpecialDiffError (NE.NonEmpty a) = ListDiffError a + specialDiff = diffListWith diff `on` NE.toList + renderSpecialDiffError = listDiffErrorDoc "non-empty list" diff --git a/src/Generics/Diff/Type.hs b/src/Generics/Diff/Type.hs index 43db7aa..6a1bd1a 100644 --- a/src/Generics/Diff/Type.hs +++ b/src/Generics/Diff/Type.hs @@ -2,9 +2,14 @@ module Generics.Diff.Type where -import Data.List.NonEmpty +import Data.List.NonEmpty (NonEmpty (..)) import Data.SOP.NP +import qualified Data.Text.Lazy.Builder as TB import Generics.SOP as SOP +import Numeric.Natural + +------------------------------------------------------------ +-- Types {- | 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 @@ -14,17 +19,16 @@ newtype Differ x = Differ (x -> x -> DiffResult x) {- | 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'. +The 'DiffSpecial' constructors for instances of 'SpecialDiff' are so that we can treat these types uniquely. +See 'SpecialDiff'. -} data DiffError a where -- | All we can say is that the values being compared are not equal. TopLevelNotEqual :: DiffError a -- | We've identified a diff at a certain constructor or field Nested :: DiffErrorNested (Code a) -> DiffError a - -- | Special case for lists - DiffList :: ListDiffError a -> DiffError [a] - -- | Special case for non-empty lists - DiffNonEmpty :: ListDiffError a -> DiffError (NonEmpty a) + -- | Special case for special cases + DiffSpecial :: (SpecialDiff a) => SpecialDiffError a -> DiffError a {- | If we did a normal 'Generics.Diff.gdiff' on a linked list, we'd have to recurse through one "level" of 'Generics.Diff.Diff's for each element of the input lists. The output would be really hard to read or understand. @@ -39,10 +43,6 @@ data ListDiffError a WrongLengths Int Int deriving (Show, Eq) -deriving instance (Show (DiffError a)) - -deriving instance (Eq (DiffError a)) - infixr 6 :*: -- | Lifted product of functors. We could have used 'Data.Functor.Product.Product', but this is more concise. @@ -73,9 +73,61 @@ of 'NS' gives us both of those things. -} newtype DiffAtField xss = DiffAtField (NS (ConstructorInfo :*: NS DiffError) xss) +------------------------------------------------------------ +-- Classes + +{- | Sometimes we want to diff types that don't quite fit the structor of a 'DiffErrorNested', +such as lists (see 'ListDiffError'), or even user-defined types that internally preserve invariants +or have unusual 'Eq' instances. In this case we can implement an instance of 'SpecialDiff' for the +type. +-} +class (Show (SpecialDiffError a), Eq (SpecialDiffError a)) => SpecialDiff a where + -- | A custom diff error type for the special case. + type SpecialDiffError a + + -- | Compare two values. The result will be converted to a 'DiffResult': 'Nothing' will result + -- in 'Equal', whereas a 'Just' result will be converted to a 'DiffError' using 'DiffSpecial'. + specialDiff :: a -> a -> Maybe (SpecialDiffError a) + + -- | As well as specifying how two diff two values, we also have to specify how to render + -- the output. See the helper functions in "Generics.Diff.Render". + renderSpecialDiffError :: SpecialDiffError a -> Doc + +------------------------------------------------------------ +-- Rendering + +{- | Configuration type used to tweak the output of 'Generics.Diff.Render.renderDiffResultWith'. + +Use 'Generics.Diff.Render.defaultRenderOpts' and the field accessors below to construct. +-} +data RenderOpts = RenderOpts + { indentSize :: Natural + -- ^ How many spaces to indent each new "level" of comparison. + , numberedLevels :: Bool + -- ^ Whether or not to include level numbers in the output. + } + deriving (Show) + +{- | An intermediate representation for diff output. + +We constrain output to follow a very simple pattern: + +- 'docLines' is a non-empty series of preliminary lines describing the error. +- 'docSubDoc' is an optional 'Doc' representing a nested error, e.g. in 'FieldMismatch'. +-} +data Doc = Doc + { docLines :: NonEmpty TB.Builder + , docSubDoc :: Maybe Doc + } + deriving (Show) + ------------------------------------------------------------ -- Instance madness +deriving instance (Show (DiffError a)) + +deriving instance (Eq (DiffError a)) + eqPair :: (f a -> f a -> Bool) -> (g a -> g a -> Bool) -> (f :*: g) a -> (f :*: g) a -> Bool eqPair onF onG (f1 :*: g1) (f2 :*: g2) = onF f1 f2 && onG g1 g2 diff --git a/test/Generics/Diff/UnitTestsSpec.hs b/test/Generics/Diff/UnitTestsSpec.hs index 287c877..71453a4 100644 --- a/test/Generics/Diff/UnitTestsSpec.hs +++ b/test/Generics/Diff/UnitTestsSpec.hs @@ -100,7 +100,7 @@ testSets = { setName = "Diff, FieldMismatch, Infix constructor, right side, nested" , leftValue = ('a', 5, ()) `Con3` [Just 1] , rightValue = ('a', 5, ()) `Con3` [Nothing, Just 1] - , expectedDiffResult = Error (Nested $ FieldMismatch (DiffAtField (S (S (Z (c3Info :*: S (Z $ DiffList (DiffAtIndex 0 (Nested (WrongConstructor (S (Z justInfo)) (Z nothingInfo))))))))))) + , expectedDiffResult = Error (Nested $ FieldMismatch (DiffAtField (S (S (Z (c3Info :*: S (Z $ DiffSpecial (DiffAtIndex 0 (Nested (WrongConstructor (S (Z justInfo)) (Z nothingInfo))))))))))) } , TestSet { setName = "Diff, FieldMismatch, Infix constructor, left side, nested"