Safe Haskell | None |
---|---|
Language | Haskell2010 |
promoted json encoding and decoding functions
Synopsis
- data ParseJson' t p
- data ParseJson (t :: Type) p
- data ParseJsonFile' t p
- data ParseJsonFile (t :: Type) p
- data EncodeJson (pretty :: Bool) p
- data EncodeJsonFile (pretty :: Bool) p q
parse
data ParseJson' t p Source #
parse json data using the type t
Instances
(P p x, PP p x ~ ByteString, Typeable (PP t x), Show (PP t x), FromJSON (PP t x)) => P (ParseJson' t p :: Type) x Source # | |
Defined in Predicate.Data.Json type PP (ParseJson' t p) x Source # eval :: MonadEval m => proxy (ParseJson' t p) -> POpts -> x -> m (TT (PP (ParseJson' t p) x)) Source # | |
Show (ParseJson' t p) Source # | |
Defined in Predicate.Data.Json showsPrec :: Int -> ParseJson' t p -> ShowS # show :: ParseJson' t p -> String # showList :: [ParseJson' t p] -> ShowS # | |
type PP (ParseJson' t p :: Type) x Source # | |
Defined in Predicate.Data.Json |
data ParseJson (t :: Type) p Source #
parse json data using the type t
>>>
pl @(ParseJson (Int,String) Id) "[10,\"abc\"]"
Present (10,"abc") (ParseJson (Int,[Char]) (10,"abc")) Val (10,"abc")
>>>
pl @(ParseJson (Int,String) Id) "[10,\"abc\",99]"
Error ParseJson (Int,[Char])([10,"abc",99]) Error in $: cannot unpack array of length 3 into a tuple of length 2 ([10,"abc",99]) Fail "ParseJson (Int,[Char])([10,\"abc\",99]) Error in $: cannot unpack array of length 3 into a tuple of length 2"
>>>
pl @(ParseJson (Int,Bool) (FromString _ Id)) "[1,true]"
Present (1,True) (ParseJson (Int,Bool) (1,True)) Val (1,True)
>>>
pl @(ParseJson (Int,Bool) Id) (A.encode (1,True))
Present (1,True) (ParseJson (Int,Bool) (1,True)) Val (1,True)
>>>
pl @(ParseJson () Id) "[1,true]"
Error ParseJson ()([1,true]) Error in $: parsing () failed, expected an empty array ([1,true]) Fail "ParseJson ()([1,true]) Error in $: parsing () failed, expected an empty array"
data ParseJsonFile' t p Source #
parse json file p
using the type t
Instances
(P p x, PP p x ~ String, Typeable (PP t x), Show (PP t x), FromJSON (PP t x)) => P (ParseJsonFile' t p :: Type) x Source # | |
Defined in Predicate.Data.Json type PP (ParseJsonFile' t p) x Source # eval :: MonadEval m => proxy (ParseJsonFile' t p) -> POpts -> x -> m (TT (PP (ParseJsonFile' t p) x)) Source # | |
Show (ParseJsonFile' t p) Source # | |
Defined in Predicate.Data.Json showsPrec :: Int -> ParseJsonFile' t p -> ShowS # show :: ParseJsonFile' t p -> String # showList :: [ParseJsonFile' t p] -> ShowS # | |
type PP (ParseJsonFile' t p :: Type) x Source # | |
Defined in Predicate.Data.Json |
data ParseJsonFile (t :: Type) p Source #
parse a json file p
using the type t
>>>
pz @(ParseJsonFile [A.Value] "test1.json" >> Id !! 2) ()
Val (Object (fromList [("lastName",String "Doe"),("age",Number 45.0),("firstName",String "John"),("likesPizza",Bool False)]))
Instances
P (ParseJsonFileT t p) x => P (ParseJsonFile t p :: Type) x Source # | |
Defined in Predicate.Data.Json type PP (ParseJsonFile t p) x Source # eval :: MonadEval m => proxy (ParseJsonFile t p) -> POpts -> x -> m (TT (PP (ParseJsonFile t p) x)) Source # | |
Show (ParseJsonFile t p) Source # | |
Defined in Predicate.Data.Json showsPrec :: Int -> ParseJsonFile t p -> ShowS # show :: ParseJsonFile t p -> String # showList :: [ParseJsonFile t p] -> ShowS # | |
type PP (ParseJsonFile t p :: Type) x Source # | |
Defined in Predicate.Data.Json |
encode
data EncodeJson (pretty :: Bool) p Source #
encode json with pretty option
>>>
pl @(EncodeJson 'False Id) (10,"def")
Present "[10,\"def\"]" (EncodeJson [10,"def"]) Val "[10,\"def\"]"
>>>
pl @(EncodeJson 'False Id >> ParseJson (Int,Bool) Id) (1,True)
Present (1,True) ((>>) (1,True) | {ParseJson (Int,Bool) (1,True)}) Val (1,True)
Instances
(GetBool pretty, ToJSON (PP p x), P p x) => P (EncodeJson pretty p :: Type) x Source # | |
Defined in Predicate.Data.Json type PP (EncodeJson pretty p) x Source # eval :: MonadEval m => proxy (EncodeJson pretty p) -> POpts -> x -> m (TT (PP (EncodeJson pretty p) x)) Source # | |
Show (EncodeJson pretty p) Source # | |
Defined in Predicate.Data.Json showsPrec :: Int -> EncodeJson pretty p -> ShowS # show :: EncodeJson pretty p -> String # showList :: [EncodeJson pretty p] -> ShowS # | |
type PP (EncodeJson pretty p :: Type) x Source # | |
Defined in Predicate.Data.Json |
data EncodeJsonFile (pretty :: Bool) p q Source #
encode a json file with pretty option
Instances
(GetBool pretty, PP p x ~ String, P p x, ToJSON (PP q x), P q x) => P (EncodeJsonFile pretty p q :: Type) x Source # | |
Defined in Predicate.Data.Json type PP (EncodeJsonFile pretty p q) x Source # eval :: MonadEval m => proxy (EncodeJsonFile pretty p q) -> POpts -> x -> m (TT (PP (EncodeJsonFile pretty p q) x)) Source # | |
Show (EncodeJsonFile pretty p q) Source # | |
Defined in Predicate.Data.Json showsPrec :: Int -> EncodeJsonFile pretty p q -> ShowS # show :: EncodeJsonFile pretty p q -> String # showList :: [EncodeJsonFile pretty p q] -> ShowS # | |
type PP (EncodeJsonFile pretty p q :: Type) x Source # | |
Defined in Predicate.Data.Json |