deriving-aeson-0: Type driven generic aeson instance customisation
Safe HaskellNone
LanguageHaskell2010

Deriving.Aeson

Description

Type-directed aeson instance CustomJSONisation

Synopsis

Documentation

newtype CustomJSON t a Source #

A newtype wrapper which gives FromJSON/ToJSON instances with modified options.

Constructors

CustomJSON 

Fields

Instances

Instances details
(AesonOptions t, Generic a, GFromJSON Zero (Rep a)) => FromJSON (CustomJSON t a) Source # 
Instance details

Defined in Deriving.Aeson

Methods

parseJSON :: Value -> Parser (CustomJSON t a)

parseJSONList :: Value -> Parser [CustomJSON t a]

(AesonOptions t, Generic a, GToJSON Zero (Rep a)) => ToJSON (CustomJSON t a) Source # 
Instance details

Defined in Deriving.Aeson

Methods

toJSON :: CustomJSON t a -> Value

toEncoding :: CustomJSON t a -> Encoding

toJSONList :: [CustomJSON t a] -> Value

toEncodingList :: [CustomJSON t a] -> Encoding

data FieldLabelModifier t Source #

Function applied to field labels. Handy for removing common record prefixes for example.

Instances

Instances details
(StringModifier f, AesonOptions xs) => AesonOptions (FieldLabelModifier f ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

data ConstrctorTagModifier t Source #

Function applied to constructor tags which could be handy for lower-casing them for example.

Instances

Instances details
(StringModifier f, AesonOptions xs) => AesonOptions (ConstrctorTagModifier f ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

data OmitNothingFields Source #

Record fields with a Nothing value will be omitted from the resulting object.

Instances

Instances details
AesonOptions xs => AesonOptions (OmitNothingFields ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

data TagSingleConstructors Source #

Encode types with a single constructor as sums, so that allNullaryToStringTag and sumEncoding apply.

Instances

Instances details
AesonOptions xs => AesonOptions (TagSingleConstructors ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

data NoAllNullaryToStringTag Source #

the encoding will always follow the sumEncoding.

Instances

Instances details
AesonOptions xs => AesonOptions (NoAllNullaryToStringTag ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

Name modifiers

data StripPrefix t Source #

Strip prefix t. If it doesn't have the prefix, keep it as-is.

Instances

Instances details
KnownSymbol k => StringModifier (StripPrefix k :: Type) Source # 
Instance details

Defined in Deriving.Aeson

data CamelToKebab Source #

CamelCase to kebab-case

Instances

Instances details
StringModifier CamelToKebab Source # 
Instance details

Defined in Deriving.Aeson

data CamelToSnake Source #

CamelCase to snake_case

Instances

Instances details
StringModifier CamelToSnake Source # 
Instance details

Defined in Deriving.Aeson

Interface

class AesonOptions xs where Source #

Reify Options from a type-level list

Methods

aesonOptions :: Options Source #

Instances

Instances details
AesonOptions ('[] :: [k]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

AesonOptions xs => AesonOptions (NoAllNullaryToStringTag ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

AesonOptions xs => AesonOptions (TagSingleConstructors ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

AesonOptions xs => AesonOptions (OmitNothingFields ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

(StringModifier f, AesonOptions xs) => AesonOptions (ConstrctorTagModifier f ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

(StringModifier f, AesonOptions xs) => AesonOptions (FieldLabelModifier f ': xs :: [Type]) Source # 
Instance details

Defined in Deriving.Aeson

Methods

aesonOptions :: Options Source #

class StringModifier t where Source #

Reify a function which modifies names

Instances

Instances details
StringModifier CamelToKebab Source # 
Instance details

Defined in Deriving.Aeson

StringModifier CamelToSnake Source # 
Instance details

Defined in Deriving.Aeson

(StringModifier a, StringModifier b) => StringModifier ((a, b) :: Type) Source #

Left-to-right (flip .) composition

Instance details

Defined in Deriving.Aeson

KnownSymbol k => StringModifier (StripPrefix k :: Type) Source # 
Instance details

Defined in Deriving.Aeson

Reexports

class FromJSON a #

Instances

Instances details
FromJSON Bool 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Bool

parseJSONList :: Value -> Parser [Bool]

FromJSON Char 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Char

parseJSONList :: Value -> Parser [Char]

FromJSON Double 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Double

parseJSONList :: Value -> Parser [Double]

FromJSON Float 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Float

parseJSONList :: Value -> Parser [Float]

FromJSON Int 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int

parseJSONList :: Value -> Parser [Int]

FromJSON Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int8

parseJSONList :: Value -> Parser [Int8]

FromJSON Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int16

parseJSONList :: Value -> Parser [Int16]

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int32

parseJSONList :: Value -> Parser [Int32]

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int64

parseJSONList :: Value -> Parser [Int64]

FromJSON Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Integer

parseJSONList :: Value -> Parser [Integer]

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Natural

parseJSONList :: Value -> Parser [Natural]

FromJSON Ordering 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Ordering

parseJSONList :: Value -> Parser [Ordering]

FromJSON Word 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word

parseJSONList :: Value -> Parser [Word]

FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word8

parseJSONList :: Value -> Parser [Word8]

FromJSON Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word16

parseJSONList :: Value -> Parser [Word16]

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word32

parseJSONList :: Value -> Parser [Word32]

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word64

parseJSONList :: Value -> Parser [Word64]

FromJSON () 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser ()

parseJSONList :: Value -> Parser [()]

FromJSON Void 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Void

parseJSONList :: Value -> Parser [Void]

FromJSON Version 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Version

parseJSONList :: Value -> Parser [Version]

FromJSON CTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser CTime

parseJSONList :: Value -> Parser [CTime]

FromJSON IntSet 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser IntSet

parseJSONList :: Value -> Parser [IntSet]

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Text

parseJSONList :: Value -> Parser [Text]

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Text

parseJSONList :: Value -> Parser [Text]

FromJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser ZonedTime

parseJSONList :: Value -> Parser [ZonedTime]

FromJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser LocalTime

parseJSONList :: Value -> Parser [LocalTime]

FromJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser TimeOfDay

parseJSONList :: Value -> Parser [TimeOfDay]

FromJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser CalendarDiffTime

parseJSONList :: Value -> Parser [CalendarDiffTime]

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser UTCTime

parseJSONList :: Value -> Parser [UTCTime]

FromJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser SystemTime

parseJSONList :: Value -> Parser [SystemTime]

FromJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser NominalDiffTime

parseJSONList :: Value -> Parser [NominalDiffTime]

FromJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DiffTime

parseJSONList :: Value -> Parser [DiffTime]

FromJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DayOfWeek

parseJSONList :: Value -> Parser [DayOfWeek]

FromJSON Day 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Day

parseJSONList :: Value -> Parser [Day]

FromJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser CalendarDiffDays

parseJSONList :: Value -> Parser [CalendarDiffDays]

FromJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DotNetTime

parseJSONList :: Value -> Parser [DotNetTime]

FromJSON Value 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Value

parseJSONList :: Value -> Parser [Value]

FromJSON Scientific 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Scientific

parseJSONList :: Value -> Parser [Scientific]

FromJSON UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser UUID

parseJSONList :: Value -> Parser [UUID]

FromJSON a => FromJSON [a] 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser [a]

parseJSONList :: Value -> Parser [[a]]

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Maybe a)

parseJSONList :: Value -> Parser [Maybe a]

(FromJSON a, Integral a) => FromJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Ratio a)

parseJSONList :: Value -> Parser [Ratio a]

HasResolution a => FromJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Fixed a)

parseJSONList :: Value -> Parser [Fixed a]

FromJSON a => FromJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Min a)

parseJSONList :: Value -> Parser [Min a]

FromJSON a => FromJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Max a)

parseJSONList :: Value -> Parser [Max a]

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (First a)

parseJSONList :: Value -> Parser [First a]

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Last a)

parseJSONList :: Value -> Parser [Last a]

FromJSON a => FromJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (WrappedMonoid a)

parseJSONList :: Value -> Parser [WrappedMonoid a]

FromJSON a => FromJSON (Option a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Option a)

parseJSONList :: Value -> Parser [Option a]

FromJSON a => FromJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Identity a)

parseJSONList :: Value -> Parser [Identity a]

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (First a)

parseJSONList :: Value -> Parser [First a]

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Last a)

parseJSONList :: Value -> Parser [Last a]

FromJSON a => FromJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Dual a)

parseJSONList :: Value -> Parser [Dual a]

FromJSON a => FromJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (NonEmpty a)

parseJSONList :: Value -> Parser [NonEmpty a]

FromJSON a => FromJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (IntMap a)

parseJSONList :: Value -> Parser [IntMap a]

FromJSON v => FromJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Tree v)

parseJSONList :: Value -> Parser [Tree v]

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Seq a)

parseJSONList :: Value -> Parser [Seq a]

(Ord a, FromJSON a) => FromJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Set a)

parseJSONList :: Value -> Parser [Set a]

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a)

parseJSONList :: Value -> Parser [Vector a]

FromJSON a => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a)

parseJSONList :: Value -> Parser [Vector a]

FromJSON a => FromJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (DList a)

parseJSONList :: Value -> Parser [DList a]

(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (HashSet a)

parseJSONList :: Value -> Parser [HashSet a]

FromJSON a => FromJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Array a)

parseJSONList :: Value -> Parser [Array a]

(Prim a, FromJSON a) => FromJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (PrimArray a)

parseJSONList :: Value -> Parser [PrimArray a]

FromJSON a => FromJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (SmallArray a)

parseJSONList :: Value -> Parser [SmallArray a]

(Prim a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a)

parseJSONList :: Value -> Parser [Vector a]

(Storable a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a)

parseJSONList :: Value -> Parser [Vector a]

(FromJSON a, FromJSON b) => FromJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Either a b)

parseJSONList :: Value -> Parser [Either a b]

(FromJSON a, FromJSON b) => FromJSON (a, b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b)

parseJSONList :: Value -> Parser [(a, b)]

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Proxy a)

parseJSONList :: Value -> Parser [Proxy a]

(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Map k v)

parseJSONList :: Value -> Parser [Map k v]

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (HashMap k v)

parseJSONList :: Value -> Parser [HashMap k v]

(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c)

parseJSONList :: Value -> Parser [(a, b, c)]

FromJSON a => FromJSON (Const a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Const a b)

parseJSONList :: Value -> Parser [Const a b]

(AesonOptions t, Generic a, GFromJSON Zero (Rep a)) => FromJSON (CustomJSON t a) Source # 
Instance details

Defined in Deriving.Aeson

Methods

parseJSON :: Value -> Parser (CustomJSON t a)

parseJSONList :: Value -> Parser [CustomJSON t a]

FromJSON b => FromJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Tagged a b)

parseJSONList :: Value -> Parser [Tagged a b]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d)

parseJSONList :: Value -> Parser [(a, b, c, d)]

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Product f g a)

parseJSONList :: Value -> Parser [Product f g a]

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Sum f g a)

parseJSONList :: Value -> Parser [Sum f g a]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e)

parseJSONList :: Value -> Parser [(a, b, c, d, e)]

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Compose f g a)

parseJSONList :: Value -> Parser [Compose f g a]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)]

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)]

class ToJSON a #

Instances

Instances details
ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Bool -> Value

toEncoding :: Bool -> Encoding

toJSONList :: [Bool] -> Value

toEncodingList :: [Bool] -> Encoding

ToJSON Char 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Char -> Value

toEncoding :: Char -> Encoding

toJSONList :: [Char] -> Value

toEncodingList :: [Char] -> Encoding

ToJSON Double 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Double -> Value

toEncoding :: Double -> Encoding

toJSONList :: [Double] -> Value

toEncodingList :: [Double] -> Encoding

ToJSON Float 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Float -> Value

toEncoding :: Float -> Encoding

toJSONList :: [Float] -> Value

toEncodingList :: [Float] -> Encoding

ToJSON Int 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int -> Value

toEncoding :: Int -> Encoding

toJSONList :: [Int] -> Value

toEncodingList :: [Int] -> Encoding

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int8 -> Value

toEncoding :: Int8 -> Encoding

toJSONList :: [Int8] -> Value

toEncodingList :: [Int8] -> Encoding

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int16 -> Value

toEncoding :: Int16 -> Encoding

toJSONList :: [Int16] -> Value

toEncodingList :: [Int16] -> Encoding

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int32 -> Value

toEncoding :: Int32 -> Encoding

toJSONList :: [Int32] -> Value

toEncodingList :: [Int32] -> Encoding

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int64 -> Value

toEncoding :: Int64 -> Encoding

toJSONList :: [Int64] -> Value

toEncodingList :: [Int64] -> Encoding

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Integer -> Value

toEncoding :: Integer -> Encoding

toJSONList :: [Integer] -> Value

toEncodingList :: [Integer] -> Encoding

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Natural -> Value

toEncoding :: Natural -> Encoding

toJSONList :: [Natural] -> Value

toEncodingList :: [Natural] -> Encoding

ToJSON Ordering 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ordering -> Value

toEncoding :: Ordering -> Encoding

toJSONList :: [Ordering] -> Value

toEncodingList :: [Ordering] -> Encoding

ToJSON Word 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word -> Value

toEncoding :: Word -> Encoding

toJSONList :: [Word] -> Value

toEncodingList :: [Word] -> Encoding

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word8 -> Value

toEncoding :: Word8 -> Encoding

toJSONList :: [Word8] -> Value

toEncodingList :: [Word8] -> Encoding

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word16 -> Value

toEncoding :: Word16 -> Encoding

toJSONList :: [Word16] -> Value

toEncodingList :: [Word16] -> Encoding

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word32 -> Value

toEncoding :: Word32 -> Encoding

toJSONList :: [Word32] -> Value

toEncodingList :: [Word32] -> Encoding

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word64 -> Value

toEncoding :: Word64 -> Encoding

toJSONList :: [Word64] -> Value

toEncodingList :: [Word64] -> Encoding

ToJSON () 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: () -> Value

toEncoding :: () -> Encoding

toJSONList :: [()] -> Value

toEncodingList :: [()] -> Encoding

ToJSON Void 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Void -> Value

toEncoding :: Void -> Encoding

toJSONList :: [Void] -> Value

toEncodingList :: [Void] -> Encoding

ToJSON Version 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Version -> Value

toEncoding :: Version -> Encoding

toJSONList :: [Version] -> Value

toEncodingList :: [Version] -> Encoding

ToJSON CTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: CTime -> Value

toEncoding :: CTime -> Encoding

toJSONList :: [CTime] -> Value

toEncodingList :: [CTime] -> Encoding

ToJSON IntSet 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntSet -> Value

toEncoding :: IntSet -> Encoding

toJSONList :: [IntSet] -> Value

toEncodingList :: [IntSet] -> Encoding

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value

toEncoding :: Text -> Encoding

toJSONList :: [Text] -> Value

toEncodingList :: [Text] -> Encoding

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value

toEncoding :: Text -> Encoding

toJSONList :: [Text] -> Value

toEncodingList :: [Text] -> Encoding

ToJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: ZonedTime -> Value

toEncoding :: ZonedTime -> Encoding

toJSONList :: [ZonedTime] -> Value

toEncodingList :: [ZonedTime] -> Encoding

ToJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: LocalTime -> Value

toEncoding :: LocalTime -> Encoding

toJSONList :: [LocalTime] -> Value

toEncodingList :: [LocalTime] -> Encoding

ToJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: TimeOfDay -> Value

toEncoding :: TimeOfDay -> Encoding

toJSONList :: [TimeOfDay] -> Value

toEncodingList :: [TimeOfDay] -> Encoding

ToJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UTCTime -> Value

toEncoding :: UTCTime -> Encoding

toJSONList :: [UTCTime] -> Value

toEncodingList :: [UTCTime] -> Encoding

ToJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: SystemTime -> Value

toEncoding :: SystemTime -> Encoding

toJSONList :: [SystemTime] -> Value

toEncodingList :: [SystemTime] -> Encoding

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: NominalDiffTime -> Value

toEncoding :: NominalDiffTime -> Encoding

toJSONList :: [NominalDiffTime] -> Value

toEncodingList :: [NominalDiffTime] -> Encoding

ToJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DiffTime -> Value

toEncoding :: DiffTime -> Encoding

toJSONList :: [DiffTime] -> Value

toEncodingList :: [DiffTime] -> Encoding

ToJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DayOfWeek -> Value

toEncoding :: DayOfWeek -> Encoding

toJSONList :: [DayOfWeek] -> Value

toEncodingList :: [DayOfWeek] -> Encoding

ToJSON Day 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Day -> Value

toEncoding :: Day -> Encoding

toJSONList :: [Day] -> Value

toEncodingList :: [Day] -> Encoding

ToJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DotNetTime -> Value

toEncoding :: DotNetTime -> Encoding

toJSONList :: [DotNetTime] -> Value

toEncodingList :: [DotNetTime] -> Encoding

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Value -> Value

toEncoding :: Value -> Encoding

toJSONList :: [Value] -> Value

toEncodingList :: [Value] -> Encoding

ToJSON Number 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Number -> Value

toEncoding :: Number -> Encoding

toJSONList :: [Number] -> Value

toEncodingList :: [Number] -> Encoding

ToJSON Scientific 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Scientific -> Value

toEncoding :: Scientific -> Encoding

toJSONList :: [Scientific] -> Value

toEncodingList :: [Scientific] -> Encoding

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UUID -> Value

toEncoding :: UUID -> Encoding

toJSONList :: [UUID] -> Value

toEncodingList :: [UUID] -> Encoding

ToJSON a => ToJSON [a] 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value

toEncoding :: [a] -> Encoding

toJSONList :: [[a]] -> Value

toEncodingList :: [[a]] -> Encoding

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Maybe a -> Value

toEncoding :: Maybe a -> Encoding

toJSONList :: [Maybe a] -> Value

toEncodingList :: [Maybe a] -> Encoding

(ToJSON a, Integral a) => ToJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ratio a -> Value

toEncoding :: Ratio a -> Encoding

toJSONList :: [Ratio a] -> Value

toEncodingList :: [Ratio a] -> Encoding

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fixed a -> Value

toEncoding :: Fixed a -> Encoding

toJSONList :: [Fixed a] -> Value

toEncodingList :: [Fixed a] -> Encoding

ToJSON a => ToJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Min a -> Value

toEncoding :: Min a -> Encoding

toJSONList :: [Min a] -> Value

toEncodingList :: [Min a] -> Encoding

ToJSON a => ToJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Max a -> Value

toEncoding :: Max a -> Encoding

toJSONList :: [Max a] -> Value

toEncodingList :: [Max a] -> Encoding

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value

toEncoding :: First a -> Encoding

toJSONList :: [First a] -> Value

toEncodingList :: [First a] -> Encoding

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value

toEncoding :: Last a -> Encoding

toJSONList :: [Last a] -> Value

toEncodingList :: [Last a] -> Encoding

ToJSON a => ToJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: WrappedMonoid a -> Value

toEncoding :: WrappedMonoid a -> Encoding

toJSONList :: [WrappedMonoid a] -> Value

toEncodingList :: [WrappedMonoid a] -> Encoding

ToJSON a => ToJSON (Option a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Option a -> Value

toEncoding :: Option a -> Encoding

toJSONList :: [Option a] -> Value

toEncodingList :: [Option a] -> Encoding

ToJSON a => ToJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Identity a -> Value

toEncoding :: Identity a -> Encoding

toJSONList :: [Identity a] -> Value

toEncodingList :: [Identity a] -> Encoding

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value

toEncoding :: First a -> Encoding

toJSONList :: [First a] -> Value

toEncodingList :: [First a] -> Encoding

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value

toEncoding :: Last a -> Encoding

toJSONList :: [Last a] -> Value

toEncodingList :: [Last a] -> Encoding

ToJSON a => ToJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Dual a -> Value

toEncoding :: Dual a -> Encoding

toJSONList :: [Dual a] -> Value

toEncodingList :: [Dual a] -> Encoding

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: NonEmpty a -> Value

toEncoding :: NonEmpty a -> Encoding

toJSONList :: [NonEmpty a] -> Value

toEncodingList :: [NonEmpty a] -> Encoding

ToJSON a => ToJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntMap a -> Value

toEncoding :: IntMap a -> Encoding

toJSONList :: [IntMap a] -> Value

toEncodingList :: [IntMap a] -> Encoding

ToJSON v => ToJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tree v -> Value

toEncoding :: Tree v -> Encoding

toJSONList :: [Tree v] -> Value

toEncodingList :: [Tree v] -> Encoding

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value

toEncoding :: Seq a -> Encoding

toJSONList :: [Seq a] -> Value

toEncodingList :: [Seq a] -> Encoding

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value

toEncoding :: Set a -> Encoding

toJSONList :: [Set a] -> Value

toEncodingList :: [Set a] -> Encoding

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value

toEncoding :: Vector a -> Encoding

toJSONList :: [Vector a] -> Value

toEncodingList :: [Vector a] -> Encoding

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value

toEncoding :: Vector a -> Encoding

toJSONList :: [Vector a] -> Value

toEncodingList :: [Vector a] -> Encoding

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DList a -> Value

toEncoding :: DList a -> Encoding

toJSONList :: [DList a] -> Value

toEncodingList :: [DList a] -> Encoding

ToJSON a => ToJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashSet a -> Value

toEncoding :: HashSet a -> Encoding

toJSONList :: [HashSet a] -> Value

toEncodingList :: [HashSet a] -> Encoding

ToJSON a => ToJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Array a -> Value

toEncoding :: Array a -> Encoding

toJSONList :: [Array a] -> Value

toEncodingList :: [Array a] -> Encoding

(Prim a, ToJSON a) => ToJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: PrimArray a -> Value

toEncoding :: PrimArray a -> Encoding

toJSONList :: [PrimArray a] -> Value

toEncodingList :: [PrimArray a] -> Encoding

ToJSON a => ToJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: SmallArray a -> Value

toEncoding :: SmallArray a -> Encoding

toJSONList :: [SmallArray a] -> Value

toEncodingList :: [SmallArray a] -> Encoding

(Prim a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value

toEncoding :: Vector a -> Encoding

toJSONList :: [Vector a] -> Value

toEncodingList :: [Vector a] -> Encoding

(Storable a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value

toEncoding :: Vector a -> Encoding

toJSONList :: [Vector a] -> Value

toEncodingList :: [Vector a] -> Encoding

(ToJSON a, ToJSON b) => ToJSON (Either a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value

toEncoding :: Either a b -> Encoding

toJSONList :: [Either a b] -> Value

toEncodingList :: [Either a b] -> Encoding

(ToJSON a, ToJSON b) => ToJSON (a, b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b) -> Value

toEncoding :: (a, b) -> Encoding

toJSONList :: [(a, b)] -> Value

toEncodingList :: [(a, b)] -> Encoding

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Proxy a -> Value

toEncoding :: Proxy a -> Encoding

toJSONList :: [Proxy a] -> Value

toEncodingList :: [Proxy a] -> Encoding

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value

toEncoding :: Map k v -> Encoding

toJSONList :: [Map k v] -> Value

toEncodingList :: [Map k v] -> Encoding

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashMap k v -> Value

toEncoding :: HashMap k v -> Encoding

toJSONList :: [HashMap k v] -> Value

toEncodingList :: [HashMap k v] -> Encoding

(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c) -> Value

toEncoding :: (a, b, c) -> Encoding

toJSONList :: [(a, b, c)] -> Value

toEncodingList :: [(a, b, c)] -> Encoding

ToJSON a => ToJSON (Const a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Const a b -> Value

toEncoding :: Const a b -> Encoding

toJSONList :: [Const a b] -> Value

toEncodingList :: [Const a b] -> Encoding

(AesonOptions t, Generic a, GToJSON Zero (Rep a)) => ToJSON (CustomJSON t a) Source # 
Instance details

Defined in Deriving.Aeson

Methods

toJSON :: CustomJSON t a -> Value

toEncoding :: CustomJSON t a -> Encoding

toJSONList :: [CustomJSON t a] -> Value

toEncodingList :: [CustomJSON t a] -> Encoding

ToJSON b => ToJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tagged a b -> Value

toEncoding :: Tagged a b -> Encoding

toJSONList :: [Tagged a b] -> Value

toEncodingList :: [Tagged a b] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d) -> Value

toEncoding :: (a, b, c, d) -> Encoding

toJSONList :: [(a, b, c, d)] -> Value

toEncodingList :: [(a, b, c, d)] -> Encoding

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Product f g a -> Value

toEncoding :: Product f g a -> Encoding

toJSONList :: [Product f g a] -> Value

toEncodingList :: [Product f g a] -> Encoding

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Sum f g a -> Value

toEncoding :: Sum f g a -> Encoding

toJSONList :: [Sum f g a] -> Value

toEncodingList :: [Sum f g a] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e) -> Value

toEncoding :: (a, b, c, d, e) -> Encoding

toJSONList :: [(a, b, c, d, e)] -> Value

toEncodingList :: [(a, b, c, d, e)] -> Encoding

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Compose f g a -> Value

toEncoding :: Compose f g a -> Encoding

toJSONList :: [Compose f g a] -> Value

toEncodingList :: [Compose f g a] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f) -> Value

toEncoding :: (a, b, c, d, e, f) -> Encoding

toJSONList :: [(a, b, c, d, e, f)] -> Value

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value

toEncoding :: (a, b, c, d, e, f, g) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances

Instances details
Generic Bool

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic ()

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic Fixity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic SourceUnpackedness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic SourceStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic DecidedStrictness

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Value 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Generic [a]

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: Type -> Type #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: Type -> Type #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: Type -> Type #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Down a)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

from :: Down a -> Rep (Down a) x #

to :: Rep (Down a) x -> Down a #

Generic (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: Type -> Type #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Either a b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: Type -> Type #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: Type -> Type #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (a, b)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: Type -> Type #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (Rec1 f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: Type -> Type #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: Type -> Type #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: Type -> Type #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: Type -> Type #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: Type -> Type #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: Type -> Type #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (K1 i c p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: Type -> Type #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((f :+: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: Type -> Type #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((f :*: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: Type -> Type #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic (a, b, c, d)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: Type -> Type #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (M1 i c f p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: Type -> Type #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic ((f :.: g) p)

Since: base-4.7.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: Type -> Type #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c, d, e)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: Type -> Type #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #