{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveLift #-}
{-# OPTIONS_GHC -Wno-partial-fields #-}
module TreeSitter.Deserialize
( Datatype (..)
, Field (..)
, Children(..)
, Required (..)
, Type (..)
, DatatypeName (..)
, Named (..)
, Multiple (..)
) where
import Data.Aeson as Aeson
import Data.Aeson.Types
import Data.Char
import GHC.Generics hiding (Constructor, Datatype)
import Language.Haskell.TH.Syntax (Lift)
import Data.Text (Text, unpack)
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.HashMap.Strict as HM
import Data.Maybe (fromMaybe)
data Datatype
  = SumType
  { Datatype -> DatatypeName
datatypeName       :: DatatypeName
  , Datatype -> Named
datatypeNameStatus :: Named
  , Datatype -> NonEmpty Type
datatypeSubtypes   :: NonEmpty Type
  }
  | ProductType
  { datatypeName       :: DatatypeName
  , datatypeNameStatus :: Named
  , Datatype -> Maybe Children
datatypeChildren   :: Maybe Children
  , Datatype -> [(String, Field)]
datatypeFields     :: [(String, Field)]
  }
  | LeafType
  { datatypeName       :: DatatypeName
  , datatypeNameStatus :: Named
  }
  deriving (Datatype -> Datatype -> Bool
(Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool) -> Eq Datatype
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Datatype -> Datatype -> Bool
$c/= :: Datatype -> Datatype -> Bool
== :: Datatype -> Datatype -> Bool
$c== :: Datatype -> Datatype -> Bool
Eq, Eq Datatype
Eq Datatype =>
(Datatype -> Datatype -> Ordering)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Bool)
-> (Datatype -> Datatype -> Datatype)
-> (Datatype -> Datatype -> Datatype)
-> Ord Datatype
Datatype -> Datatype -> Bool
Datatype -> Datatype -> Ordering
Datatype -> Datatype -> Datatype
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Datatype -> Datatype -> Datatype
$cmin :: Datatype -> Datatype -> Datatype
max :: Datatype -> Datatype -> Datatype
$cmax :: Datatype -> Datatype -> Datatype
>= :: Datatype -> Datatype -> Bool
$c>= :: Datatype -> Datatype -> Bool
> :: Datatype -> Datatype -> Bool
$c> :: Datatype -> Datatype -> Bool
<= :: Datatype -> Datatype -> Bool
$c<= :: Datatype -> Datatype -> Bool
< :: Datatype -> Datatype -> Bool
$c< :: Datatype -> Datatype -> Bool
compare :: Datatype -> Datatype -> Ordering
$ccompare :: Datatype -> Datatype -> Ordering
$cp1Ord :: Eq Datatype
Ord, Int -> Datatype -> ShowS
[Datatype] -> ShowS
Datatype -> String
(Int -> Datatype -> ShowS)
-> (Datatype -> String) -> ([Datatype] -> ShowS) -> Show Datatype
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Datatype] -> ShowS
$cshowList :: [Datatype] -> ShowS
show :: Datatype -> String
$cshow :: Datatype -> String
showsPrec :: Int -> Datatype -> ShowS
$cshowsPrec :: Int -> Datatype -> ShowS
Show, (forall x. Datatype -> Rep Datatype x)
-> (forall x. Rep Datatype x -> Datatype) -> Generic Datatype
forall x. Rep Datatype x -> Datatype
forall x. Datatype -> Rep Datatype x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Datatype x -> Datatype
$cfrom :: forall x. Datatype -> Rep Datatype x
Generic, [Datatype] -> Encoding
[Datatype] -> Value
Datatype -> Encoding
Datatype -> Value
(Datatype -> Value)
-> (Datatype -> Encoding)
-> ([Datatype] -> Value)
-> ([Datatype] -> Encoding)
-> ToJSON Datatype
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Datatype] -> Encoding
$ctoEncodingList :: [Datatype] -> Encoding
toJSONList :: [Datatype] -> Value
$ctoJSONList :: [Datatype] -> Value
toEncoding :: Datatype -> Encoding
$ctoEncoding :: Datatype -> Encoding
toJSON :: Datatype -> Value
$ctoJSON :: Datatype -> Value
ToJSON)
instance FromJSON Datatype where
  parseJSON :: Value -> Parser Datatype
parseJSON = String -> (Object -> Parser Datatype) -> Value -> Parser Datatype
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject "Datatype" ((Object -> Parser Datatype) -> Value -> Parser Datatype)
-> (Object -> Parser Datatype) -> Value -> Parser Datatype
forall a b. (a -> b) -> a -> b
$ \v :: Object
v -> do
    DatatypeName
type' <- Object
v Object -> Text -> Parser DatatypeName
forall a. FromJSON a => Object -> Text -> Parser a
.: "type"
    Named
named <- Object
v Object -> Text -> Parser Named
forall a. FromJSON a => Object -> Text -> Parser a
.: "named"
    Maybe (NonEmpty Type)
subtypes <- Object
v Object -> Text -> Parser (Maybe (NonEmpty Type))
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "subtypes"
    case Maybe (NonEmpty Type)
subtypes of
      Nothing -> do
        Object
fields <- (Maybe Object -> Object) -> Parser (Maybe Object) -> Parser Object
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Object -> Maybe Object -> Object
forall a. a -> Maybe a -> a
fromMaybe Object
forall k v. HashMap k v
HM.empty) (Object
v Object -> Text -> Parser (Maybe Object)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "fields")
        Maybe Children
children <- Object
v Object -> Text -> Parser (Maybe Children)
forall a. FromJSON a => Object -> Text -> Parser (Maybe a)
.:? "children"
        if Object -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Object
fields Bool -> Bool -> Bool
&& Maybe Children -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null Maybe Children
children then
          Datatype -> Parser Datatype
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DatatypeName -> Named -> Datatype
LeafType DatatypeName
type' Named
named)
        else
          DatatypeName
-> Named -> Maybe Children -> [(String, Field)] -> Datatype
ProductType DatatypeName
type' Named
named Maybe Children
children ([(String, Field)] -> Datatype)
-> Parser [(String, Field)] -> Parser Datatype
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Value)] -> Parser [(String, Field)]
parseKVPairs (Object -> [(Text, Value)]
forall k v. HashMap k v -> [(k, v)]
HM.toList Object
fields)
      Just subtypes :: NonEmpty Type
subtypes   -> Datatype -> Parser Datatype
forall (f :: * -> *) a. Applicative f => a -> f a
pure (DatatypeName -> Named -> NonEmpty Type -> Datatype
SumType DatatypeName
type' Named
named NonEmpty Type
subtypes)
parseKVPairs :: [(Text, Value)] -> Parser [(String, Field)]
parseKVPairs :: [(Text, Value)] -> Parser [(String, Field)]
parseKVPairs = ((Text, Value) -> Parser (String, Field))
-> [(Text, Value)] -> Parser [(String, Field)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (Text, Value) -> Parser (String, Field)
go
  where go :: (Text, Value) -> Parser (String, Field)
        go :: (Text, Value) -> Parser (String, Field)
go (t :: Text
t,v :: Value
v) = do
          Field
v' <- Value -> Parser Field
forall a. FromJSON a => Value -> Parser a
parseJSON Value
v
          (String, Field) -> Parser (String, Field)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> String
unpack Text
t, Field
v')
data Field = MkField
  { Field -> Required
fieldRequired :: Required
  , Field -> NonEmpty Type
fieldTypes    :: NonEmpty Type
  , Field -> Multiple
fieldMultiple :: Multiple
  }
  deriving (Field -> Field -> Bool
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq, Eq Field
Eq Field =>
(Field -> Field -> Ordering)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Field)
-> (Field -> Field -> Field)
-> Ord Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmax :: Field -> Field -> Field
>= :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c< :: Field -> Field -> Bool
compare :: Field -> Field -> Ordering
$ccompare :: Field -> Field -> Ordering
$cp1Ord :: Eq Field
Ord, Int -> Field -> ShowS
[Field] -> ShowS
Field -> String
(Int -> Field -> ShowS)
-> (Field -> String) -> ([Field] -> ShowS) -> Show Field
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Field] -> ShowS
$cshowList :: [Field] -> ShowS
show :: Field -> String
$cshow :: Field -> String
showsPrec :: Int -> Field -> ShowS
$cshowsPrec :: Int -> Field -> ShowS
Show, (forall x. Field -> Rep Field x)
-> (forall x. Rep Field x -> Field) -> Generic Field
forall x. Rep Field x -> Field
forall x. Field -> Rep Field x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Field x -> Field
$cfrom :: forall x. Field -> Rep Field x
Generic, [Field] -> Encoding
[Field] -> Value
Field -> Encoding
Field -> Value
(Field -> Value)
-> (Field -> Encoding)
-> ([Field] -> Value)
-> ([Field] -> Encoding)
-> ToJSON Field
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Field] -> Encoding
$ctoEncodingList :: [Field] -> Encoding
toJSONList :: [Field] -> Value
$ctoJSONList :: [Field] -> Value
toEncoding :: Field -> Encoding
$ctoEncoding :: Field -> Encoding
toJSON :: Field -> Value
$ctoJSON :: Field -> Value
ToJSON)
instance FromJSON Field where
  parseJSON :: Value -> Parser Field
parseJSON = Options -> Value -> Parser Field
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
customOptions
newtype Children = MkChildren Field
  deriving (Children -> Children -> Bool
(Children -> Children -> Bool)
-> (Children -> Children -> Bool) -> Eq Children
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Children -> Children -> Bool
$c/= :: Children -> Children -> Bool
== :: Children -> Children -> Bool
$c== :: Children -> Children -> Bool
Eq, Eq Children
Eq Children =>
(Children -> Children -> Ordering)
-> (Children -> Children -> Bool)
-> (Children -> Children -> Bool)
-> (Children -> Children -> Bool)
-> (Children -> Children -> Bool)
-> (Children -> Children -> Children)
-> (Children -> Children -> Children)
-> Ord Children
Children -> Children -> Bool
Children -> Children -> Ordering
Children -> Children -> Children
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Children -> Children -> Children
$cmin :: Children -> Children -> Children
max :: Children -> Children -> Children
$cmax :: Children -> Children -> Children
>= :: Children -> Children -> Bool
$c>= :: Children -> Children -> Bool
> :: Children -> Children -> Bool
$c> :: Children -> Children -> Bool
<= :: Children -> Children -> Bool
$c<= :: Children -> Children -> Bool
< :: Children -> Children -> Bool
$c< :: Children -> Children -> Bool
compare :: Children -> Children -> Ordering
$ccompare :: Children -> Children -> Ordering
$cp1Ord :: Eq Children
Ord, Int -> Children -> ShowS
[Children] -> ShowS
Children -> String
(Int -> Children -> ShowS)
-> (Children -> String) -> ([Children] -> ShowS) -> Show Children
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Children] -> ShowS
$cshowList :: [Children] -> ShowS
show :: Children -> String
$cshow :: Children -> String
showsPrec :: Int -> Children -> ShowS
$cshowsPrec :: Int -> Children -> ShowS
Show, (forall x. Children -> Rep Children x)
-> (forall x. Rep Children x -> Children) -> Generic Children
forall x. Rep Children x -> Children
forall x. Children -> Rep Children x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Children x -> Children
$cfrom :: forall x. Children -> Rep Children x
Generic)
  deriving newtype ([Children] -> Encoding
[Children] -> Value
Children -> Encoding
Children -> Value
(Children -> Value)
-> (Children -> Encoding)
-> ([Children] -> Value)
-> ([Children] -> Encoding)
-> ToJSON Children
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Children] -> Encoding
$ctoEncodingList :: [Children] -> Encoding
toJSONList :: [Children] -> Value
$ctoJSONList :: [Children] -> Value
toEncoding :: Children -> Encoding
$ctoEncoding :: Children -> Encoding
toJSON :: Children -> Value
$ctoJSON :: Children -> Value
ToJSON, Value -> Parser [Children]
Value -> Parser Children
(Value -> Parser Children)
-> (Value -> Parser [Children]) -> FromJSON Children
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Children]
$cparseJSONList :: Value -> Parser [Children]
parseJSON :: Value -> Parser Children
$cparseJSON :: Value -> Parser Children
FromJSON)
data Required = Optional | Required
  deriving (Required -> Required -> Bool
(Required -> Required -> Bool)
-> (Required -> Required -> Bool) -> Eq Required
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Required -> Required -> Bool
$c/= :: Required -> Required -> Bool
== :: Required -> Required -> Bool
$c== :: Required -> Required -> Bool
Eq, Eq Required
Eq Required =>
(Required -> Required -> Ordering)
-> (Required -> Required -> Bool)
-> (Required -> Required -> Bool)
-> (Required -> Required -> Bool)
-> (Required -> Required -> Bool)
-> (Required -> Required -> Required)
-> (Required -> Required -> Required)
-> Ord Required
Required -> Required -> Bool
Required -> Required -> Ordering
Required -> Required -> Required
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Required -> Required -> Required
$cmin :: Required -> Required -> Required
max :: Required -> Required -> Required
$cmax :: Required -> Required -> Required
>= :: Required -> Required -> Bool
$c>= :: Required -> Required -> Bool
> :: Required -> Required -> Bool
$c> :: Required -> Required -> Bool
<= :: Required -> Required -> Bool
$c<= :: Required -> Required -> Bool
< :: Required -> Required -> Bool
$c< :: Required -> Required -> Bool
compare :: Required -> Required -> Ordering
$ccompare :: Required -> Required -> Ordering
$cp1Ord :: Eq Required
Ord, Int -> Required -> ShowS
[Required] -> ShowS
Required -> String
(Int -> Required -> ShowS)
-> (Required -> String) -> ([Required] -> ShowS) -> Show Required
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Required] -> ShowS
$cshowList :: [Required] -> ShowS
show :: Required -> String
$cshow :: Required -> String
showsPrec :: Int -> Required -> ShowS
$cshowsPrec :: Int -> Required -> ShowS
Show, (forall x. Required -> Rep Required x)
-> (forall x. Rep Required x -> Required) -> Generic Required
forall x. Rep Required x -> Required
forall x. Required -> Rep Required x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Required x -> Required
$cfrom :: forall x. Required -> Rep Required x
Generic, [Required] -> Encoding
[Required] -> Value
Required -> Encoding
Required -> Value
(Required -> Value)
-> (Required -> Encoding)
-> ([Required] -> Value)
-> ([Required] -> Encoding)
-> ToJSON Required
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Required] -> Encoding
$ctoEncodingList :: [Required] -> Encoding
toJSONList :: [Required] -> Value
$ctoJSONList :: [Required] -> Value
toEncoding :: Required -> Encoding
$ctoEncoding :: Required -> Encoding
toJSON :: Required -> Value
$ctoJSON :: Required -> Value
ToJSON)
instance FromJSON Required where
  parseJSON :: Value -> Parser Required
parseJSON = String -> (Bool -> Parser Required) -> Value -> Parser Required
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
withBool "Required" (\p :: Bool
p -> Required -> Parser Required
forall (f :: * -> *) a. Applicative f => a -> f a
pure (if Bool
p then Required
Required else Required
Optional))
data Type = MkType
  { Type -> DatatypeName
fieldType :: DatatypeName
  , Type -> Named
isNamed :: Named
  }
  deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
$cp1Ord :: Eq Type
Ord, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type] -> ShowS
$cshowList :: [Type] -> ShowS
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> ShowS
$cshowsPrec :: Int -> Type -> ShowS
Show, (forall x. Type -> Rep Type x)
-> (forall x. Rep Type x -> Type) -> Generic Type
forall x. Rep Type x -> Type
forall x. Type -> Rep Type x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Type x -> Type
$cfrom :: forall x. Type -> Rep Type x
Generic, [Type] -> Encoding
[Type] -> Value
Type -> Encoding
Type -> Value
(Type -> Value)
-> (Type -> Encoding)
-> ([Type] -> Value)
-> ([Type] -> Encoding)
-> ToJSON Type
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Type] -> Encoding
$ctoEncodingList :: [Type] -> Encoding
toJSONList :: [Type] -> Value
$ctoJSONList :: [Type] -> Value
toEncoding :: Type -> Encoding
$ctoEncoding :: Type -> Encoding
toJSON :: Type -> Value
$ctoJSON :: Type -> Value
ToJSON)
instance FromJSON Type where
  parseJSON :: Value -> Parser Type
parseJSON = Options -> Value -> Parser Type
forall a.
(Generic a, GFromJSON Zero (Rep a)) =>
Options -> Value -> Parser a
genericParseJSON Options
customOptions
newtype DatatypeName = DatatypeName { DatatypeName -> String
getDatatypeName :: String }
  deriving (DatatypeName -> DatatypeName -> Bool
(DatatypeName -> DatatypeName -> Bool)
-> (DatatypeName -> DatatypeName -> Bool) -> Eq DatatypeName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DatatypeName -> DatatypeName -> Bool
$c/= :: DatatypeName -> DatatypeName -> Bool
== :: DatatypeName -> DatatypeName -> Bool
$c== :: DatatypeName -> DatatypeName -> Bool
Eq, Eq DatatypeName
Eq DatatypeName =>
(DatatypeName -> DatatypeName -> Ordering)
-> (DatatypeName -> DatatypeName -> Bool)
-> (DatatypeName -> DatatypeName -> Bool)
-> (DatatypeName -> DatatypeName -> Bool)
-> (DatatypeName -> DatatypeName -> Bool)
-> (DatatypeName -> DatatypeName -> DatatypeName)
-> (DatatypeName -> DatatypeName -> DatatypeName)
-> Ord DatatypeName
DatatypeName -> DatatypeName -> Bool
DatatypeName -> DatatypeName -> Ordering
DatatypeName -> DatatypeName -> DatatypeName
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: DatatypeName -> DatatypeName -> DatatypeName
$cmin :: DatatypeName -> DatatypeName -> DatatypeName
max :: DatatypeName -> DatatypeName -> DatatypeName
$cmax :: DatatypeName -> DatatypeName -> DatatypeName
>= :: DatatypeName -> DatatypeName -> Bool
$c>= :: DatatypeName -> DatatypeName -> Bool
> :: DatatypeName -> DatatypeName -> Bool
$c> :: DatatypeName -> DatatypeName -> Bool
<= :: DatatypeName -> DatatypeName -> Bool
$c<= :: DatatypeName -> DatatypeName -> Bool
< :: DatatypeName -> DatatypeName -> Bool
$c< :: DatatypeName -> DatatypeName -> Bool
compare :: DatatypeName -> DatatypeName -> Ordering
$ccompare :: DatatypeName -> DatatypeName -> Ordering
$cp1Ord :: Eq DatatypeName
Ord, Int -> DatatypeName -> ShowS
[DatatypeName] -> ShowS
DatatypeName -> String
(Int -> DatatypeName -> ShowS)
-> (DatatypeName -> String)
-> ([DatatypeName] -> ShowS)
-> Show DatatypeName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DatatypeName] -> ShowS
$cshowList :: [DatatypeName] -> ShowS
show :: DatatypeName -> String
$cshow :: DatatypeName -> String
showsPrec :: Int -> DatatypeName -> ShowS
$cshowsPrec :: Int -> DatatypeName -> ShowS
Show, (forall x. DatatypeName -> Rep DatatypeName x)
-> (forall x. Rep DatatypeName x -> DatatypeName)
-> Generic DatatypeName
forall x. Rep DatatypeName x -> DatatypeName
forall x. DatatypeName -> Rep DatatypeName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DatatypeName x -> DatatypeName
$cfrom :: forall x. DatatypeName -> Rep DatatypeName x
Generic)
  deriving newtype (Value -> Parser [DatatypeName]
Value -> Parser DatatypeName
(Value -> Parser DatatypeName)
-> (Value -> Parser [DatatypeName]) -> FromJSON DatatypeName
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [DatatypeName]
$cparseJSONList :: Value -> Parser [DatatypeName]
parseJSON :: Value -> Parser DatatypeName
$cparseJSON :: Value -> Parser DatatypeName
FromJSON, [DatatypeName] -> Encoding
[DatatypeName] -> Value
DatatypeName -> Encoding
DatatypeName -> Value
(DatatypeName -> Value)
-> (DatatypeName -> Encoding)
-> ([DatatypeName] -> Value)
-> ([DatatypeName] -> Encoding)
-> ToJSON DatatypeName
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [DatatypeName] -> Encoding
$ctoEncodingList :: [DatatypeName] -> Encoding
toJSONList :: [DatatypeName] -> Value
$ctoJSONList :: [DatatypeName] -> Value
toEncoding :: DatatypeName -> Encoding
$ctoEncoding :: DatatypeName -> Encoding
toJSON :: DatatypeName -> Value
$ctoJSON :: DatatypeName -> Value
ToJSON)
data Named = Anonymous | Named
  deriving (Named -> Named -> Bool
(Named -> Named -> Bool) -> (Named -> Named -> Bool) -> Eq Named
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Named -> Named -> Bool
$c/= :: Named -> Named -> Bool
== :: Named -> Named -> Bool
$c== :: Named -> Named -> Bool
Eq, Eq Named
Eq Named =>
(Named -> Named -> Ordering)
-> (Named -> Named -> Bool)
-> (Named -> Named -> Bool)
-> (Named -> Named -> Bool)
-> (Named -> Named -> Bool)
-> (Named -> Named -> Named)
-> (Named -> Named -> Named)
-> Ord Named
Named -> Named -> Bool
Named -> Named -> Ordering
Named -> Named -> Named
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Named -> Named -> Named
$cmin :: Named -> Named -> Named
max :: Named -> Named -> Named
$cmax :: Named -> Named -> Named
>= :: Named -> Named -> Bool
$c>= :: Named -> Named -> Bool
> :: Named -> Named -> Bool
$c> :: Named -> Named -> Bool
<= :: Named -> Named -> Bool
$c<= :: Named -> Named -> Bool
< :: Named -> Named -> Bool
$c< :: Named -> Named -> Bool
compare :: Named -> Named -> Ordering
$ccompare :: Named -> Named -> Ordering
$cp1Ord :: Eq Named
Ord, Int -> Named -> ShowS
[Named] -> ShowS
Named -> String
(Int -> Named -> ShowS)
-> (Named -> String) -> ([Named] -> ShowS) -> Show Named
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Named] -> ShowS
$cshowList :: [Named] -> ShowS
show :: Named -> String
$cshow :: Named -> String
showsPrec :: Int -> Named -> ShowS
$cshowsPrec :: Int -> Named -> ShowS
Show, (forall x. Named -> Rep Named x)
-> (forall x. Rep Named x -> Named) -> Generic Named
forall x. Rep Named x -> Named
forall x. Named -> Rep Named x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Named x -> Named
$cfrom :: forall x. Named -> Rep Named x
Generic, [Named] -> Encoding
[Named] -> Value
Named -> Encoding
Named -> Value
(Named -> Value)
-> (Named -> Encoding)
-> ([Named] -> Value)
-> ([Named] -> Encoding)
-> ToJSON Named
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Named] -> Encoding
$ctoEncodingList :: [Named] -> Encoding
toJSONList :: [Named] -> Value
$ctoJSONList :: [Named] -> Value
toEncoding :: Named -> Encoding
$ctoEncoding :: Named -> Encoding
toJSON :: Named -> Value
$ctoJSON :: Named -> Value
ToJSON, Named -> Q Exp
(Named -> Q Exp) -> Lift Named
forall t. (t -> Q Exp) -> Lift t
lift :: Named -> Q Exp
$clift :: Named -> Q Exp
Lift)
instance FromJSON Named where
  parseJSON :: Value -> Parser Named
parseJSON = String -> (Bool -> Parser Named) -> Value -> Parser Named
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
withBool "Named" (\p :: Bool
p -> Named -> Parser Named
forall (f :: * -> *) a. Applicative f => a -> f a
pure (if Bool
p then Named
Named else Named
Anonymous))
data Multiple = Single | Multiple
  deriving (Multiple -> Multiple -> Bool
(Multiple -> Multiple -> Bool)
-> (Multiple -> Multiple -> Bool) -> Eq Multiple
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Multiple -> Multiple -> Bool
$c/= :: Multiple -> Multiple -> Bool
== :: Multiple -> Multiple -> Bool
$c== :: Multiple -> Multiple -> Bool
Eq, Eq Multiple
Eq Multiple =>
(Multiple -> Multiple -> Ordering)
-> (Multiple -> Multiple -> Bool)
-> (Multiple -> Multiple -> Bool)
-> (Multiple -> Multiple -> Bool)
-> (Multiple -> Multiple -> Bool)
-> (Multiple -> Multiple -> Multiple)
-> (Multiple -> Multiple -> Multiple)
-> Ord Multiple
Multiple -> Multiple -> Bool
Multiple -> Multiple -> Ordering
Multiple -> Multiple -> Multiple
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Multiple -> Multiple -> Multiple
$cmin :: Multiple -> Multiple -> Multiple
max :: Multiple -> Multiple -> Multiple
$cmax :: Multiple -> Multiple -> Multiple
>= :: Multiple -> Multiple -> Bool
$c>= :: Multiple -> Multiple -> Bool
> :: Multiple -> Multiple -> Bool
$c> :: Multiple -> Multiple -> Bool
<= :: Multiple -> Multiple -> Bool
$c<= :: Multiple -> Multiple -> Bool
< :: Multiple -> Multiple -> Bool
$c< :: Multiple -> Multiple -> Bool
compare :: Multiple -> Multiple -> Ordering
$ccompare :: Multiple -> Multiple -> Ordering
$cp1Ord :: Eq Multiple
Ord, Int -> Multiple -> ShowS
[Multiple] -> ShowS
Multiple -> String
(Int -> Multiple -> ShowS)
-> (Multiple -> String) -> ([Multiple] -> ShowS) -> Show Multiple
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Multiple] -> ShowS
$cshowList :: [Multiple] -> ShowS
show :: Multiple -> String
$cshow :: Multiple -> String
showsPrec :: Int -> Multiple -> ShowS
$cshowsPrec :: Int -> Multiple -> ShowS
Show, (forall x. Multiple -> Rep Multiple x)
-> (forall x. Rep Multiple x -> Multiple) -> Generic Multiple
forall x. Rep Multiple x -> Multiple
forall x. Multiple -> Rep Multiple x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Multiple x -> Multiple
$cfrom :: forall x. Multiple -> Rep Multiple x
Generic, [Multiple] -> Encoding
[Multiple] -> Value
Multiple -> Encoding
Multiple -> Value
(Multiple -> Value)
-> (Multiple -> Encoding)
-> ([Multiple] -> Value)
-> ([Multiple] -> Encoding)
-> ToJSON Multiple
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Multiple] -> Encoding
$ctoEncodingList :: [Multiple] -> Encoding
toJSONList :: [Multiple] -> Value
$ctoJSONList :: [Multiple] -> Value
toEncoding :: Multiple -> Encoding
$ctoEncoding :: Multiple -> Encoding
toJSON :: Multiple -> Value
$ctoJSON :: Multiple -> Value
ToJSON)
instance FromJSON Multiple where
  parseJSON :: Value -> Parser Multiple
parseJSON = String -> (Bool -> Parser Multiple) -> Value -> Parser Multiple
forall a. String -> (Bool -> Parser a) -> Value -> Parser a
withBool "Multiple" (\p :: Bool
p -> Multiple -> Parser Multiple
forall (f :: * -> *) a. Applicative f => a -> f a
pure (if Bool
p then Multiple
Multiple else Multiple
Single))
customOptions :: Aeson.Options
customOptions :: Options
customOptions = Options
Aeson.defaultOptions
  {
    fieldLabelModifier :: ShowS
fieldLabelModifier = ShowS
initLower ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS
dropPrefix
  , constructorTagModifier :: ShowS
constructorTagModifier = ShowS
initLower
  }
dropPrefix :: String -> String
dropPrefix :: ShowS
dropPrefix = (Char -> Bool) -> ShowS
forall a. (a -> Bool) -> [a] -> [a]
Prelude.dropWhile Char -> Bool
isLower
initLower :: String -> String
initLower :: ShowS
initLower (c :: Char
c:cs :: String
cs) = Char -> Char
toLower Char
c Char -> ShowS
forall a. a -> [a] -> [a]
: String
cs
initLower "" = ""