predicate-typed-0.7.3.0: Predicates, Refinement types and Dsl

Safe HaskellNone
LanguageHaskell2010

Predicate.Data.Json

Description

promoted json encoding and decoding functions

Synopsis

Documentation

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 # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (ParseJson' t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseJson' t p) -> POpts -> x -> m (TT (PP (ParseJson' t p) x)) Source #

type PP (ParseJson' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (ParseJson' t p :: Type) x = PP t x

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"))
PresentT (10,"abc")
>>> pl @(ParseJson (Int,String) Id) "[10,\"abc\",99]"
Error ParseJson (Int,[Char])([10,"abc",...) Error in $ (Error in $: cannot unpack array of length 3 into a tuple of length 2 | [10,"abc",99])
FailT "ParseJson (Int,[Char])([10,\"abc\",...) Error in $"
>>> pl @(ParseJson (Int,Bool) (FromString _ Id)) ("[1,true]" :: String)
Present (1,True) (ParseJson (Int,Bool) (1,True))
PresentT (1,True)
>>> pl @(ParseJson (Int,Bool) Id) (A.encode (1,True))
Present (1,True) (ParseJson (Int,Bool) (1,True))
PresentT (1,True)
>>> pl @(ParseJson () Id) "[1,true]"
Error ParseJson ()([1,true]) Error in $ (Error in $: parsing () failed, expected an empty array | [1,true])
FailT "ParseJson ()([1,true]) Error in $"
Instances
P (ParseJsonT t p) x => P (ParseJson t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (ParseJson t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseJson t p) -> POpts -> x -> m (TT (PP (ParseJson t p) x)) Source #

type PP (ParseJson t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (ParseJson t p :: Type) x

data EncodeJson (pretty :: Bool) p Source #

encode json with pretty option

>>> pl @(EncodeJson 'False Id) (10,"def")
Present "[10,\"def\"]" (EncodeJson [10,"def"])
PresentT "[10,\"def\"]"
>>> pl @(EncodeJson 'False Id >> ParseJson (Int,Bool) Id) (1,True)
Present (1,True) ((>>) (1,True) | {ParseJson (Int,Bool) (1,True)})
PresentT (1,True)
Instances
(GetBool pretty, ToJSON (PP p x), P p x) => P (EncodeJson pretty p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (EncodeJson pretty p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (EncodeJson pretty p) -> POpts -> x -> m (TT (PP (EncodeJson pretty p) x)) Source #

type PP (EncodeJson pretty p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (EncodeJson pretty p :: Type) x = ByteString

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 # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (EncodeJsonFile pretty p q) x :: Type Source #

Methods

eval :: MonadEval m => proxy (EncodeJsonFile pretty p q) -> POpts -> x -> m (TT (PP (EncodeJsonFile pretty p q) x)) Source #

type PP (EncodeJsonFile pretty p q :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (EncodeJsonFile pretty p q :: Type) x = ()

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 # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (ParseJsonFile' t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseJsonFile' t p) -> POpts -> x -> m (TT (PP (ParseJsonFile' t p) x)) Source #

type PP (ParseJsonFile' t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (ParseJsonFile' t p :: Type) x = PP t x

data ParseJsonFile (t :: Type) p Source #

parse a json file 'p' using the type 't'

>>> pz @(ParseJsonFile [A.Value] "test1.json" >> Id !! 2) ()
PresentT (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 # 
Instance details

Defined in Predicate.Data.Json

Associated Types

type PP (ParseJsonFile t p) x :: Type Source #

Methods

eval :: MonadEval m => proxy (ParseJsonFile t p) -> POpts -> x -> m (TT (PP (ParseJsonFile t p) x)) Source #

type PP (ParseJsonFile t p :: Type) x Source # 
Instance details

Defined in Predicate.Data.Json

type PP (ParseJsonFile t p :: Type) x