{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
module Language.LSP.MetaModel.Types where
import Data.Aeson hiding (Null, String)
import qualified Data.Aeson as JSON
import qualified Data.Aeson.TH as JSON
import qualified Data.Char as Char
import Data.Text (Text)
import Control.Lens
import Control.Monad.IO.Class
import qualified Data.List.NonEmpty as NE
import Language.Haskell.TH.Syntax (Lift(..), Q, Exp, addDependentFile)
data MessageDirection = ServerToClient | ClientToServer | Both
deriving stock (Int -> MessageDirection -> ShowS
[MessageDirection] -> ShowS
MessageDirection -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MessageDirection] -> ShowS
$cshowList :: [MessageDirection] -> ShowS
show :: MessageDirection -> String
$cshow :: MessageDirection -> String
showsPrec :: Int -> MessageDirection -> ShowS
$cshowsPrec :: Int -> MessageDirection -> ShowS
Show, MessageDirection -> MessageDirection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MessageDirection -> MessageDirection -> Bool
$c/= :: MessageDirection -> MessageDirection -> Bool
== :: MessageDirection -> MessageDirection -> Bool
$c== :: MessageDirection -> MessageDirection -> Bool
Eq, Eq MessageDirection
MessageDirection -> MessageDirection -> Bool
MessageDirection -> MessageDirection -> Ordering
MessageDirection -> MessageDirection -> MessageDirection
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 :: MessageDirection -> MessageDirection -> MessageDirection
$cmin :: MessageDirection -> MessageDirection -> MessageDirection
max :: MessageDirection -> MessageDirection -> MessageDirection
$cmax :: MessageDirection -> MessageDirection -> MessageDirection
>= :: MessageDirection -> MessageDirection -> Bool
$c>= :: MessageDirection -> MessageDirection -> Bool
> :: MessageDirection -> MessageDirection -> Bool
$c> :: MessageDirection -> MessageDirection -> Bool
<= :: MessageDirection -> MessageDirection -> Bool
$c<= :: MessageDirection -> MessageDirection -> Bool
< :: MessageDirection -> MessageDirection -> Bool
$c< :: MessageDirection -> MessageDirection -> Bool
compare :: MessageDirection -> MessageDirection -> Ordering
$ccompare :: MessageDirection -> MessageDirection -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => MessageDirection -> m Exp
forall (m :: * -> *).
Quote m =>
MessageDirection -> Code m MessageDirection
liftTyped :: forall (m :: * -> *).
Quote m =>
MessageDirection -> Code m MessageDirection
$cliftTyped :: forall (m :: * -> *).
Quote m =>
MessageDirection -> Code m MessageDirection
lift :: forall (m :: * -> *). Quote m => MessageDirection -> m Exp
$clift :: forall (m :: * -> *). Quote m => MessageDirection -> m Exp
Lift)
instance ToJSON MessageDirection where
toJSON :: MessageDirection -> Value
toJSON MessageDirection
ServerToClient = forall a. ToJSON a => a -> Value
toJSON @String String
"serverToClient"
toJSON MessageDirection
ClientToServer = forall a. ToJSON a => a -> Value
toJSON @String String
"clientToServer"
toJSON MessageDirection
Both = forall a. ToJSON a => a -> Value
toJSON @String String
"both"
instance FromJSON MessageDirection where
parseJSON :: Value -> Parser MessageDirection
parseJSON = forall a. String -> (Text -> Parser a) -> Value -> Parser a
withText String
"MessageDirection" forall a b. (a -> b) -> a -> b
$ \case
Text
"serverToClient" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MessageDirection
ServerToClient
Text
"clientToServer" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MessageDirection
ClientToServer
Text
"both" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure MessageDirection
Both
Text
t -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail forall a b. (a -> b) -> a -> b
$ String
"unknown message direction " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
t
data BaseTypeName = URI | DocumentUri | Integer | UInteger | Decimal | RegExp | String | Boolean | Null
deriving stock (Int -> BaseTypeName -> ShowS
[BaseTypeName] -> ShowS
BaseTypeName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BaseTypeName] -> ShowS
$cshowList :: [BaseTypeName] -> ShowS
show :: BaseTypeName -> String
$cshow :: BaseTypeName -> String
showsPrec :: Int -> BaseTypeName -> ShowS
$cshowsPrec :: Int -> BaseTypeName -> ShowS
Show, BaseTypeName -> BaseTypeName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BaseTypeName -> BaseTypeName -> Bool
$c/= :: BaseTypeName -> BaseTypeName -> Bool
== :: BaseTypeName -> BaseTypeName -> Bool
$c== :: BaseTypeName -> BaseTypeName -> Bool
Eq, Eq BaseTypeName
BaseTypeName -> BaseTypeName -> Bool
BaseTypeName -> BaseTypeName -> Ordering
BaseTypeName -> BaseTypeName -> BaseTypeName
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 :: BaseTypeName -> BaseTypeName -> BaseTypeName
$cmin :: BaseTypeName -> BaseTypeName -> BaseTypeName
max :: BaseTypeName -> BaseTypeName -> BaseTypeName
$cmax :: BaseTypeName -> BaseTypeName -> BaseTypeName
>= :: BaseTypeName -> BaseTypeName -> Bool
$c>= :: BaseTypeName -> BaseTypeName -> Bool
> :: BaseTypeName -> BaseTypeName -> Bool
$c> :: BaseTypeName -> BaseTypeName -> Bool
<= :: BaseTypeName -> BaseTypeName -> Bool
$c<= :: BaseTypeName -> BaseTypeName -> Bool
< :: BaseTypeName -> BaseTypeName -> Bool
$c< :: BaseTypeName -> BaseTypeName -> Bool
compare :: BaseTypeName -> BaseTypeName -> Ordering
$ccompare :: BaseTypeName -> BaseTypeName -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => BaseTypeName -> m Exp
forall (m :: * -> *).
Quote m =>
BaseTypeName -> Code m BaseTypeName
liftTyped :: forall (m :: * -> *).
Quote m =>
BaseTypeName -> Code m BaseTypeName
$cliftTyped :: forall (m :: * -> *).
Quote m =>
BaseTypeName -> Code m BaseTypeName
lift :: forall (m :: * -> *). Quote m => BaseTypeName -> m Exp
$clift :: forall (m :: * -> *). Quote m => BaseTypeName -> m Exp
Lift)
data Property = Property
{ Property -> Text
name :: Text
, Property -> Type
type_ :: Type
, Property -> Maybe Bool
optional :: Maybe Bool
, Property -> Maybe Text
documentation :: Maybe Text
, Property -> Maybe Text
since :: Maybe Text
, Property -> Maybe Bool
proposed :: Maybe Bool
, Property -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> Property -> ShowS
[Property] -> ShowS
Property -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Property] -> ShowS
$cshowList :: [Property] -> ShowS
show :: Property -> String
$cshow :: Property -> String
showsPrec :: Int -> Property -> ShowS
$cshowsPrec :: Int -> Property -> ShowS
Show, Property -> Property -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Property -> Property -> Bool
$c/= :: Property -> Property -> Bool
== :: Property -> Property -> Bool
$c== :: Property -> Property -> Bool
Eq, Eq Property
Property -> Property -> Bool
Property -> Property -> Ordering
Property -> Property -> Property
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 :: Property -> Property -> Property
$cmin :: Property -> Property -> Property
max :: Property -> Property -> Property
$cmax :: Property -> Property -> Property
>= :: Property -> Property -> Bool
$c>= :: Property -> Property -> Bool
> :: Property -> Property -> Bool
$c> :: Property -> Property -> Bool
<= :: Property -> Property -> Bool
$c<= :: Property -> Property -> Bool
< :: Property -> Property -> Bool
$c< :: Property -> Property -> Bool
compare :: Property -> Property -> Ordering
$ccompare :: Property -> Property -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Property -> m Exp
forall (m :: * -> *). Quote m => Property -> Code m Property
liftTyped :: forall (m :: * -> *). Quote m => Property -> Code m Property
$cliftTyped :: forall (m :: * -> *). Quote m => Property -> Code m Property
lift :: forall (m :: * -> *). Quote m => Property -> m Exp
$clift :: forall (m :: * -> *). Quote m => Property -> m Exp
Lift)
data StructureLiteral = StructureLiteral
{ StructureLiteral -> [Property]
properties :: [Property]
, StructureLiteral -> Maybe Text
documentation :: Maybe Text
, StructureLiteral -> Maybe Text
since :: Maybe Text
, StructureLiteral -> Maybe Bool
proposed :: Maybe Bool
, StructureLiteral -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> StructureLiteral -> ShowS
[StructureLiteral] -> ShowS
StructureLiteral -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StructureLiteral] -> ShowS
$cshowList :: [StructureLiteral] -> ShowS
show :: StructureLiteral -> String
$cshow :: StructureLiteral -> String
showsPrec :: Int -> StructureLiteral -> ShowS
$cshowsPrec :: Int -> StructureLiteral -> ShowS
Show, StructureLiteral -> StructureLiteral -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StructureLiteral -> StructureLiteral -> Bool
$c/= :: StructureLiteral -> StructureLiteral -> Bool
== :: StructureLiteral -> StructureLiteral -> Bool
$c== :: StructureLiteral -> StructureLiteral -> Bool
Eq, Eq StructureLiteral
StructureLiteral -> StructureLiteral -> Bool
StructureLiteral -> StructureLiteral -> Ordering
StructureLiteral -> StructureLiteral -> StructureLiteral
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 :: StructureLiteral -> StructureLiteral -> StructureLiteral
$cmin :: StructureLiteral -> StructureLiteral -> StructureLiteral
max :: StructureLiteral -> StructureLiteral -> StructureLiteral
$cmax :: StructureLiteral -> StructureLiteral -> StructureLiteral
>= :: StructureLiteral -> StructureLiteral -> Bool
$c>= :: StructureLiteral -> StructureLiteral -> Bool
> :: StructureLiteral -> StructureLiteral -> Bool
$c> :: StructureLiteral -> StructureLiteral -> Bool
<= :: StructureLiteral -> StructureLiteral -> Bool
$c<= :: StructureLiteral -> StructureLiteral -> Bool
< :: StructureLiteral -> StructureLiteral -> Bool
$c< :: StructureLiteral -> StructureLiteral -> Bool
compare :: StructureLiteral -> StructureLiteral -> Ordering
$ccompare :: StructureLiteral -> StructureLiteral -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => StructureLiteral -> m Exp
forall (m :: * -> *).
Quote m =>
StructureLiteral -> Code m StructureLiteral
liftTyped :: forall (m :: * -> *).
Quote m =>
StructureLiteral -> Code m StructureLiteral
$cliftTyped :: forall (m :: * -> *).
Quote m =>
StructureLiteral -> Code m StructureLiteral
lift :: forall (m :: * -> *). Quote m => StructureLiteral -> m Exp
$clift :: forall (m :: * -> *). Quote m => StructureLiteral -> m Exp
Lift)
data Type =
BaseType { Type -> BaseTypeName
btName :: BaseTypeName }
| ReferenceType { Type -> Text
rtName :: Text }
| ArrayType { Type -> Type
atElement :: Type }
| MapType { Type -> Type
mKey :: Type, Type -> Type
mValue :: Type }
| AndType { Type -> NonEmpty Type
aItems :: NE.NonEmpty Type }
| OrType { Type -> NonEmpty Type
oItems :: NE.NonEmpty Type }
| TupleType { Type -> [Type]
tItems :: [Type] }
| StructureLiteralType { Type -> StructureLiteral
stlValue :: StructureLiteral }
| StringLiteralType { Type -> Text
slValue :: Text }
| IntegerLiteralType { Type -> Integer
ilValue :: Integer }
| BooleanLiteralType { Type -> Bool
blValue :: Bool }
deriving stock (Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
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, Type -> Type -> Bool
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
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
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Type -> m Exp
forall (m :: * -> *). Quote m => Type -> Code m Type
liftTyped :: forall (m :: * -> *). Quote m => Type -> Code m Type
$cliftTyped :: forall (m :: * -> *). Quote m => Type -> Code m Type
lift :: forall (m :: * -> *). Quote m => Type -> m Exp
$clift :: forall (m :: * -> *). Quote m => Type -> m Exp
Lift)
data Request = Request
{ Request -> Text
method :: Text
, Request -> Maybe Type
params :: Maybe Type
, Request -> Type
result :: Type
, Request -> Maybe Type
partialResult :: Maybe Type
, Request -> Maybe Type
errorData :: Maybe Type
, Request -> Maybe Type
registrationOptions :: Maybe Type
, Request -> MessageDirection
messageDirection :: MessageDirection
, Request -> Maybe Text
documentation :: Maybe Text
, Request -> Maybe Text
since :: Maybe Text
, Request -> Maybe Bool
proposed :: Maybe Bool
, Request -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> Request -> ShowS
[Request] -> ShowS
Request -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Request] -> ShowS
$cshowList :: [Request] -> ShowS
show :: Request -> String
$cshow :: Request -> String
showsPrec :: Int -> Request -> ShowS
$cshowsPrec :: Int -> Request -> ShowS
Show, Request -> Request -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Request -> Request -> Bool
$c/= :: Request -> Request -> Bool
== :: Request -> Request -> Bool
$c== :: Request -> Request -> Bool
Eq, Eq Request
Request -> Request -> Bool
Request -> Request -> Ordering
Request -> Request -> Request
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 :: Request -> Request -> Request
$cmin :: Request -> Request -> Request
max :: Request -> Request -> Request
$cmax :: Request -> Request -> Request
>= :: Request -> Request -> Bool
$c>= :: Request -> Request -> Bool
> :: Request -> Request -> Bool
$c> :: Request -> Request -> Bool
<= :: Request -> Request -> Bool
$c<= :: Request -> Request -> Bool
< :: Request -> Request -> Bool
$c< :: Request -> Request -> Bool
compare :: Request -> Request -> Ordering
$ccompare :: Request -> Request -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Request -> m Exp
forall (m :: * -> *). Quote m => Request -> Code m Request
liftTyped :: forall (m :: * -> *). Quote m => Request -> Code m Request
$cliftTyped :: forall (m :: * -> *). Quote m => Request -> Code m Request
lift :: forall (m :: * -> *). Quote m => Request -> m Exp
$clift :: forall (m :: * -> *). Quote m => Request -> m Exp
Lift)
data Notification = Notification
{ Notification -> Text
method :: Text
, Notification -> Maybe Type
params :: Maybe Type
, Notification -> Maybe Type
registrationOptions :: Maybe Type
, Notification -> MessageDirection
messageDirection :: MessageDirection
, Notification -> Maybe Text
documentation :: Maybe Text
, Notification -> Maybe Text
since :: Maybe Text
, Notification -> Maybe Bool
proposed :: Maybe Bool
, Notification -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> Notification -> ShowS
[Notification] -> ShowS
Notification -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Notification] -> ShowS
$cshowList :: [Notification] -> ShowS
show :: Notification -> String
$cshow :: Notification -> String
showsPrec :: Int -> Notification -> ShowS
$cshowsPrec :: Int -> Notification -> ShowS
Show, Notification -> Notification -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Notification -> Notification -> Bool
$c/= :: Notification -> Notification -> Bool
== :: Notification -> Notification -> Bool
$c== :: Notification -> Notification -> Bool
Eq, Eq Notification
Notification -> Notification -> Bool
Notification -> Notification -> Ordering
Notification -> Notification -> Notification
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 :: Notification -> Notification -> Notification
$cmin :: Notification -> Notification -> Notification
max :: Notification -> Notification -> Notification
$cmax :: Notification -> Notification -> Notification
>= :: Notification -> Notification -> Bool
$c>= :: Notification -> Notification -> Bool
> :: Notification -> Notification -> Bool
$c> :: Notification -> Notification -> Bool
<= :: Notification -> Notification -> Bool
$c<= :: Notification -> Notification -> Bool
< :: Notification -> Notification -> Bool
$c< :: Notification -> Notification -> Bool
compare :: Notification -> Notification -> Ordering
$ccompare :: Notification -> Notification -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Notification -> m Exp
forall (m :: * -> *).
Quote m =>
Notification -> Code m Notification
liftTyped :: forall (m :: * -> *).
Quote m =>
Notification -> Code m Notification
$cliftTyped :: forall (m :: * -> *).
Quote m =>
Notification -> Code m Notification
lift :: forall (m :: * -> *). Quote m => Notification -> m Exp
$clift :: forall (m :: * -> *). Quote m => Notification -> m Exp
Lift)
data Structure = Structure
{ Structure -> Text
name :: Text
, Structure -> Maybe [Type]
extends :: Maybe [Type]
, Structure -> Maybe [Type]
mixins :: Maybe [Type]
, Structure -> [Property]
properties :: [Property]
, Structure -> Maybe Text
documentation :: Maybe Text
, Structure -> Maybe Text
since :: Maybe Text
, Structure -> Maybe Bool
proposed :: Maybe Bool
, Structure -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> Structure -> ShowS
[Structure] -> ShowS
Structure -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Structure] -> ShowS
$cshowList :: [Structure] -> ShowS
show :: Structure -> String
$cshow :: Structure -> String
showsPrec :: Int -> Structure -> ShowS
$cshowsPrec :: Int -> Structure -> ShowS
Show, Structure -> Structure -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Structure -> Structure -> Bool
$c/= :: Structure -> Structure -> Bool
== :: Structure -> Structure -> Bool
$c== :: Structure -> Structure -> Bool
Eq, Eq Structure
Structure -> Structure -> Bool
Structure -> Structure -> Ordering
Structure -> Structure -> Structure
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 :: Structure -> Structure -> Structure
$cmin :: Structure -> Structure -> Structure
max :: Structure -> Structure -> Structure
$cmax :: Structure -> Structure -> Structure
>= :: Structure -> Structure -> Bool
$c>= :: Structure -> Structure -> Bool
> :: Structure -> Structure -> Bool
$c> :: Structure -> Structure -> Bool
<= :: Structure -> Structure -> Bool
$c<= :: Structure -> Structure -> Bool
< :: Structure -> Structure -> Bool
$c< :: Structure -> Structure -> Bool
compare :: Structure -> Structure -> Ordering
$ccompare :: Structure -> Structure -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Structure -> m Exp
forall (m :: * -> *). Quote m => Structure -> Code m Structure
liftTyped :: forall (m :: * -> *). Quote m => Structure -> Code m Structure
$cliftTyped :: forall (m :: * -> *). Quote m => Structure -> Code m Structure
lift :: forall (m :: * -> *). Quote m => Structure -> m Exp
$clift :: forall (m :: * -> *). Quote m => Structure -> m Exp
Lift)
data TypeAlias = TypeAlias
{ TypeAlias -> Text
name :: Text
, TypeAlias -> Type
type_ :: Type
, TypeAlias -> Maybe Text
documentation :: Maybe Text
, TypeAlias -> Maybe Text
since :: Maybe Text
, TypeAlias -> Maybe Bool
proposed :: Maybe Bool
, TypeAlias -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> TypeAlias -> ShowS
[TypeAlias] -> ShowS
TypeAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeAlias] -> ShowS
$cshowList :: [TypeAlias] -> ShowS
show :: TypeAlias -> String
$cshow :: TypeAlias -> String
showsPrec :: Int -> TypeAlias -> ShowS
$cshowsPrec :: Int -> TypeAlias -> ShowS
Show, TypeAlias -> TypeAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeAlias -> TypeAlias -> Bool
$c/= :: TypeAlias -> TypeAlias -> Bool
== :: TypeAlias -> TypeAlias -> Bool
$c== :: TypeAlias -> TypeAlias -> Bool
Eq, Eq TypeAlias
TypeAlias -> TypeAlias -> Bool
TypeAlias -> TypeAlias -> Ordering
TypeAlias -> TypeAlias -> TypeAlias
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 :: TypeAlias -> TypeAlias -> TypeAlias
$cmin :: TypeAlias -> TypeAlias -> TypeAlias
max :: TypeAlias -> TypeAlias -> TypeAlias
$cmax :: TypeAlias -> TypeAlias -> TypeAlias
>= :: TypeAlias -> TypeAlias -> Bool
$c>= :: TypeAlias -> TypeAlias -> Bool
> :: TypeAlias -> TypeAlias -> Bool
$c> :: TypeAlias -> TypeAlias -> Bool
<= :: TypeAlias -> TypeAlias -> Bool
$c<= :: TypeAlias -> TypeAlias -> Bool
< :: TypeAlias -> TypeAlias -> Bool
$c< :: TypeAlias -> TypeAlias -> Bool
compare :: TypeAlias -> TypeAlias -> Ordering
$ccompare :: TypeAlias -> TypeAlias -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TypeAlias -> m Exp
forall (m :: * -> *). Quote m => TypeAlias -> Code m TypeAlias
liftTyped :: forall (m :: * -> *). Quote m => TypeAlias -> Code m TypeAlias
$cliftTyped :: forall (m :: * -> *). Quote m => TypeAlias -> Code m TypeAlias
lift :: forall (m :: * -> *). Quote m => TypeAlias -> m Exp
$clift :: forall (m :: * -> *). Quote m => TypeAlias -> m Exp
Lift)
data TextOrInteger = T Text | I Integer
deriving stock (Int -> TextOrInteger -> ShowS
[TextOrInteger] -> ShowS
TextOrInteger -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextOrInteger] -> ShowS
$cshowList :: [TextOrInteger] -> ShowS
show :: TextOrInteger -> String
$cshow :: TextOrInteger -> String
showsPrec :: Int -> TextOrInteger -> ShowS
$cshowsPrec :: Int -> TextOrInteger -> ShowS
Show, TextOrInteger -> TextOrInteger -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TextOrInteger -> TextOrInteger -> Bool
$c/= :: TextOrInteger -> TextOrInteger -> Bool
== :: TextOrInteger -> TextOrInteger -> Bool
$c== :: TextOrInteger -> TextOrInteger -> Bool
Eq, Eq TextOrInteger
TextOrInteger -> TextOrInteger -> Bool
TextOrInteger -> TextOrInteger -> Ordering
TextOrInteger -> TextOrInteger -> TextOrInteger
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 :: TextOrInteger -> TextOrInteger -> TextOrInteger
$cmin :: TextOrInteger -> TextOrInteger -> TextOrInteger
max :: TextOrInteger -> TextOrInteger -> TextOrInteger
$cmax :: TextOrInteger -> TextOrInteger -> TextOrInteger
>= :: TextOrInteger -> TextOrInteger -> Bool
$c>= :: TextOrInteger -> TextOrInteger -> Bool
> :: TextOrInteger -> TextOrInteger -> Bool
$c> :: TextOrInteger -> TextOrInteger -> Bool
<= :: TextOrInteger -> TextOrInteger -> Bool
$c<= :: TextOrInteger -> TextOrInteger -> Bool
< :: TextOrInteger -> TextOrInteger -> Bool
$c< :: TextOrInteger -> TextOrInteger -> Bool
compare :: TextOrInteger -> TextOrInteger -> Ordering
$ccompare :: TextOrInteger -> TextOrInteger -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => TextOrInteger -> m Exp
forall (m :: * -> *).
Quote m =>
TextOrInteger -> Code m TextOrInteger
liftTyped :: forall (m :: * -> *).
Quote m =>
TextOrInteger -> Code m TextOrInteger
$cliftTyped :: forall (m :: * -> *).
Quote m =>
TextOrInteger -> Code m TextOrInteger
lift :: forall (m :: * -> *). Quote m => TextOrInteger -> m Exp
$clift :: forall (m :: * -> *). Quote m => TextOrInteger -> m Exp
Lift)
data EnumerationEntry = EnumerationEntry
{ EnumerationEntry -> Text
name :: Text
, EnumerationEntry -> TextOrInteger
value :: TextOrInteger
, EnumerationEntry -> Maybe Text
documentation :: Maybe Text
, EnumerationEntry -> Maybe Text
since :: Maybe Text
, EnumerationEntry -> Maybe Bool
proposed :: Maybe Bool
, EnumerationEntry -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> EnumerationEntry -> ShowS
[EnumerationEntry] -> ShowS
EnumerationEntry -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [EnumerationEntry] -> ShowS
$cshowList :: [EnumerationEntry] -> ShowS
show :: EnumerationEntry -> String
$cshow :: EnumerationEntry -> String
showsPrec :: Int -> EnumerationEntry -> ShowS
$cshowsPrec :: Int -> EnumerationEntry -> ShowS
Show, EnumerationEntry -> EnumerationEntry -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumerationEntry -> EnumerationEntry -> Bool
$c/= :: EnumerationEntry -> EnumerationEntry -> Bool
== :: EnumerationEntry -> EnumerationEntry -> Bool
$c== :: EnumerationEntry -> EnumerationEntry -> Bool
Eq, Eq EnumerationEntry
EnumerationEntry -> EnumerationEntry -> Bool
EnumerationEntry -> EnumerationEntry -> Ordering
EnumerationEntry -> EnumerationEntry -> EnumerationEntry
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 :: EnumerationEntry -> EnumerationEntry -> EnumerationEntry
$cmin :: EnumerationEntry -> EnumerationEntry -> EnumerationEntry
max :: EnumerationEntry -> EnumerationEntry -> EnumerationEntry
$cmax :: EnumerationEntry -> EnumerationEntry -> EnumerationEntry
>= :: EnumerationEntry -> EnumerationEntry -> Bool
$c>= :: EnumerationEntry -> EnumerationEntry -> Bool
> :: EnumerationEntry -> EnumerationEntry -> Bool
$c> :: EnumerationEntry -> EnumerationEntry -> Bool
<= :: EnumerationEntry -> EnumerationEntry -> Bool
$c<= :: EnumerationEntry -> EnumerationEntry -> Bool
< :: EnumerationEntry -> EnumerationEntry -> Bool
$c< :: EnumerationEntry -> EnumerationEntry -> Bool
compare :: EnumerationEntry -> EnumerationEntry -> Ordering
$ccompare :: EnumerationEntry -> EnumerationEntry -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => EnumerationEntry -> m Exp
forall (m :: * -> *).
Quote m =>
EnumerationEntry -> Code m EnumerationEntry
liftTyped :: forall (m :: * -> *).
Quote m =>
EnumerationEntry -> Code m EnumerationEntry
$cliftTyped :: forall (m :: * -> *).
Quote m =>
EnumerationEntry -> Code m EnumerationEntry
lift :: forall (m :: * -> *). Quote m => EnumerationEntry -> m Exp
$clift :: forall (m :: * -> *). Quote m => EnumerationEntry -> m Exp
Lift)
data Enumeration = Enumeration
{ Enumeration -> Text
name :: Text
, Enumeration -> Type
type_ :: Type
, Enumeration -> [EnumerationEntry]
values :: [EnumerationEntry]
, Enumeration -> Maybe Bool
supportsCustomValues :: Maybe Bool
, Enumeration -> Maybe Text
documentation :: Maybe Text
, Enumeration -> Maybe Text
since :: Maybe Text
, Enumeration -> Maybe Bool
proposed :: Maybe Bool
, Enumeration -> Maybe Text
deprecated :: Maybe Text
}
deriving stock (Int -> Enumeration -> ShowS
[Enumeration] -> ShowS
Enumeration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Enumeration] -> ShowS
$cshowList :: [Enumeration] -> ShowS
show :: Enumeration -> String
$cshow :: Enumeration -> String
showsPrec :: Int -> Enumeration -> ShowS
$cshowsPrec :: Int -> Enumeration -> ShowS
Show, Enumeration -> Enumeration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Enumeration -> Enumeration -> Bool
$c/= :: Enumeration -> Enumeration -> Bool
== :: Enumeration -> Enumeration -> Bool
$c== :: Enumeration -> Enumeration -> Bool
Eq, Eq Enumeration
Enumeration -> Enumeration -> Bool
Enumeration -> Enumeration -> Ordering
Enumeration -> Enumeration -> Enumeration
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 :: Enumeration -> Enumeration -> Enumeration
$cmin :: Enumeration -> Enumeration -> Enumeration
max :: Enumeration -> Enumeration -> Enumeration
$cmax :: Enumeration -> Enumeration -> Enumeration
>= :: Enumeration -> Enumeration -> Bool
$c>= :: Enumeration -> Enumeration -> Bool
> :: Enumeration -> Enumeration -> Bool
$c> :: Enumeration -> Enumeration -> Bool
<= :: Enumeration -> Enumeration -> Bool
$c<= :: Enumeration -> Enumeration -> Bool
< :: Enumeration -> Enumeration -> Bool
$c< :: Enumeration -> Enumeration -> Bool
compare :: Enumeration -> Enumeration -> Ordering
$ccompare :: Enumeration -> Enumeration -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => Enumeration -> m Exp
forall (m :: * -> *). Quote m => Enumeration -> Code m Enumeration
liftTyped :: forall (m :: * -> *). Quote m => Enumeration -> Code m Enumeration
$cliftTyped :: forall (m :: * -> *). Quote m => Enumeration -> Code m Enumeration
lift :: forall (m :: * -> *). Quote m => Enumeration -> m Exp
$clift :: forall (m :: * -> *). Quote m => Enumeration -> m Exp
Lift)
data MetaData = MetaData
{ MetaData -> Text
version :: Text
}
deriving stock (Int -> MetaData -> ShowS
[MetaData] -> ShowS
MetaData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetaData] -> ShowS
$cshowList :: [MetaData] -> ShowS
show :: MetaData -> String
$cshow :: MetaData -> String
showsPrec :: Int -> MetaData -> ShowS
$cshowsPrec :: Int -> MetaData -> ShowS
Show, MetaData -> MetaData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetaData -> MetaData -> Bool
$c/= :: MetaData -> MetaData -> Bool
== :: MetaData -> MetaData -> Bool
$c== :: MetaData -> MetaData -> Bool
Eq, Eq MetaData
MetaData -> MetaData -> Bool
MetaData -> MetaData -> Ordering
MetaData -> MetaData -> MetaData
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 :: MetaData -> MetaData -> MetaData
$cmin :: MetaData -> MetaData -> MetaData
max :: MetaData -> MetaData -> MetaData
$cmax :: MetaData -> MetaData -> MetaData
>= :: MetaData -> MetaData -> Bool
$c>= :: MetaData -> MetaData -> Bool
> :: MetaData -> MetaData -> Bool
$c> :: MetaData -> MetaData -> Bool
<= :: MetaData -> MetaData -> Bool
$c<= :: MetaData -> MetaData -> Bool
< :: MetaData -> MetaData -> Bool
$c< :: MetaData -> MetaData -> Bool
compare :: MetaData -> MetaData -> Ordering
$ccompare :: MetaData -> MetaData -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => MetaData -> m Exp
forall (m :: * -> *). Quote m => MetaData -> Code m MetaData
liftTyped :: forall (m :: * -> *). Quote m => MetaData -> Code m MetaData
$cliftTyped :: forall (m :: * -> *). Quote m => MetaData -> Code m MetaData
lift :: forall (m :: * -> *). Quote m => MetaData -> m Exp
$clift :: forall (m :: * -> *). Quote m => MetaData -> m Exp
Lift)
data MetaModel = MetaModel
{ MetaModel -> MetaData
metaData :: MetaData
, MetaModel -> [Request]
requests :: [Request]
, MetaModel -> [Notification]
notifications :: [Notification]
, MetaModel -> [Structure]
structures :: [Structure]
, MetaModel -> [Enumeration]
enumerations :: [Enumeration]
, MetaModel -> [TypeAlias]
typeAliases :: [TypeAlias]
}
deriving stock (Int -> MetaModel -> ShowS
[MetaModel] -> ShowS
MetaModel -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MetaModel] -> ShowS
$cshowList :: [MetaModel] -> ShowS
show :: MetaModel -> String
$cshow :: MetaModel -> String
showsPrec :: Int -> MetaModel -> ShowS
$cshowsPrec :: Int -> MetaModel -> ShowS
Show, MetaModel -> MetaModel -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MetaModel -> MetaModel -> Bool
$c/= :: MetaModel -> MetaModel -> Bool
== :: MetaModel -> MetaModel -> Bool
$c== :: MetaModel -> MetaModel -> Bool
Eq, Eq MetaModel
MetaModel -> MetaModel -> Bool
MetaModel -> MetaModel -> Ordering
MetaModel -> MetaModel -> MetaModel
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 :: MetaModel -> MetaModel -> MetaModel
$cmin :: MetaModel -> MetaModel -> MetaModel
max :: MetaModel -> MetaModel -> MetaModel
$cmax :: MetaModel -> MetaModel -> MetaModel
>= :: MetaModel -> MetaModel -> Bool
$c>= :: MetaModel -> MetaModel -> Bool
> :: MetaModel -> MetaModel -> Bool
$c> :: MetaModel -> MetaModel -> Bool
<= :: MetaModel -> MetaModel -> Bool
$c<= :: MetaModel -> MetaModel -> Bool
< :: MetaModel -> MetaModel -> Bool
$c< :: MetaModel -> MetaModel -> Bool
compare :: MetaModel -> MetaModel -> Ordering
$ccompare :: MetaModel -> MetaModel -> Ordering
Ord, forall t.
(forall (m :: * -> *). Quote m => t -> m Exp)
-> (forall (m :: * -> *). Quote m => t -> Code m t) -> Lift t
forall (m :: * -> *). Quote m => MetaModel -> m Exp
forall (m :: * -> *). Quote m => MetaModel -> Code m MetaModel
liftTyped :: forall (m :: * -> *). Quote m => MetaModel -> Code m MetaModel
$cliftTyped :: forall (m :: * -> *). Quote m => MetaModel -> Code m MetaModel
lift :: forall (m :: * -> *). Quote m => MetaModel -> m Exp
$clift :: forall (m :: * -> *). Quote m => MetaModel -> m Exp
Lift)
$(
let
defOpts = defaultOptions{fieldLabelModifier = \case { "type_" -> "type"; x -> x; }}
propertyInst = JSON.deriveJSON defOpts ''Property
slInst = JSON.deriveJSON defOpts ''StructureLiteral
baseTyNameToTag :: String -> String
baseTyNameToTag = \case
"Integer" -> "integer"
"UInteger" -> "uinteger"
"Decimal" -> "decimal"
"String" -> "string"
"Boolean" -> "boolean"
"Null" -> "null"
x -> x
baseTyNameInst = JSON.deriveJSON (defOpts{sumEncoding=JSON.UntaggedValue, constructorTagModifier=baseTyNameToTag}) ''BaseTypeName
typeToTag :: String -> String
typeToTag = \case
"BaseType" -> "base"
"ReferenceType" -> "reference"
"ArrayType" -> "array"
"MapType" -> "map"
"AndType" -> "and"
"OrType" -> "or"
"TupleType" -> "tuple"
"StructureLiteralType" -> "literal"
"StringLiteralType" -> "stringLiteral"
"IntegerLiteralType" -> "integerLiteral"
"BooleanLiteralType" -> "booleanLiteral"
x -> x
typeOpts = defOpts
{ sumEncoding=JSON.defaultTaggedObject{tagFieldName="kind"}
, constructorTagModifier=typeToTag
, fieldLabelModifier= \s -> over _head Char.toLower $ Prelude.dropWhile Char.isLower s
}
typeInst = JSON.deriveJSON typeOpts ''Type
reqInst = JSON.deriveJSON defOpts ''Request
notInst = JSON.deriveJSON defOpts ''Notification
sInst = JSON.deriveJSON defOpts ''Structure
taInst = JSON.deriveJSON defOpts ''TypeAlias
tiInst = JSON.deriveJSON (defOpts{sumEncoding=UntaggedValue}) ''TextOrInteger
eeInst = JSON.deriveJSON defOpts ''EnumerationEntry
eInst = JSON.deriveJSON defOpts ''Enumeration
mdInst = JSON.deriveJSON defOpts ''MetaData
mmInst = JSON.deriveJSON defOpts ''MetaModel
in mconcat <$> sequence [ propertyInst, slInst, baseTyNameInst, typeInst, reqInst, notInst, sInst, taInst, tiInst, eeInst, eInst, mdInst, mmInst ]
)
loadMetaModelFromFile :: FilePath -> Q Exp
loadMetaModelFromFile :: String -> Q Exp
loadMetaModelFromFile String
fp = do
String -> Q ()
addDependentFile String
fp
Either String MetaModel
res <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. FromJSON a => String -> IO (Either String a)
JSON.eitherDecodeFileStrict' String
fp
case Either String MetaModel
res of
Left String
e -> forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
e
Right (MetaModel
mm :: MetaModel) -> forall t (m :: * -> *). (Lift t, Quote m) => t -> m Exp
lift MetaModel
mm