generic-diff
Safe HaskellSafe-Inferred
LanguageHaskell2010

Generics.Diff.Special

Contents

Description

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 (Diff a) => SpecialDiff [a] where
  type SpecialDiffError [a] = ListDiffError a
  specialDiff = diffListWith diff
  renderSpecialDiffError = 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.
listDiffErrorDoc :: Builder -> ListDiffError a -> Doc
listDiffErrorDoc lst = case
  DiffAtIndex idx err ->
    let
      -- top line
      lns = pure $ "Diff at " <> lst <> " index " <> showB idx <> " (0-indexed)"
    in
      -- makeDoc is a smart constructor for a Doc with a sub error
      makeDoc lns err
  WrongLengths l r ->
      -- linesDoc is a smart constructor for a Doc without a sub error
    linesDoc $
      (lst <> "s are wrong lengths")
        :| [ "Length of left list: " <> showB l
           , "Length of right list: " <> showB r
           ]

Note that diffListWith and 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 NonEmpty lists is:

instance (Diff a) => SpecialDiff (NonEmpty a) where
  type SpecialDiffError (NonEmpty a) = ListDiffError a
  specialDiff l r = diffListWith diff (toList l) (toList r)
  renderSpecialDiffError = listDiffErrorDoc "non-empty list"
Synopsis

Documentation

class (Show (SpecialDiffError a), Eq (SpecialDiffError a)) => SpecialDiff a where Source #

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.

For concrete examples implementing SpecialDiff on types from "containers", see the examples/containers-instances directory.

Associated Types

type SpecialDiffError a Source #

A custom diff error type for the special case.

Methods

specialDiff :: a -> a -> Maybe (SpecialDiffError a) Source #

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.

renderSpecialDiffError :: SpecialDiffError a -> Doc Source #

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.

Instances

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

Defined in Generics.Diff.Special.List

Associated Types

type SpecialDiffError (NonEmpty a) Source #

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

Defined in Generics.Diff.Class

Associated Types

type SpecialDiffError [a] Source #

diffWithSpecial :: SpecialDiff a => a -> a -> DiffResult a Source #

When we have an instance of SpecialDiff, we can implement diff using DiffSpecial.

gspecialDiffNested :: forall a. (Generic a, GFrom a, GDatatypeInfo a, All2 Diff (GCode a)) => a -> a -> Maybe (DiffErrorNested (GCode a)) Source #

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 Generic instance, but we don't have one. Nevertheless we can fake one, using Generic from GHC.Generics.

data Tree a = Node
  { rootLabel :: a
  , subForest :: [Tree a]
  }
  deriving (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

Lists