lib: move assertParseEqual' (#812)
This commit is contained in:
		
							parent
							
								
									ebe2d52965
								
							
						
					
					
						commit
						321635274c
					
				| @ -500,16 +500,6 @@ spaceandamountormissingp = | ||||
|     lift $ skipSome spacenonewline | ||||
|     Mixed . (:[]) <$> amountp | ||||
| 
 | ||||
| assertParseEqual' :: | ||||
|      (Show a, Eq a) | ||||
|   => Identity (Either (ParseError Char CustomErr) a) | ||||
|   -> a | ||||
|   -> Assertion | ||||
| assertParseEqual' parse expected = either (assertFailure.show) (`is'` expected) (runIdentity parse) | ||||
| 
 | ||||
| is' :: (Eq a, Show a) => a -> a -> Assertion | ||||
| a `is'` e = assertEqual "values are equal" e a | ||||
| 
 | ||||
| test_spaceandamountormissingp = TestCase $ do | ||||
|     assertParseEqual' (parseWithState mempty spaceandamountormissingp " $47.18") (Mixed [usd 47.18]) | ||||
|     assertParseEqual' (parseWithState mempty spaceandamountormissingp "$47.18") missingmixedamt | ||||
|  | ||||
| @ -1,5 +1,6 @@ | ||||
| module Hledger.Utils.Test where | ||||
| 
 | ||||
| import Data.Functor.Identity | ||||
| import Test.HUnit | ||||
| import Text.Megaparsec | ||||
| 
 | ||||
| @ -22,7 +23,7 @@ filterTests _ t = t | ||||
| 
 | ||||
| -- | Simple way to assert something is some expected value, with no label. | ||||
| is :: (Eq a, Show a) => a -> a -> Assertion | ||||
| a `is` e = assertEqual "" e a | ||||
| a `is` e = assertEqual "" e a  -- XXX should it have a message ? | ||||
| 
 | ||||
| -- | Assert a parse result is successful, printing the parse error on failure. | ||||
| assertParse :: (Show t, Show e) => (Either (ParseError t e) a) -> Assertion | ||||
| @ -37,6 +38,11 @@ assertParseFailure parse = either (const $ return ()) (const $ assertFailure "pa | ||||
| assertParseEqual :: (Show a, Eq a, Show t, Show e) => (Either (ParseError t e) a) -> a -> Assertion | ||||
| assertParseEqual parse expected = either (assertFailure.show) (`is` expected) parse | ||||
| 
 | ||||
| -- | Assert that the parse result returned from an identity monad is some expected value,  | ||||
| -- printing the parse error on failure. | ||||
| assertParseEqual' :: (Show a, Eq a, Show t, Show e) => Identity (Either (ParseError t e) a) -> a -> Assertion | ||||
| assertParseEqual' parse expected = either (assertFailure.show) (`is` expected) (runIdentity parse) | ||||
| 
 | ||||
| printParseError :: (Show a) => a -> IO () | ||||
| printParseError e = do putStr "parse error at "; print e | ||||
| 
 | ||||
|  | ||||
		Loading…
	
		Reference in New Issue
	
	Block a user