Fix diff so that an empty list is equal to itself (#740)

* Test with QuickCheck that an expression is always the same as itself

I noticed cases where the diffing code returns that an expression is not the
same as itself (for example, an empty list). This commit adds a QuickCheck test
to illustrate it, and maybe other cases.

Sadly, I had to expose some internals from Dhall.Diff for the test, which makes
the interface less nice.

* Fix diff so that an empty list is the same as itself
This commit is contained in:
Georges Dubus 2018-12-07 18:07:47 +01:00 committed by Gabriel Gonzalez
parent cf69f5a953
commit f308ca29b0
2 changed files with 20 additions and 3 deletions

View File

@ -11,7 +11,9 @@
module Dhall.Diff (
-- * Diff
diffNormalized
Diff (..)
, diffExpression
, diffNormalized
, Dhall.Diff.diff
) where
@ -362,7 +364,7 @@ diffList l r
| allDifferent parts = difference listSkeleton listSkeleton
| otherwise = bracketed (foldMap diffPart parts)
where
allDifferent = not . any isBoth
allDifferent = any (not . isBoth)
-- Sections of the list that are only in left, only in right, or in both
parts =

View File

@ -8,6 +8,7 @@ module Dhall.Test.QuickCheck where
import Codec.Serialise (DeserialiseFailure(..))
import Control.Monad (guard)
import Data.Either (isRight)
import Data.List.NonEmpty (NonEmpty(..))
import Dhall.Map (Map)
import Dhall.Core
@ -29,7 +30,7 @@ import Dhall.Core
import Dhall.Set (Set)
import Numeric.Natural (Natural)
import Test.QuickCheck
(Arbitrary(..), Gen, Property, genericShrink, (===))
(Arbitrary(..), Gen, Property, genericShrink, (===), (==>))
import Test.QuickCheck.Instances ()
import Test.Tasty (TestTree)
@ -39,7 +40,9 @@ import qualified Dhall.Map
import qualified Data.Sequence
import qualified Dhall.Binary
import qualified Dhall.Core
import qualified Dhall.Diff
import qualified Dhall.Set
import qualified Dhall.TypeCheck
import qualified Test.QuickCheck
import qualified Test.Tasty.QuickCheck
@ -350,6 +353,14 @@ isNormalizedIsConsistentWithNormalize expression =
Dhall.Core.isNormalized expression
=== (Dhall.Core.normalize expression == expression)
isSameAsSelf :: Expr () Import -> Property
isSameAsSelf expression =
hasNoImportAndTypechecks ==> Dhall.Diff.same (Dhall.Diff.diffExpression expression expression)
where hasNoImportAndTypechecks =
case traverse (\_ -> Left ()) expression of
Right importlessExpression -> isRight (Dhall.TypeCheck.typeOf importlessExpression)
Left _ -> False
tests :: TestTree
tests =
Test.Tasty.QuickCheck.testProperties
@ -361,4 +372,8 @@ tests =
, Test.QuickCheck.property
(Test.QuickCheck.withMaxSuccess 10000 isNormalizedIsConsistentWithNormalize)
)
, ( "An expression should have no difference with itself"
, Test.QuickCheck.property
(Test.QuickCheck.withMaxSuccess 10000 isSameAsSelf)
)
]