File tree Expand file tree Collapse file tree 3 files changed +15
-3
lines changed Expand file tree Collapse file tree 3 files changed +15
-3
lines changed Original file line number Diff line number Diff line change 1+ ## 0.3.3
2+
3+ - Change 'ediffGolden' so that parse errors in expected file don't cause the hard failure.
4+ This way you may ` --accept ` new results even when expected files are broken, e.g. due merge conflict markers.
5+ For now the change is a bit a hack to avoid breaking change in type-signature of ` ediffGolden/1 ` .
6+
17## 0.3.2
28
39- Add 'ediffGolden1', a variant of 'ediffGolden' with an additional argument.
Original file line number Diff line number Diff line change 1+ {-# LANGUAGE ScopedTypeVariables #-}
12-- | "Golden tests" using 'ediff' comparison.
23module Data.TreeDiff.Golden (
34 ediffGolden ,
@@ -50,20 +51,25 @@ ediffGolden impl testName fp x = ediffGolden1 impl' testName fp (\() -> x) where
5051-- @since 0.3.2
5152--
5253ediffGolden1
53- :: (Eq a , ToExpr a )
54+ :: forall a arg testName testTree . (Eq a , ToExpr a )
5455 => (testName -> IO Expr -> (arg -> IO Expr ) -> (Expr -> Expr -> IO (Maybe String )) -> (Expr -> IO () ) -> testTree ) -- ^ 'goldenTest'
5556 -> testName -- ^ test name
5657 -> FilePath -- ^ path to "golden file"
5758 -> (arg -> IO a ) -- ^ result value
5859 -> testTree
5960ediffGolden1 impl testName fp x = impl testName expect actual cmp wrt
6061 where
62+ actual :: arg -> IO Expr
6163 actual arg = fmap toExpr (x arg)
64+
65+ expect :: IO Expr
6266 expect = do
6367 contents <- BS. readFile fp
6468 case parse (exprParser <* eof) fp $ TE. decodeUtf8 contents of
65- Left err -> print err >> fail " parse error "
69+ Left err -> return $ App " ParseError " [toExpr fp, toExpr ( show err)]
6670 Right r -> return r
71+
72+ cmp :: Expr -> Expr -> IO (Maybe [Char ])
6773 cmp a b
6874 | a == b = return Nothing
6975 | otherwise = return $ Just $
Original file line number Diff line number Diff line change 11cabal-version : 2.2
22name : tree-diff
3- version : 0.3.2
3+ version : 0.3.3
44synopsis : Diffing of (expression) trees.
55category : Data, Testing
66description :
You can’t perform that action at this time.
0 commit comments