module Test.Aeson.Internal.Utils where
import Control.Exception
import Data.Aeson
import Data.ByteString.Lazy (ByteString)
import Data.Proxy
import Prelude
import Test.Hspec
import Test.QuickCheck
data Settings = Settings {
goldenDirectoryOption :: GoldenDirectoryOption
, useModuleNameAsSubDirectory :: Bool
, sampleSize :: Int
}
data GoldenDirectoryOption = CustomDirectoryName String | GoldenDirectory
defaultSettings :: Settings
defaultSettings = Settings GoldenDirectory False 5
addBrackets :: String -> String
addBrackets s =
if ' ' `elem` s
then "(" ++ s ++ ")"
else s
shouldBeIdentity :: (Eq a, Show a, Arbitrary a) =>
Proxy a -> (a -> IO a) -> Property
shouldBeIdentity Proxy function =
property $ \ (a :: a) -> function a `shouldReturn` a
checkAesonEncodingEquality :: forall a . (ToJSON a, FromJSON a) => JsonShow a -> Bool
checkAesonEncodingEquality (JsonShow a) =
let byteStrA = encode a
decodedVal = (eitherDecode byteStrA) :: Either String a
eitherByteStrB = encode <$> decodedVal
in (Right byteStrA) == eitherByteStrB
aesonDecodeIO :: FromJSON a => ByteString -> IO a
aesonDecodeIO bs = case eitherDecode bs of
Right a -> return a
Left msg -> throwIO $ ErrorCall
("aeson couldn't parse value: " ++ msg)
newtype JsonShow a = JsonShow a
instance ToJSON a => Show (JsonShow a ) where
show (JsonShow v) = show . encode $ v
instance ToJSON a => ToJSON (JsonShow a) where
toJSON (JsonShow a) = toJSON a
instance FromJSON a => FromJSON (JsonShow a) where
parseJSON v = JsonShow <$> (parseJSON v)
instance Arbitrary a => Arbitrary (JsonShow a) where
arbitrary = JsonShow <$> arbitrary