jordan-0.2.0.0: JSON with Structure
Safe HaskellNone
LanguageHaskell2010

Jordan.Generic.Options

Synopsis

Documentation

type Representational (f :: * -> *) = forall a b. Coercible a b => Coercible (f a) (f b) :: Constraint Source #

data SumTypeEncoding Source #

Constructors

TagVal 
TagInField 

Instances

Instances details
Bounded SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Enum SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Eq SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Ord SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Read SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Show SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Generic SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

Associated Types

type Rep SumTypeEncoding :: Type -> Type #

type Rep SumTypeEncoding Source # 
Instance details

Defined in Jordan.Generic.Options

type Rep SumTypeEncoding = D1 ('MetaData "SumTypeEncoding" "Jordan.Generic.Options" "jordan-0.2.0.0-inplace" 'False) (C1 ('MetaCons "TagVal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TagInField" 'PrefixI 'False) (U1 :: Type -> Type))

type family AllNullary cons where ... Source #

Equations

AllNullary (C1 ('MetaCons _ _ 'False) (S1 ('MetaSel 'Nothing _ _ _) U1)) = True 
AllNullary (a :+: b) = AllNullary a && AllNullary b 
AllNullary _ = False 

newtype PartOfSum f a Source #

Constructors

MkPartOfSum 

Fields

Instances

Instances details
(GFromJSON (PartOfSum l), GFromJSON (PartOfSum r)) => GFromJSON (PartOfSum (l :+: r)) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (PartOfSum (l :+: r) a) Source #

(GFromJSON (C1 t f), Constructor t) => GFromJSON (PartOfSum (C1 t f)) Source #

When rendering a sum type, if we have a more complex value (IE, maybe this is a constructor that takes arguments), we want to use whatever sum encoding was provided in the options.

Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f0 => FromJSONOptions -> f0 (PartOfSum (C1 t f) a) Source #

KnownSymbol connName => GFromJSON (PartOfSum (C1 ('MetaCons connName dontCare 'False) (U1 :: Type -> Type))) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

gFromJSON :: JSONParser f => FromJSONOptions -> f (PartOfSum (C1 ('MetaCons connName dontCare 'False) U1) a) Source #

(GToJSON (PartOfSum l), GToJSON (PartOfSum r)) => GToJSON (PartOfSum (l :+: r)) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (l :+: r) a) Source #

(Constructor t, GToJSON (C1 t f)) => GToJSON (PartOfSum (C1 t f)) Source #

When rendering a sum type, and this is NOT an enum value, render via the sum encoding option the user provided.

Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (C1 t f) a) Source #

KnownSymbol name => GToJSON (PartOfSum (C1 ('MetaCons name fixity 'False) (U1 :: Type -> Type))) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

gToJSON :: JSONSerializer s => ToJSONOptions -> s (PartOfSum (C1 ('MetaCons name fixity 'False) U1) a) Source #

Eq (f a) => Eq (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

(==) :: PartOfSum f a -> PartOfSum f a -> Bool #

(/=) :: PartOfSum f a -> PartOfSum f a -> Bool #

Ord (f a) => Ord (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

compare :: PartOfSum f a -> PartOfSum f a -> Ordering #

(<) :: PartOfSum f a -> PartOfSum f a -> Bool #

(<=) :: PartOfSum f a -> PartOfSum f a -> Bool #

(>) :: PartOfSum f a -> PartOfSum f a -> Bool #

(>=) :: PartOfSum f a -> PartOfSum f a -> Bool #

max :: PartOfSum f a -> PartOfSum f a -> PartOfSum f a #

min :: PartOfSum f a -> PartOfSum f a -> PartOfSum f a #

Read (f a) => Read (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

Show (f a) => Show (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

showsPrec :: Int -> PartOfSum f a -> ShowS #

show :: PartOfSum f a -> String #

showList :: [PartOfSum f a] -> ShowS #

Generic (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

Associated Types

type Rep (PartOfSum f a) :: Type -> Type #

Methods

from :: PartOfSum f a -> Rep (PartOfSum f a) x #

to :: Rep (PartOfSum f a) x -> PartOfSum f a #

type Rep (PartOfSum f a) Source # 
Instance details

Defined in Jordan.Generic.Options

type Rep (PartOfSum f a) = D1 ('MetaData "PartOfSum" "Jordan.Generic.Options" "jordan-0.2.0.0-inplace" 'True) (C1 ('MetaCons "MkPartOfSum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getPartOfSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))

newtype WithOptions (options :: [*]) a Source #

A newtype wrapper, designed to make it easier to derive ToJSON and FromJSON instances. The API of abstract JSON serializing is awkward due to the somewhat bad ergonomics of the Divisible and (especially) Decidable typeclasses.

In general, using -XDerivingVia , -XDeriveGeneric , -XDataKinds and this wrapper will make your life much easier. Unfortunately, due to a weird GHC quirk, you also need -XDerivingVia .

That is, the following won't work, complaining about role errors:

 data PersonFilter = PersonFilter { filterFirstName :: Maybe Text, filterLastName :: Maybe Text }
   deriving (Show, Generic)
   deriving (ToJSON, FromJSON) via (WithOptions '[KeepNothingFields] PersonFilter)

But this will:

 data PersonFilter = PersonFilter { filterFirstName :: Maybe Text, filterLastName :: Maybe Text }
   deriving (Show, Generic)

 deriving via (WithOptions '[KeepNothingFields] PersonFilter) instance (ToJSON PersonFilter)
 deriving via (WithOptions '[KeepNothingFields] PersonFilter) instance (FromJSON PersonFilter)

Constructors

WithOptions 

Fields

Instances

Instances details
Eq a => Eq (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

(==) :: WithOptions options a -> WithOptions options a -> Bool #

(/=) :: WithOptions options a -> WithOptions options a -> Bool #

Ord a => Ord (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

compare :: WithOptions options a -> WithOptions options a -> Ordering #

(<) :: WithOptions options a -> WithOptions options a -> Bool #

(<=) :: WithOptions options a -> WithOptions options a -> Bool #

(>) :: WithOptions options a -> WithOptions options a -> Bool #

(>=) :: WithOptions options a -> WithOptions options a -> Bool #

max :: WithOptions options a -> WithOptions options a -> WithOptions options a #

min :: WithOptions options a -> WithOptions options a -> WithOptions options a #

Show a => Show (WithOptions options a) Source # 
Instance details

Defined in Jordan.Generic.Options

Methods

showsPrec :: Int -> WithOptions options a -> ShowS #

show :: WithOptions options a -> String #

showList :: [WithOptions options a] -> ShowS #

(Generic a, GFromJSON (Rep a), Typeable a, SpecifiesFromJSONOptions options) => FromJSON (WithOptions options a) Source # 
Instance details

Defined in Jordan.FromJSON.Class

Methods

fromJSON :: JSONParser f => f (WithOptions options a) Source #

(Generic a, GToJSON (Rep a), Typeable a, SpecifiesToJSONOptions options) => ToJSON (WithOptions options a) Source # 
Instance details

Defined in Jordan.ToJSON.Class

Methods

toJSON :: JSONSerializer f => f (WithOptions options a) Source #

data OmitNothingFields Source #

Newtype for use with GeneralizedNewtypeDeriving. Will have us omit Nothing fields for parsing and serializing.

Constructors

OmitNothingFields 

data KeepNothingFields Source #

Keep nothing fields. Will have us omit null when serializing Maybe types.

Constructors

KeepNothingFields