Commit 7e4cff2c authored by Mael NICOLAS's avatar Mael NICOLAS

Added Arbitrary instance for ParseError

parent 9a19f5e0
{-# LANGUAGE NoImplicitPrelude #-}
module Parsers.Date where
import Gargantext.Prelude
import Test.Hspec
import Test.QuickCheck
import Parsers.Types
import Data.Either (Either(..))
import Data.Time (ZonedTime(..))
import Data.Text (pack, Text)
import Text.Parsec.Error (ParseError)
import Duckling.Time.Types (toRFC3339)
import Gargantext.Parsers.Date (fromRFC3339)
fromRFC3339Inv :: Either ParseError ZonedTime -> Text
fromRFC3339Inv (Right z) = toRFC3339 z
fromRFC3339Inv (Left pe) = panic . pack $ show pe
testFromRFC3339 :: IO ()
testFromRFC3339 = hspec $ do
describe "Test fromRFC3339: " $ do
it "is the inverse of Duckling's toRFC3339" $ property $
\x -> (fromRFC3339 . fromRFC3339Inv) x == (x :: Either ParseError ZonedTime)
{-# LANGUAGE NoImplicitPrelude #-}
module Parsers.Types where
import Gargantext.Prelude
import Test.QuickCheck
import Text.Parsec.Pos
import Text.Parsec.Error (ParseError(..), Message(..), newErrorMessage)
instance Arbitrary Message where
arbitrary = do
msgContent <- arbitrary
oneof $ return <$> [SysUnExpect msgContent
, UnExpect msgContent
, Expect msgContent
, Message msgContent
]
instance Arbitrary SourcePos where
arbitrary = do
sn <- arbitrary
l <- arbitrary
c <- arbitrary
return $ newPos sn l c
instance Arbitrary ParseError where
arbitrary = do
sp <- arbitrary
msg <- arbitrary
return $ newErrorMessage msg sp
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment