{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
module Network.MCP.Types
(
ServerInfo,
ClientInfo,
Implementation (..),
ServerCapabilities (..),
ClientCapabilities (..),
ResourcesCapability (..),
ToolsCapability (..),
PromptsCapability (..),
SamplingCapability (..),
RootsCapability (..),
Resource (..),
ResourceContent (..),
ResourceContentType (..),
Tool (..),
ToolContent (..),
ToolContentType (..),
ToolAnnotations (..),
Prompt (..),
PromptArgument (..),
PromptMessage (..),
PromptContentType (..),
PromptContent (..),
Root (..),
ProtocolVersion,
supportedVersions,
ServerInitializeOptions (..),
ClientInitializeOptions (..),
ServerInitializeResult,
ClientInitializeResult,
ListResourcesRequest (..),
ListResourcesResult (..),
ReadResourceRequest (..),
ReadResourceResult (..),
SubscribeResourceRequest (..),
SubscribeResourceResult (..),
UnsubscribeResourceRequest (..),
UnsubscribeResourceResult (..),
ListToolsRequest (..),
ListToolsResult (..),
CallToolRequest (..),
CallToolResult (..),
ListPromptsRequest (..),
ListPromptsResult (..),
GetPromptRequest (..),
GetPromptResult (..),
ListRootsRequest (..),
ListRootsResult (..),
ResourcesListChangedNotification (..),
ResourceUpdatedNotification (..),
ToolsListChangedNotification (..),
PromptsListChangedNotification (..),
)
where
import Data.Aeson
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Text (Text)
import GHC.Generics
type ProtocolVersion = Text
supportedVersions :: [ProtocolVersion]
supportedVersions :: [ProtocolVersion]
supportedVersions =
[ ProtocolVersion
"2024-11-05"
]
data Implementation = Implementation
{
Implementation -> ProtocolVersion
serverName :: Text,
Implementation -> ProtocolVersion
serverVersion :: Text
}
deriving (Int -> Implementation -> ShowS
[Implementation] -> ShowS
Implementation -> String
(Int -> Implementation -> ShowS)
-> (Implementation -> String)
-> ([Implementation] -> ShowS)
-> Show Implementation
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Implementation -> ShowS
showsPrec :: Int -> Implementation -> ShowS
$cshow :: Implementation -> String
show :: Implementation -> String
$cshowList :: [Implementation] -> ShowS
showList :: [Implementation] -> ShowS
Show, Implementation -> Implementation -> Bool
(Implementation -> Implementation -> Bool)
-> (Implementation -> Implementation -> Bool) -> Eq Implementation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Implementation -> Implementation -> Bool
== :: Implementation -> Implementation -> Bool
$c/= :: Implementation -> Implementation -> Bool
/= :: Implementation -> Implementation -> Bool
Eq, (forall x. Implementation -> Rep Implementation x)
-> (forall x. Rep Implementation x -> Implementation)
-> Generic Implementation
forall x. Rep Implementation x -> Implementation
forall x. Implementation -> Rep Implementation x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Implementation -> Rep Implementation x
from :: forall x. Implementation -> Rep Implementation x
$cto :: forall x. Rep Implementation x -> Implementation
to :: forall x. Rep Implementation x -> Implementation
Generic)
instance ToJSON Implementation where
toJSON :: Implementation -> Value
toJSON Implementation {ProtocolVersion
$sel:serverName:Implementation :: Implementation -> ProtocolVersion
$sel:serverVersion:Implementation :: Implementation -> ProtocolVersion
serverName :: ProtocolVersion
serverVersion :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
serverName,
Key
"version" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
serverVersion
]
instance FromJSON Implementation where
parseJSON :: Value -> Parser Implementation
parseJSON = String
-> (Object -> Parser Implementation)
-> Value
-> Parser Implementation
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Implementation" ((Object -> Parser Implementation)
-> Value -> Parser Implementation)
-> (Object -> Parser Implementation)
-> Value
-> Parser Implementation
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
ProtocolVersion
version <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"version"
return $ ProtocolVersion -> ProtocolVersion -> Implementation
Implementation ProtocolVersion
name ProtocolVersion
version
type ServerInfo = Implementation
type ClientInfo = Implementation
data ResourcesCapability = ResourcesCapability
{
ResourcesCapability -> Bool
resourcesListChanged :: Bool
}
deriving (Int -> ResourcesCapability -> ShowS
[ResourcesCapability] -> ShowS
ResourcesCapability -> String
(Int -> ResourcesCapability -> ShowS)
-> (ResourcesCapability -> String)
-> ([ResourcesCapability] -> ShowS)
-> Show ResourcesCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourcesCapability -> ShowS
showsPrec :: Int -> ResourcesCapability -> ShowS
$cshow :: ResourcesCapability -> String
show :: ResourcesCapability -> String
$cshowList :: [ResourcesCapability] -> ShowS
showList :: [ResourcesCapability] -> ShowS
Show, ResourcesCapability -> ResourcesCapability -> Bool
(ResourcesCapability -> ResourcesCapability -> Bool)
-> (ResourcesCapability -> ResourcesCapability -> Bool)
-> Eq ResourcesCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourcesCapability -> ResourcesCapability -> Bool
== :: ResourcesCapability -> ResourcesCapability -> Bool
$c/= :: ResourcesCapability -> ResourcesCapability -> Bool
/= :: ResourcesCapability -> ResourcesCapability -> Bool
Eq, (forall x. ResourcesCapability -> Rep ResourcesCapability x)
-> (forall x. Rep ResourcesCapability x -> ResourcesCapability)
-> Generic ResourcesCapability
forall x. Rep ResourcesCapability x -> ResourcesCapability
forall x. ResourcesCapability -> Rep ResourcesCapability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResourcesCapability -> Rep ResourcesCapability x
from :: forall x. ResourcesCapability -> Rep ResourcesCapability x
$cto :: forall x. Rep ResourcesCapability x -> ResourcesCapability
to :: forall x. Rep ResourcesCapability x -> ResourcesCapability
Generic)
instance ToJSON ResourcesCapability where
toJSON :: ResourcesCapability -> Value
toJSON ResourcesCapability {Bool
$sel:resourcesListChanged:ResourcesCapability :: ResourcesCapability -> Bool
resourcesListChanged :: Bool
..} =
[Pair] -> Value
object
[ Key
"listChanged" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
resourcesListChanged
]
instance FromJSON ResourcesCapability where
parseJSON :: Value -> Parser ResourcesCapability
parseJSON = String
-> (Object -> Parser ResourcesCapability)
-> Value
-> Parser ResourcesCapability
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResourcesCapability" ((Object -> Parser ResourcesCapability)
-> Value -> Parser ResourcesCapability)
-> (Object -> Parser ResourcesCapability)
-> Value
-> Parser ResourcesCapability
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Bool
listChanged <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"listChanged"
return $ Bool -> ResourcesCapability
ResourcesCapability Bool
listChanged
data ToolsCapability = ToolsCapability
{
ToolsCapability -> Bool
toolsListChanged :: Bool
}
deriving (Int -> ToolsCapability -> ShowS
[ToolsCapability] -> ShowS
ToolsCapability -> String
(Int -> ToolsCapability -> ShowS)
-> (ToolsCapability -> String)
-> ([ToolsCapability] -> ShowS)
-> Show ToolsCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolsCapability -> ShowS
showsPrec :: Int -> ToolsCapability -> ShowS
$cshow :: ToolsCapability -> String
show :: ToolsCapability -> String
$cshowList :: [ToolsCapability] -> ShowS
showList :: [ToolsCapability] -> ShowS
Show, ToolsCapability -> ToolsCapability -> Bool
(ToolsCapability -> ToolsCapability -> Bool)
-> (ToolsCapability -> ToolsCapability -> Bool)
-> Eq ToolsCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolsCapability -> ToolsCapability -> Bool
== :: ToolsCapability -> ToolsCapability -> Bool
$c/= :: ToolsCapability -> ToolsCapability -> Bool
/= :: ToolsCapability -> ToolsCapability -> Bool
Eq, (forall x. ToolsCapability -> Rep ToolsCapability x)
-> (forall x. Rep ToolsCapability x -> ToolsCapability)
-> Generic ToolsCapability
forall x. Rep ToolsCapability x -> ToolsCapability
forall x. ToolsCapability -> Rep ToolsCapability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolsCapability -> Rep ToolsCapability x
from :: forall x. ToolsCapability -> Rep ToolsCapability x
$cto :: forall x. Rep ToolsCapability x -> ToolsCapability
to :: forall x. Rep ToolsCapability x -> ToolsCapability
Generic)
instance ToJSON ToolsCapability where
toJSON :: ToolsCapability -> Value
toJSON ToolsCapability {Bool
$sel:toolsListChanged:ToolsCapability :: ToolsCapability -> Bool
toolsListChanged :: Bool
..} =
[Pair] -> Value
object
[ Key
"listChanged" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
toolsListChanged
]
instance FromJSON ToolsCapability where
parseJSON :: Value -> Parser ToolsCapability
parseJSON = String
-> (Object -> Parser ToolsCapability)
-> Value
-> Parser ToolsCapability
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ToolsCapability" ((Object -> Parser ToolsCapability)
-> Value -> Parser ToolsCapability)
-> (Object -> Parser ToolsCapability)
-> Value
-> Parser ToolsCapability
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Bool
listChanged <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"listChanged"
return $ Bool -> ToolsCapability
ToolsCapability Bool
listChanged
data PromptsCapability = PromptsCapability
{
PromptsCapability -> Bool
promptsListChanged :: Bool
}
deriving (Int -> PromptsCapability -> ShowS
[PromptsCapability] -> ShowS
PromptsCapability -> String
(Int -> PromptsCapability -> ShowS)
-> (PromptsCapability -> String)
-> ([PromptsCapability] -> ShowS)
-> Show PromptsCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptsCapability -> ShowS
showsPrec :: Int -> PromptsCapability -> ShowS
$cshow :: PromptsCapability -> String
show :: PromptsCapability -> String
$cshowList :: [PromptsCapability] -> ShowS
showList :: [PromptsCapability] -> ShowS
Show, PromptsCapability -> PromptsCapability -> Bool
(PromptsCapability -> PromptsCapability -> Bool)
-> (PromptsCapability -> PromptsCapability -> Bool)
-> Eq PromptsCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptsCapability -> PromptsCapability -> Bool
== :: PromptsCapability -> PromptsCapability -> Bool
$c/= :: PromptsCapability -> PromptsCapability -> Bool
/= :: PromptsCapability -> PromptsCapability -> Bool
Eq, (forall x. PromptsCapability -> Rep PromptsCapability x)
-> (forall x. Rep PromptsCapability x -> PromptsCapability)
-> Generic PromptsCapability
forall x. Rep PromptsCapability x -> PromptsCapability
forall x. PromptsCapability -> Rep PromptsCapability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptsCapability -> Rep PromptsCapability x
from :: forall x. PromptsCapability -> Rep PromptsCapability x
$cto :: forall x. Rep PromptsCapability x -> PromptsCapability
to :: forall x. Rep PromptsCapability x -> PromptsCapability
Generic)
instance ToJSON PromptsCapability where
toJSON :: PromptsCapability -> Value
toJSON PromptsCapability {Bool
$sel:promptsListChanged:PromptsCapability :: PromptsCapability -> Bool
promptsListChanged :: Bool
..} =
[Pair] -> Value
object
[ Key
"listChanged" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
promptsListChanged
]
instance FromJSON PromptsCapability where
parseJSON :: Value -> Parser PromptsCapability
parseJSON = String
-> (Object -> Parser PromptsCapability)
-> Value
-> Parser PromptsCapability
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptsCapability" ((Object -> Parser PromptsCapability)
-> Value -> Parser PromptsCapability)
-> (Object -> Parser PromptsCapability)
-> Value
-> Parser PromptsCapability
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Bool
listChanged <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"listChanged"
return $ Bool -> PromptsCapability
PromptsCapability Bool
listChanged
data SamplingCapability = SamplingCapability
deriving (Int -> SamplingCapability -> ShowS
[SamplingCapability] -> ShowS
SamplingCapability -> String
(Int -> SamplingCapability -> ShowS)
-> (SamplingCapability -> String)
-> ([SamplingCapability] -> ShowS)
-> Show SamplingCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SamplingCapability -> ShowS
showsPrec :: Int -> SamplingCapability -> ShowS
$cshow :: SamplingCapability -> String
show :: SamplingCapability -> String
$cshowList :: [SamplingCapability] -> ShowS
showList :: [SamplingCapability] -> ShowS
Show, SamplingCapability -> SamplingCapability -> Bool
(SamplingCapability -> SamplingCapability -> Bool)
-> (SamplingCapability -> SamplingCapability -> Bool)
-> Eq SamplingCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SamplingCapability -> SamplingCapability -> Bool
== :: SamplingCapability -> SamplingCapability -> Bool
$c/= :: SamplingCapability -> SamplingCapability -> Bool
/= :: SamplingCapability -> SamplingCapability -> Bool
Eq, (forall x. SamplingCapability -> Rep SamplingCapability x)
-> (forall x. Rep SamplingCapability x -> SamplingCapability)
-> Generic SamplingCapability
forall x. Rep SamplingCapability x -> SamplingCapability
forall x. SamplingCapability -> Rep SamplingCapability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SamplingCapability -> Rep SamplingCapability x
from :: forall x. SamplingCapability -> Rep SamplingCapability x
$cto :: forall x. Rep SamplingCapability x -> SamplingCapability
to :: forall x. Rep SamplingCapability x -> SamplingCapability
Generic)
instance ToJSON SamplingCapability where
toJSON :: SamplingCapability -> Value
toJSON SamplingCapability
_ = [Pair] -> Value
object []
instance FromJSON SamplingCapability where
parseJSON :: Value -> Parser SamplingCapability
parseJSON = String
-> (Object -> Parser SamplingCapability)
-> Value
-> Parser SamplingCapability
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SamplingCapability" ((Object -> Parser SamplingCapability)
-> Value -> Parser SamplingCapability)
-> (Object -> Parser SamplingCapability)
-> Value
-> Parser SamplingCapability
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
SamplingCapability -> Parser SamplingCapability
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return SamplingCapability
SamplingCapability
data RootsCapability = RootsCapability
deriving (Int -> RootsCapability -> ShowS
[RootsCapability] -> ShowS
RootsCapability -> String
(Int -> RootsCapability -> ShowS)
-> (RootsCapability -> String)
-> ([RootsCapability] -> ShowS)
-> Show RootsCapability
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RootsCapability -> ShowS
showsPrec :: Int -> RootsCapability -> ShowS
$cshow :: RootsCapability -> String
show :: RootsCapability -> String
$cshowList :: [RootsCapability] -> ShowS
showList :: [RootsCapability] -> ShowS
Show, RootsCapability -> RootsCapability -> Bool
(RootsCapability -> RootsCapability -> Bool)
-> (RootsCapability -> RootsCapability -> Bool)
-> Eq RootsCapability
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RootsCapability -> RootsCapability -> Bool
== :: RootsCapability -> RootsCapability -> Bool
$c/= :: RootsCapability -> RootsCapability -> Bool
/= :: RootsCapability -> RootsCapability -> Bool
Eq, (forall x. RootsCapability -> Rep RootsCapability x)
-> (forall x. Rep RootsCapability x -> RootsCapability)
-> Generic RootsCapability
forall x. Rep RootsCapability x -> RootsCapability
forall x. RootsCapability -> Rep RootsCapability x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RootsCapability -> Rep RootsCapability x
from :: forall x. RootsCapability -> Rep RootsCapability x
$cto :: forall x. Rep RootsCapability x -> RootsCapability
to :: forall x. Rep RootsCapability x -> RootsCapability
Generic)
instance ToJSON RootsCapability where
toJSON :: RootsCapability -> Value
toJSON RootsCapability
_ = [Pair] -> Value
object []
instance FromJSON RootsCapability where
parseJSON :: Value -> Parser RootsCapability
parseJSON = String
-> (Object -> Parser RootsCapability)
-> Value
-> Parser RootsCapability
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"RootsCapability" ((Object -> Parser RootsCapability)
-> Value -> Parser RootsCapability)
-> (Object -> Parser RootsCapability)
-> Value
-> Parser RootsCapability
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
RootsCapability -> Parser RootsCapability
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return RootsCapability
RootsCapability
data ServerCapabilities = ServerCapabilities
{
ServerCapabilities -> Maybe ResourcesCapability
resourcesCapability :: Maybe ResourcesCapability,
ServerCapabilities -> Maybe ToolsCapability
toolsCapability :: Maybe ToolsCapability,
ServerCapabilities -> Maybe PromptsCapability
promptsCapability :: Maybe PromptsCapability
}
deriving (Int -> ServerCapabilities -> ShowS
[ServerCapabilities] -> ShowS
ServerCapabilities -> String
(Int -> ServerCapabilities -> ShowS)
-> (ServerCapabilities -> String)
-> ([ServerCapabilities] -> ShowS)
-> Show ServerCapabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerCapabilities -> ShowS
showsPrec :: Int -> ServerCapabilities -> ShowS
$cshow :: ServerCapabilities -> String
show :: ServerCapabilities -> String
$cshowList :: [ServerCapabilities] -> ShowS
showList :: [ServerCapabilities] -> ShowS
Show, ServerCapabilities -> ServerCapabilities -> Bool
(ServerCapabilities -> ServerCapabilities -> Bool)
-> (ServerCapabilities -> ServerCapabilities -> Bool)
-> Eq ServerCapabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerCapabilities -> ServerCapabilities -> Bool
== :: ServerCapabilities -> ServerCapabilities -> Bool
$c/= :: ServerCapabilities -> ServerCapabilities -> Bool
/= :: ServerCapabilities -> ServerCapabilities -> Bool
Eq, (forall x. ServerCapabilities -> Rep ServerCapabilities x)
-> (forall x. Rep ServerCapabilities x -> ServerCapabilities)
-> Generic ServerCapabilities
forall x. Rep ServerCapabilities x -> ServerCapabilities
forall x. ServerCapabilities -> Rep ServerCapabilities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServerCapabilities -> Rep ServerCapabilities x
from :: forall x. ServerCapabilities -> Rep ServerCapabilities x
$cto :: forall x. Rep ServerCapabilities x -> ServerCapabilities
to :: forall x. Rep ServerCapabilities x -> ServerCapabilities
Generic)
instance ToJSON ServerCapabilities where
toJSON :: ServerCapabilities -> Value
toJSON ServerCapabilities {Maybe PromptsCapability
Maybe ToolsCapability
Maybe ResourcesCapability
$sel:resourcesCapability:ServerCapabilities :: ServerCapabilities -> Maybe ResourcesCapability
$sel:toolsCapability:ServerCapabilities :: ServerCapabilities -> Maybe ToolsCapability
$sel:promptsCapability:ServerCapabilities :: ServerCapabilities -> Maybe PromptsCapability
resourcesCapability :: Maybe ResourcesCapability
toolsCapability :: Maybe ToolsCapability
promptsCapability :: Maybe PromptsCapability
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[Key
"resources" Key -> ResourcesCapability -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ResourcesCapability
resources | ResourcesCapability
resources <- Maybe ResourcesCapability -> [ResourcesCapability]
forall a. Maybe a -> [a]
maybeToList Maybe ResourcesCapability
resourcesCapability]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"tools" Key -> ToolsCapability -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ToolsCapability
tools | ToolsCapability
tools <- Maybe ToolsCapability -> [ToolsCapability]
forall a. Maybe a -> [a]
maybeToList Maybe ToolsCapability
toolsCapability]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"prompts" Key -> PromptsCapability -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= PromptsCapability
prompts | PromptsCapability
prompts <- Maybe PromptsCapability -> [PromptsCapability]
forall a. Maybe a -> [a]
maybeToList Maybe PromptsCapability
promptsCapability]
instance FromJSON ServerCapabilities where
parseJSON :: Value -> Parser ServerCapabilities
parseJSON = String
-> (Object -> Parser ServerCapabilities)
-> Value
-> Parser ServerCapabilities
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ServerCapabilities" ((Object -> Parser ServerCapabilities)
-> Value -> Parser ServerCapabilities)
-> (Object -> Parser ServerCapabilities)
-> Value
-> Parser ServerCapabilities
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe ResourcesCapability
resources <- Object
o Object -> Key -> Parser (Maybe ResourcesCapability)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"resources"
Maybe ToolsCapability
tools <- Object
o Object -> Key -> Parser (Maybe ToolsCapability)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"tools"
Maybe PromptsCapability
prompts <- Object
o Object -> Key -> Parser (Maybe PromptsCapability)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"prompts"
return $ Maybe ResourcesCapability
-> Maybe ToolsCapability
-> Maybe PromptsCapability
-> ServerCapabilities
ServerCapabilities Maybe ResourcesCapability
resources Maybe ToolsCapability
tools Maybe PromptsCapability
prompts
data ClientCapabilities = ClientCapabilities
{
ClientCapabilities -> Maybe RootsCapability
clientRootsCapability :: Maybe RootsCapability,
ClientCapabilities -> Maybe SamplingCapability
clientSamplingCapability :: Maybe SamplingCapability
}
deriving (Int -> ClientCapabilities -> ShowS
[ClientCapabilities] -> ShowS
ClientCapabilities -> String
(Int -> ClientCapabilities -> ShowS)
-> (ClientCapabilities -> String)
-> ([ClientCapabilities] -> ShowS)
-> Show ClientCapabilities
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientCapabilities -> ShowS
showsPrec :: Int -> ClientCapabilities -> ShowS
$cshow :: ClientCapabilities -> String
show :: ClientCapabilities -> String
$cshowList :: [ClientCapabilities] -> ShowS
showList :: [ClientCapabilities] -> ShowS
Show, ClientCapabilities -> ClientCapabilities -> Bool
(ClientCapabilities -> ClientCapabilities -> Bool)
-> (ClientCapabilities -> ClientCapabilities -> Bool)
-> Eq ClientCapabilities
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClientCapabilities -> ClientCapabilities -> Bool
== :: ClientCapabilities -> ClientCapabilities -> Bool
$c/= :: ClientCapabilities -> ClientCapabilities -> Bool
/= :: ClientCapabilities -> ClientCapabilities -> Bool
Eq, (forall x. ClientCapabilities -> Rep ClientCapabilities x)
-> (forall x. Rep ClientCapabilities x -> ClientCapabilities)
-> Generic ClientCapabilities
forall x. Rep ClientCapabilities x -> ClientCapabilities
forall x. ClientCapabilities -> Rep ClientCapabilities x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClientCapabilities -> Rep ClientCapabilities x
from :: forall x. ClientCapabilities -> Rep ClientCapabilities x
$cto :: forall x. Rep ClientCapabilities x -> ClientCapabilities
to :: forall x. Rep ClientCapabilities x -> ClientCapabilities
Generic)
instance ToJSON ClientCapabilities where
toJSON :: ClientCapabilities -> Value
toJSON ClientCapabilities {Maybe RootsCapability
Maybe SamplingCapability
$sel:clientRootsCapability:ClientCapabilities :: ClientCapabilities -> Maybe RootsCapability
$sel:clientSamplingCapability:ClientCapabilities :: ClientCapabilities -> Maybe SamplingCapability
clientRootsCapability :: Maybe RootsCapability
clientSamplingCapability :: Maybe SamplingCapability
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[Key
"roots" Key -> RootsCapability -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= RootsCapability
roots | RootsCapability
roots <- Maybe RootsCapability -> [RootsCapability]
forall a. Maybe a -> [a]
maybeToList Maybe RootsCapability
clientRootsCapability]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"sampling" Key -> SamplingCapability -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SamplingCapability
sampling | SamplingCapability
sampling <- Maybe SamplingCapability -> [SamplingCapability]
forall a. Maybe a -> [a]
maybeToList Maybe SamplingCapability
clientSamplingCapability]
instance FromJSON ClientCapabilities where
parseJSON :: Value -> Parser ClientCapabilities
parseJSON = String
-> (Object -> Parser ClientCapabilities)
-> Value
-> Parser ClientCapabilities
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ClientCapabilities" ((Object -> Parser ClientCapabilities)
-> Value -> Parser ClientCapabilities)
-> (Object -> Parser ClientCapabilities)
-> Value
-> Parser ClientCapabilities
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe RootsCapability
roots <- Object
o Object -> Key -> Parser (Maybe RootsCapability)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"roots"
Maybe SamplingCapability
sampling <- Object
o Object -> Key -> Parser (Maybe SamplingCapability)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"sampling"
return $ Maybe RootsCapability
-> Maybe SamplingCapability -> ClientCapabilities
ClientCapabilities Maybe RootsCapability
roots Maybe SamplingCapability
sampling
data Resource = Resource
{
Resource -> ProtocolVersion
resourceUri :: Text,
Resource -> ProtocolVersion
resourceName :: Text,
Resource -> Maybe ProtocolVersion
resourceDescription :: Maybe Text,
Resource -> Maybe ProtocolVersion
resourceMimeType :: Maybe Text,
Resource -> Maybe ProtocolVersion
resourceTemplate :: Maybe Text
}
deriving (Int -> Resource -> ShowS
[Resource] -> ShowS
Resource -> String
(Int -> Resource -> ShowS)
-> (Resource -> String) -> ([Resource] -> ShowS) -> Show Resource
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Resource -> ShowS
showsPrec :: Int -> Resource -> ShowS
$cshow :: Resource -> String
show :: Resource -> String
$cshowList :: [Resource] -> ShowS
showList :: [Resource] -> ShowS
Show, Resource -> Resource -> Bool
(Resource -> Resource -> Bool)
-> (Resource -> Resource -> Bool) -> Eq Resource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Resource -> Resource -> Bool
== :: Resource -> Resource -> Bool
$c/= :: Resource -> Resource -> Bool
/= :: Resource -> Resource -> Bool
Eq, (forall x. Resource -> Rep Resource x)
-> (forall x. Rep Resource x -> Resource) -> Generic Resource
forall x. Rep Resource x -> Resource
forall x. Resource -> Rep Resource x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Resource -> Rep Resource x
from :: forall x. Resource -> Rep Resource x
$cto :: forall x. Rep Resource x -> Resource
to :: forall x. Rep Resource x -> Resource
Generic)
instance ToJSON Resource where
toJSON :: Resource -> Value
toJSON Resource {Maybe ProtocolVersion
ProtocolVersion
$sel:resourceUri:Resource :: Resource -> ProtocolVersion
$sel:resourceName:Resource :: Resource -> ProtocolVersion
$sel:resourceDescription:Resource :: Resource -> Maybe ProtocolVersion
$sel:resourceMimeType:Resource :: Resource -> Maybe ProtocolVersion
$sel:resourceTemplate:Resource :: Resource -> Maybe ProtocolVersion
resourceUri :: ProtocolVersion
resourceName :: ProtocolVersion
resourceDescription :: Maybe ProtocolVersion
resourceMimeType :: Maybe ProtocolVersion
resourceTemplate :: Maybe ProtocolVersion
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
resourceUri,
Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
resourceName
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"description" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
d | ProtocolVersion
d <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceDescription]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"mimeType" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
m | ProtocolVersion
m <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceMimeType]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"template" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
t | ProtocolVersion
t <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceTemplate]
instance FromJSON Resource where
parseJSON :: Value -> Parser Resource
parseJSON = String -> (Object -> Parser Resource) -> Value -> Parser Resource
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Resource" ((Object -> Parser Resource) -> Value -> Parser Resource)
-> (Object -> Parser Resource) -> Value -> Parser Resource
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Maybe ProtocolVersion
description <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
Maybe ProtocolVersion
mimeType <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mimeType"
Maybe ProtocolVersion
template <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"template"
return $ ProtocolVersion
-> ProtocolVersion
-> Maybe ProtocolVersion
-> Maybe ProtocolVersion
-> Maybe ProtocolVersion
-> Resource
Resource ProtocolVersion
uri ProtocolVersion
name Maybe ProtocolVersion
description Maybe ProtocolVersion
mimeType Maybe ProtocolVersion
template
data ResourceContentType = TextContent | BlobContent
deriving (Int -> ResourceContentType -> ShowS
[ResourceContentType] -> ShowS
ResourceContentType -> String
(Int -> ResourceContentType -> ShowS)
-> (ResourceContentType -> String)
-> ([ResourceContentType] -> ShowS)
-> Show ResourceContentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceContentType -> ShowS
showsPrec :: Int -> ResourceContentType -> ShowS
$cshow :: ResourceContentType -> String
show :: ResourceContentType -> String
$cshowList :: [ResourceContentType] -> ShowS
showList :: [ResourceContentType] -> ShowS
Show, ResourceContentType -> ResourceContentType -> Bool
(ResourceContentType -> ResourceContentType -> Bool)
-> (ResourceContentType -> ResourceContentType -> Bool)
-> Eq ResourceContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceContentType -> ResourceContentType -> Bool
== :: ResourceContentType -> ResourceContentType -> Bool
$c/= :: ResourceContentType -> ResourceContentType -> Bool
/= :: ResourceContentType -> ResourceContentType -> Bool
Eq, (forall x. ResourceContentType -> Rep ResourceContentType x)
-> (forall x. Rep ResourceContentType x -> ResourceContentType)
-> Generic ResourceContentType
forall x. Rep ResourceContentType x -> ResourceContentType
forall x. ResourceContentType -> Rep ResourceContentType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResourceContentType -> Rep ResourceContentType x
from :: forall x. ResourceContentType -> Rep ResourceContentType x
$cto :: forall x. Rep ResourceContentType x -> ResourceContentType
to :: forall x. Rep ResourceContentType x -> ResourceContentType
Generic)
data ResourceContent = ResourceContent
{
ResourceContent -> ProtocolVersion
resourceContentUri :: Text,
ResourceContent -> Maybe ProtocolVersion
resourceContentMimeType :: Maybe Text,
ResourceContent -> Maybe ProtocolVersion
resourceContentText :: Maybe Text,
ResourceContent -> Maybe ProtocolVersion
resourceContentBlob :: Maybe Text
}
deriving (Int -> ResourceContent -> ShowS
[ResourceContent] -> ShowS
ResourceContent -> String
(Int -> ResourceContent -> ShowS)
-> (ResourceContent -> String)
-> ([ResourceContent] -> ShowS)
-> Show ResourceContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceContent -> ShowS
showsPrec :: Int -> ResourceContent -> ShowS
$cshow :: ResourceContent -> String
show :: ResourceContent -> String
$cshowList :: [ResourceContent] -> ShowS
showList :: [ResourceContent] -> ShowS
Show, ResourceContent -> ResourceContent -> Bool
(ResourceContent -> ResourceContent -> Bool)
-> (ResourceContent -> ResourceContent -> Bool)
-> Eq ResourceContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceContent -> ResourceContent -> Bool
== :: ResourceContent -> ResourceContent -> Bool
$c/= :: ResourceContent -> ResourceContent -> Bool
/= :: ResourceContent -> ResourceContent -> Bool
Eq, (forall x. ResourceContent -> Rep ResourceContent x)
-> (forall x. Rep ResourceContent x -> ResourceContent)
-> Generic ResourceContent
forall x. Rep ResourceContent x -> ResourceContent
forall x. ResourceContent -> Rep ResourceContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ResourceContent -> Rep ResourceContent x
from :: forall x. ResourceContent -> Rep ResourceContent x
$cto :: forall x. Rep ResourceContent x -> ResourceContent
to :: forall x. Rep ResourceContent x -> ResourceContent
Generic)
instance ToJSON ResourceContent where
toJSON :: ResourceContent -> Value
toJSON ResourceContent {Maybe ProtocolVersion
ProtocolVersion
$sel:resourceContentUri:ResourceContent :: ResourceContent -> ProtocolVersion
$sel:resourceContentMimeType:ResourceContent :: ResourceContent -> Maybe ProtocolVersion
$sel:resourceContentText:ResourceContent :: ResourceContent -> Maybe ProtocolVersion
$sel:resourceContentBlob:ResourceContent :: ResourceContent -> Maybe ProtocolVersion
resourceContentUri :: ProtocolVersion
resourceContentMimeType :: Maybe ProtocolVersion
resourceContentText :: Maybe ProtocolVersion
resourceContentBlob :: Maybe ProtocolVersion
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
resourceContentUri
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"mimeType" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
m | ProtocolVersion
m <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceContentMimeType]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"text" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
t | ProtocolVersion
t <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceContentText]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"blob" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
b | ProtocolVersion
b <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
resourceContentBlob]
instance FromJSON ResourceContent where
parseJSON :: Value -> Parser ResourceContent
parseJSON = String
-> (Object -> Parser ResourceContent)
-> Value
-> Parser ResourceContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResourceContent" ((Object -> Parser ResourceContent)
-> Value -> Parser ResourceContent)
-> (Object -> Parser ResourceContent)
-> Value
-> Parser ResourceContent
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
Maybe ProtocolVersion
mimeType <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"mimeType"
Maybe ProtocolVersion
text <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"text"
Maybe ProtocolVersion
blob <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"blob"
return $ ProtocolVersion
-> Maybe ProtocolVersion
-> Maybe ProtocolVersion
-> Maybe ProtocolVersion
-> ResourceContent
ResourceContent ProtocolVersion
uri Maybe ProtocolVersion
mimeType Maybe ProtocolVersion
text Maybe ProtocolVersion
blob
data ToolAnnotations = ToolAnnotations
{
ToolAnnotations -> Maybe ProtocolVersion
title :: Maybe Text,
ToolAnnotations -> Maybe Bool
readOnlyHint :: Maybe Bool,
ToolAnnotations -> Maybe Bool
destructiveHint :: Maybe Bool,
ToolAnnotations -> Maybe Bool
idempotentHint :: Maybe Bool,
ToolAnnotations -> Maybe Bool
openWorldHint :: Maybe Bool
}
deriving (Int -> ToolAnnotations -> ShowS
[ToolAnnotations] -> ShowS
ToolAnnotations -> String
(Int -> ToolAnnotations -> ShowS)
-> (ToolAnnotations -> String)
-> ([ToolAnnotations] -> ShowS)
-> Show ToolAnnotations
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolAnnotations -> ShowS
showsPrec :: Int -> ToolAnnotations -> ShowS
$cshow :: ToolAnnotations -> String
show :: ToolAnnotations -> String
$cshowList :: [ToolAnnotations] -> ShowS
showList :: [ToolAnnotations] -> ShowS
Show, ToolAnnotations -> ToolAnnotations -> Bool
(ToolAnnotations -> ToolAnnotations -> Bool)
-> (ToolAnnotations -> ToolAnnotations -> Bool)
-> Eq ToolAnnotations
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolAnnotations -> ToolAnnotations -> Bool
== :: ToolAnnotations -> ToolAnnotations -> Bool
$c/= :: ToolAnnotations -> ToolAnnotations -> Bool
/= :: ToolAnnotations -> ToolAnnotations -> Bool
Eq, (forall x. ToolAnnotations -> Rep ToolAnnotations x)
-> (forall x. Rep ToolAnnotations x -> ToolAnnotations)
-> Generic ToolAnnotations
forall x. Rep ToolAnnotations x -> ToolAnnotations
forall x. ToolAnnotations -> Rep ToolAnnotations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolAnnotations -> Rep ToolAnnotations x
from :: forall x. ToolAnnotations -> Rep ToolAnnotations x
$cto :: forall x. Rep ToolAnnotations x -> ToolAnnotations
to :: forall x. Rep ToolAnnotations x -> ToolAnnotations
Generic)
instance ToJSON ToolAnnotations where
toJSON :: ToolAnnotations -> Value
toJSON ToolAnnotations {Maybe Bool
Maybe ProtocolVersion
$sel:title:ToolAnnotations :: ToolAnnotations -> Maybe ProtocolVersion
$sel:readOnlyHint:ToolAnnotations :: ToolAnnotations -> Maybe Bool
$sel:destructiveHint:ToolAnnotations :: ToolAnnotations -> Maybe Bool
$sel:idempotentHint:ToolAnnotations :: ToolAnnotations -> Maybe Bool
$sel:openWorldHint:ToolAnnotations :: ToolAnnotations -> Maybe Bool
title :: Maybe ProtocolVersion
readOnlyHint :: Maybe Bool
destructiveHint :: Maybe Bool
idempotentHint :: Maybe Bool
openWorldHint :: Maybe Bool
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"title" Key -> Maybe ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe ProtocolVersion
title,
Key
"readOnly" Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Bool
readOnlyHint,
Key
"destructive" Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Bool
destructiveHint,
Key
"idempotent" Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Bool
idempotentHint,
Key
"openWorld" Key -> Maybe Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Maybe Bool
openWorldHint
]
instance FromJSON ToolAnnotations where
parseJSON :: Value -> Parser ToolAnnotations
parseJSON = String
-> (Object -> Parser ToolAnnotations)
-> Value
-> Parser ToolAnnotations
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ToolAnnotations" ((Object -> Parser ToolAnnotations)
-> Value -> Parser ToolAnnotations)
-> (Object -> Parser ToolAnnotations)
-> Value
-> Parser ToolAnnotations
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe ProtocolVersion
title <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"title"
Maybe Bool
readOnly <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"readOnly"
Maybe Bool
destructive <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"destructive"
Maybe Bool
idempotent <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"idempotent"
Maybe Bool
openWorld <- Object
o Object -> Key -> Parser (Maybe Bool)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"openWorld"
return $ Maybe ProtocolVersion
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> Maybe Bool
-> ToolAnnotations
ToolAnnotations Maybe ProtocolVersion
title Maybe Bool
readOnly Maybe Bool
destructive Maybe Bool
idempotent Maybe Bool
openWorld
data Tool = Tool
{
Tool -> ProtocolVersion
toolName :: Text,
Tool -> Maybe ProtocolVersion
toolDescription :: Maybe Text,
Tool -> Value
toolInputSchema :: Value,
Tool -> Maybe ToolAnnotations
toolAnnotations :: Maybe ToolAnnotations
}
deriving (Int -> Tool -> ShowS
[Tool] -> ShowS
Tool -> String
(Int -> Tool -> ShowS)
-> (Tool -> String) -> ([Tool] -> ShowS) -> Show Tool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Tool -> ShowS
showsPrec :: Int -> Tool -> ShowS
$cshow :: Tool -> String
show :: Tool -> String
$cshowList :: [Tool] -> ShowS
showList :: [Tool] -> ShowS
Show, Tool -> Tool -> Bool
(Tool -> Tool -> Bool) -> (Tool -> Tool -> Bool) -> Eq Tool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Tool -> Tool -> Bool
== :: Tool -> Tool -> Bool
$c/= :: Tool -> Tool -> Bool
/= :: Tool -> Tool -> Bool
Eq, (forall x. Tool -> Rep Tool x)
-> (forall x. Rep Tool x -> Tool) -> Generic Tool
forall x. Rep Tool x -> Tool
forall x. Tool -> Rep Tool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Tool -> Rep Tool x
from :: forall x. Tool -> Rep Tool x
$cto :: forall x. Rep Tool x -> Tool
to :: forall x. Rep Tool x -> Tool
Generic)
instance ToJSON Tool where
toJSON :: Tool -> Value
toJSON Tool {Maybe ProtocolVersion
Maybe ToolAnnotations
Value
ProtocolVersion
$sel:toolName:Tool :: Tool -> ProtocolVersion
$sel:toolDescription:Tool :: Tool -> Maybe ProtocolVersion
$sel:toolInputSchema:Tool :: Tool -> Value
$sel:toolAnnotations:Tool :: Tool -> Maybe ToolAnnotations
toolName :: ProtocolVersion
toolDescription :: Maybe ProtocolVersion
toolInputSchema :: Value
toolAnnotations :: Maybe ToolAnnotations
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
toolName,
Key
"inputSchema" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Value
toolInputSchema
]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Key
"description" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
d | ProtocolVersion
d <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
toolDescription]
[Pair] -> [Pair] -> [Pair]
forall a. Semigroup a => a -> a -> a
<> [Key
"annotations" Key -> ToolAnnotations -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ToolAnnotations
a | ToolAnnotations
a <- Maybe ToolAnnotations -> [ToolAnnotations]
forall a. Maybe a -> [a]
maybeToList Maybe ToolAnnotations
toolAnnotations]
instance FromJSON Tool where
parseJSON :: Value -> Parser Tool
parseJSON = String -> (Object -> Parser Tool) -> Value -> Parser Tool
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Tool" ((Object -> Parser Tool) -> Value -> Parser Tool)
-> (Object -> Parser Tool) -> Value -> Parser Tool
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Maybe ProtocolVersion
description <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
Value
inputSchema <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"inputSchema"
Maybe ToolAnnotations
annotations <- Object
o Object -> Key -> Parser (Maybe ToolAnnotations)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"annotations"
return $ ProtocolVersion
-> Maybe ProtocolVersion -> Value -> Maybe ToolAnnotations -> Tool
Tool ProtocolVersion
name Maybe ProtocolVersion
description Value
inputSchema Maybe ToolAnnotations
annotations
data ToolContentType = TextualContent | ImageContent | EmbeddedResource
deriving (Int -> ToolContentType -> ShowS
[ToolContentType] -> ShowS
ToolContentType -> String
(Int -> ToolContentType -> ShowS)
-> (ToolContentType -> String)
-> ([ToolContentType] -> ShowS)
-> Show ToolContentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolContentType -> ShowS
showsPrec :: Int -> ToolContentType -> ShowS
$cshow :: ToolContentType -> String
show :: ToolContentType -> String
$cshowList :: [ToolContentType] -> ShowS
showList :: [ToolContentType] -> ShowS
Show, ToolContentType -> ToolContentType -> Bool
(ToolContentType -> ToolContentType -> Bool)
-> (ToolContentType -> ToolContentType -> Bool)
-> Eq ToolContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolContentType -> ToolContentType -> Bool
== :: ToolContentType -> ToolContentType -> Bool
$c/= :: ToolContentType -> ToolContentType -> Bool
/= :: ToolContentType -> ToolContentType -> Bool
Eq, (forall x. ToolContentType -> Rep ToolContentType x)
-> (forall x. Rep ToolContentType x -> ToolContentType)
-> Generic ToolContentType
forall x. Rep ToolContentType x -> ToolContentType
forall x. ToolContentType -> Rep ToolContentType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolContentType -> Rep ToolContentType x
from :: forall x. ToolContentType -> Rep ToolContentType x
$cto :: forall x. Rep ToolContentType x -> ToolContentType
to :: forall x. Rep ToolContentType x -> ToolContentType
Generic)
instance ToJSON ToolContentType where
toJSON :: ToolContentType -> Value
toJSON ToolContentType
TextualContent = ProtocolVersion -> Value
String ProtocolVersion
"text"
toJSON ToolContentType
ImageContent = ProtocolVersion -> Value
String ProtocolVersion
"image"
toJSON ToolContentType
EmbeddedResource = ProtocolVersion -> Value
String ProtocolVersion
"resource"
instance FromJSON ToolContentType where
parseJSON :: Value -> Parser ToolContentType
parseJSON = String
-> (ProtocolVersion -> Parser ToolContentType)
-> Value
-> Parser ToolContentType
forall a.
String -> (ProtocolVersion -> Parser a) -> Value -> Parser a
withText String
"ToolContentType" ((ProtocolVersion -> Parser ToolContentType)
-> Value -> Parser ToolContentType)
-> (ProtocolVersion -> Parser ToolContentType)
-> Value
-> Parser ToolContentType
forall a b. (a -> b) -> a -> b
$ \case
ProtocolVersion
"text" -> ToolContentType -> Parser ToolContentType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolContentType
TextualContent
ProtocolVersion
"image" -> ToolContentType -> Parser ToolContentType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolContentType
ImageContent
ProtocolVersion
"resource" -> ToolContentType -> Parser ToolContentType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolContentType
EmbeddedResource
ProtocolVersion
_ -> String -> Parser ToolContentType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid tool content type"
data ToolContent = ToolContent
{
ToolContent -> ToolContentType
toolContentType :: ToolContentType,
ToolContent -> Maybe ProtocolVersion
toolContentText :: Maybe Text
}
deriving (Int -> ToolContent -> ShowS
[ToolContent] -> ShowS
ToolContent -> String
(Int -> ToolContent -> ShowS)
-> (ToolContent -> String)
-> ([ToolContent] -> ShowS)
-> Show ToolContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolContent -> ShowS
showsPrec :: Int -> ToolContent -> ShowS
$cshow :: ToolContent -> String
show :: ToolContent -> String
$cshowList :: [ToolContent] -> ShowS
showList :: [ToolContent] -> ShowS
Show, ToolContent -> ToolContent -> Bool
(ToolContent -> ToolContent -> Bool)
-> (ToolContent -> ToolContent -> Bool) -> Eq ToolContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolContent -> ToolContent -> Bool
== :: ToolContent -> ToolContent -> Bool
$c/= :: ToolContent -> ToolContent -> Bool
/= :: ToolContent -> ToolContent -> Bool
Eq, (forall x. ToolContent -> Rep ToolContent x)
-> (forall x. Rep ToolContent x -> ToolContent)
-> Generic ToolContent
forall x. Rep ToolContent x -> ToolContent
forall x. ToolContent -> Rep ToolContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ToolContent -> Rep ToolContent x
from :: forall x. ToolContent -> Rep ToolContent x
$cto :: forall x. Rep ToolContent x -> ToolContent
to :: forall x. Rep ToolContent x -> ToolContent
Generic)
instance ToJSON ToolContent where
toJSON :: ToolContent -> Value
toJSON ToolContent {Maybe ProtocolVersion
ToolContentType
$sel:toolContentType:ToolContent :: ToolContent -> ToolContentType
$sel:toolContentText:ToolContent :: ToolContent -> Maybe ProtocolVersion
toolContentType :: ToolContentType
toolContentText :: Maybe ProtocolVersion
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"type" Key -> ToolContentType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ToolContentType
toolContentType
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"text" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
t | ProtocolVersion
t <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
toolContentText]
instance FromJSON ToolContent where
parseJSON :: Value -> Parser ToolContent
parseJSON = String
-> (Object -> Parser ToolContent) -> Value -> Parser ToolContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ToolContent" ((Object -> Parser ToolContent) -> Value -> Parser ToolContent)
-> (Object -> Parser ToolContent) -> Value -> Parser ToolContent
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ToolContentType
contentType <- Object
o Object -> Key -> Parser ToolContentType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
Maybe ProtocolVersion
text <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"text"
return $ ToolContentType -> Maybe ProtocolVersion -> ToolContent
ToolContent ToolContentType
contentType Maybe ProtocolVersion
text
data PromptArgument = PromptArgument
{
PromptArgument -> ProtocolVersion
promptArgumentName :: Text,
PromptArgument -> Maybe ProtocolVersion
promptArgumentDescription :: Maybe Text,
PromptArgument -> Bool
promptArgumentRequired :: Bool
}
deriving (Int -> PromptArgument -> ShowS
[PromptArgument] -> ShowS
PromptArgument -> String
(Int -> PromptArgument -> ShowS)
-> (PromptArgument -> String)
-> ([PromptArgument] -> ShowS)
-> Show PromptArgument
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptArgument -> ShowS
showsPrec :: Int -> PromptArgument -> ShowS
$cshow :: PromptArgument -> String
show :: PromptArgument -> String
$cshowList :: [PromptArgument] -> ShowS
showList :: [PromptArgument] -> ShowS
Show, PromptArgument -> PromptArgument -> Bool
(PromptArgument -> PromptArgument -> Bool)
-> (PromptArgument -> PromptArgument -> Bool) -> Eq PromptArgument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptArgument -> PromptArgument -> Bool
== :: PromptArgument -> PromptArgument -> Bool
$c/= :: PromptArgument -> PromptArgument -> Bool
/= :: PromptArgument -> PromptArgument -> Bool
Eq, (forall x. PromptArgument -> Rep PromptArgument x)
-> (forall x. Rep PromptArgument x -> PromptArgument)
-> Generic PromptArgument
forall x. Rep PromptArgument x -> PromptArgument
forall x. PromptArgument -> Rep PromptArgument x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptArgument -> Rep PromptArgument x
from :: forall x. PromptArgument -> Rep PromptArgument x
$cto :: forall x. Rep PromptArgument x -> PromptArgument
to :: forall x. Rep PromptArgument x -> PromptArgument
Generic)
instance ToJSON PromptArgument where
toJSON :: PromptArgument -> Value
toJSON PromptArgument {Bool
Maybe ProtocolVersion
ProtocolVersion
$sel:promptArgumentName:PromptArgument :: PromptArgument -> ProtocolVersion
$sel:promptArgumentDescription:PromptArgument :: PromptArgument -> Maybe ProtocolVersion
$sel:promptArgumentRequired:PromptArgument :: PromptArgument -> Bool
promptArgumentName :: ProtocolVersion
promptArgumentDescription :: Maybe ProtocolVersion
promptArgumentRequired :: Bool
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
promptArgumentName,
Key
"required" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
promptArgumentRequired
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"description" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
d | ProtocolVersion
d <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
promptArgumentDescription]
instance FromJSON PromptArgument where
parseJSON :: Value -> Parser PromptArgument
parseJSON = String
-> (Object -> Parser PromptArgument)
-> Value
-> Parser PromptArgument
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptArgument" ((Object -> Parser PromptArgument)
-> Value -> Parser PromptArgument)
-> (Object -> Parser PromptArgument)
-> Value
-> Parser PromptArgument
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Maybe ProtocolVersion
description <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
Bool
required <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"required"
return $ ProtocolVersion -> Maybe ProtocolVersion -> Bool -> PromptArgument
PromptArgument ProtocolVersion
name Maybe ProtocolVersion
description Bool
required
data Prompt = Prompt
{
Prompt -> ProtocolVersion
promptName :: Text,
Prompt -> Maybe ProtocolVersion
promptDescription :: Maybe Text,
Prompt -> [PromptArgument]
promptArguments :: [PromptArgument]
}
deriving (Int -> Prompt -> ShowS
[Prompt] -> ShowS
Prompt -> String
(Int -> Prompt -> ShowS)
-> (Prompt -> String) -> ([Prompt] -> ShowS) -> Show Prompt
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Prompt -> ShowS
showsPrec :: Int -> Prompt -> ShowS
$cshow :: Prompt -> String
show :: Prompt -> String
$cshowList :: [Prompt] -> ShowS
showList :: [Prompt] -> ShowS
Show, Prompt -> Prompt -> Bool
(Prompt -> Prompt -> Bool)
-> (Prompt -> Prompt -> Bool) -> Eq Prompt
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Prompt -> Prompt -> Bool
== :: Prompt -> Prompt -> Bool
$c/= :: Prompt -> Prompt -> Bool
/= :: Prompt -> Prompt -> Bool
Eq, (forall x. Prompt -> Rep Prompt x)
-> (forall x. Rep Prompt x -> Prompt) -> Generic Prompt
forall x. Rep Prompt x -> Prompt
forall x. Prompt -> Rep Prompt x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Prompt -> Rep Prompt x
from :: forall x. Prompt -> Rep Prompt x
$cto :: forall x. Rep Prompt x -> Prompt
to :: forall x. Rep Prompt x -> Prompt
Generic)
instance ToJSON Prompt where
toJSON :: Prompt -> Value
toJSON Prompt {[PromptArgument]
Maybe ProtocolVersion
ProtocolVersion
$sel:promptName:Prompt :: Prompt -> ProtocolVersion
$sel:promptDescription:Prompt :: Prompt -> Maybe ProtocolVersion
$sel:promptArguments:Prompt :: Prompt -> [PromptArgument]
promptName :: ProtocolVersion
promptDescription :: Maybe ProtocolVersion
promptArguments :: [PromptArgument]
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
promptName,
Key
"arguments" Key -> [PromptArgument] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [PromptArgument]
promptArguments
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"description" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
d | ProtocolVersion
d <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
promptDescription]
instance FromJSON Prompt where
parseJSON :: Value -> Parser Prompt
parseJSON = String -> (Object -> Parser Prompt) -> Value -> Parser Prompt
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Prompt" ((Object -> Parser Prompt) -> Value -> Parser Prompt)
-> (Object -> Parser Prompt) -> Value -> Parser Prompt
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Maybe ProtocolVersion
description <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
[PromptArgument]
arguments <- Object
o Object -> Key -> Parser [PromptArgument]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"arguments"
return $ ProtocolVersion
-> Maybe ProtocolVersion -> [PromptArgument] -> Prompt
Prompt ProtocolVersion
name Maybe ProtocolVersion
description [PromptArgument]
arguments
data PromptContentType = TextPromptContent | ResourcePromptContent
deriving (Int -> PromptContentType -> ShowS
[PromptContentType] -> ShowS
PromptContentType -> String
(Int -> PromptContentType -> ShowS)
-> (PromptContentType -> String)
-> ([PromptContentType] -> ShowS)
-> Show PromptContentType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptContentType -> ShowS
showsPrec :: Int -> PromptContentType -> ShowS
$cshow :: PromptContentType -> String
show :: PromptContentType -> String
$cshowList :: [PromptContentType] -> ShowS
showList :: [PromptContentType] -> ShowS
Show, PromptContentType -> PromptContentType -> Bool
(PromptContentType -> PromptContentType -> Bool)
-> (PromptContentType -> PromptContentType -> Bool)
-> Eq PromptContentType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptContentType -> PromptContentType -> Bool
== :: PromptContentType -> PromptContentType -> Bool
$c/= :: PromptContentType -> PromptContentType -> Bool
/= :: PromptContentType -> PromptContentType -> Bool
Eq, (forall x. PromptContentType -> Rep PromptContentType x)
-> (forall x. Rep PromptContentType x -> PromptContentType)
-> Generic PromptContentType
forall x. Rep PromptContentType x -> PromptContentType
forall x. PromptContentType -> Rep PromptContentType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptContentType -> Rep PromptContentType x
from :: forall x. PromptContentType -> Rep PromptContentType x
$cto :: forall x. Rep PromptContentType x -> PromptContentType
to :: forall x. Rep PromptContentType x -> PromptContentType
Generic)
instance ToJSON PromptContentType where
toJSON :: PromptContentType -> Value
toJSON PromptContentType
TextPromptContent = ProtocolVersion -> Value
String ProtocolVersion
"text"
toJSON PromptContentType
ResourcePromptContent = ProtocolVersion -> Value
String ProtocolVersion
"resource"
instance FromJSON PromptContentType where
parseJSON :: Value -> Parser PromptContentType
parseJSON = String
-> (ProtocolVersion -> Parser PromptContentType)
-> Value
-> Parser PromptContentType
forall a.
String -> (ProtocolVersion -> Parser a) -> Value -> Parser a
withText String
"PromptContentType" ((ProtocolVersion -> Parser PromptContentType)
-> Value -> Parser PromptContentType)
-> (ProtocolVersion -> Parser PromptContentType)
-> Value
-> Parser PromptContentType
forall a b. (a -> b) -> a -> b
$ \case
ProtocolVersion
"text" -> PromptContentType -> Parser PromptContentType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PromptContentType
TextPromptContent
ProtocolVersion
"resource" -> PromptContentType -> Parser PromptContentType
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PromptContentType
ResourcePromptContent
ProtocolVersion
_ -> String -> Parser PromptContentType
forall a. String -> Parser a
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Invalid prompt content type"
data PromptContent = PromptContent
{
PromptContent -> PromptContentType
promptContentType :: PromptContentType,
PromptContent -> ProtocolVersion
promptContentText :: Text
}
deriving (Int -> PromptContent -> ShowS
[PromptContent] -> ShowS
PromptContent -> String
(Int -> PromptContent -> ShowS)
-> (PromptContent -> String)
-> ([PromptContent] -> ShowS)
-> Show PromptContent
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptContent -> ShowS
showsPrec :: Int -> PromptContent -> ShowS
$cshow :: PromptContent -> String
show :: PromptContent -> String
$cshowList :: [PromptContent] -> ShowS
showList :: [PromptContent] -> ShowS
Show, PromptContent -> PromptContent -> Bool
(PromptContent -> PromptContent -> Bool)
-> (PromptContent -> PromptContent -> Bool) -> Eq PromptContent
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptContent -> PromptContent -> Bool
== :: PromptContent -> PromptContent -> Bool
$c/= :: PromptContent -> PromptContent -> Bool
/= :: PromptContent -> PromptContent -> Bool
Eq, (forall x. PromptContent -> Rep PromptContent x)
-> (forall x. Rep PromptContent x -> PromptContent)
-> Generic PromptContent
forall x. Rep PromptContent x -> PromptContent
forall x. PromptContent -> Rep PromptContent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptContent -> Rep PromptContent x
from :: forall x. PromptContent -> Rep PromptContent x
$cto :: forall x. Rep PromptContent x -> PromptContent
to :: forall x. Rep PromptContent x -> PromptContent
Generic)
instance ToJSON PromptContent where
toJSON :: PromptContent -> Value
toJSON PromptContent {ProtocolVersion
PromptContentType
$sel:promptContentType:PromptContent :: PromptContent -> PromptContentType
$sel:promptContentText:PromptContent :: PromptContent -> ProtocolVersion
promptContentType :: PromptContentType
promptContentText :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"type" Key -> PromptContentType -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= PromptContentType
promptContentType,
Key
"text" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
promptContentText
]
instance FromJSON PromptContent where
parseJSON :: Value -> Parser PromptContent
parseJSON = String
-> (Object -> Parser PromptContent)
-> Value
-> Parser PromptContent
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptContent" ((Object -> Parser PromptContent) -> Value -> Parser PromptContent)
-> (Object -> Parser PromptContent)
-> Value
-> Parser PromptContent
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
PromptContentType
contentType <- Object
o Object -> Key -> Parser PromptContentType
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"type"
ProtocolVersion
text <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"text"
return $ PromptContentType -> ProtocolVersion -> PromptContent
PromptContent PromptContentType
contentType ProtocolVersion
text
data PromptMessage = PromptMessage
{
PromptMessage -> ProtocolVersion
promptMessageRole :: Text,
PromptMessage -> PromptContent
promptMessageContent :: PromptContent
}
deriving (Int -> PromptMessage -> ShowS
[PromptMessage] -> ShowS
PromptMessage -> String
(Int -> PromptMessage -> ShowS)
-> (PromptMessage -> String)
-> ([PromptMessage] -> ShowS)
-> Show PromptMessage
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptMessage -> ShowS
showsPrec :: Int -> PromptMessage -> ShowS
$cshow :: PromptMessage -> String
show :: PromptMessage -> String
$cshowList :: [PromptMessage] -> ShowS
showList :: [PromptMessage] -> ShowS
Show, PromptMessage -> PromptMessage -> Bool
(PromptMessage -> PromptMessage -> Bool)
-> (PromptMessage -> PromptMessage -> Bool) -> Eq PromptMessage
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptMessage -> PromptMessage -> Bool
== :: PromptMessage -> PromptMessage -> Bool
$c/= :: PromptMessage -> PromptMessage -> Bool
/= :: PromptMessage -> PromptMessage -> Bool
Eq, (forall x. PromptMessage -> Rep PromptMessage x)
-> (forall x. Rep PromptMessage x -> PromptMessage)
-> Generic PromptMessage
forall x. Rep PromptMessage x -> PromptMessage
forall x. PromptMessage -> Rep PromptMessage x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PromptMessage -> Rep PromptMessage x
from :: forall x. PromptMessage -> Rep PromptMessage x
$cto :: forall x. Rep PromptMessage x -> PromptMessage
to :: forall x. Rep PromptMessage x -> PromptMessage
Generic)
instance ToJSON PromptMessage where
toJSON :: PromptMessage -> Value
toJSON PromptMessage {ProtocolVersion
PromptContent
$sel:promptMessageRole:PromptMessage :: PromptMessage -> ProtocolVersion
$sel:promptMessageContent:PromptMessage :: PromptMessage -> PromptContent
promptMessageRole :: ProtocolVersion
promptMessageContent :: PromptContent
..} =
[Pair] -> Value
object
[ Key
"role" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
promptMessageRole,
Key
"content" Key -> PromptContent -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= PromptContent
promptMessageContent
]
instance FromJSON PromptMessage where
parseJSON :: Value -> Parser PromptMessage
parseJSON = String
-> (Object -> Parser PromptMessage)
-> Value
-> Parser PromptMessage
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptMessage" ((Object -> Parser PromptMessage) -> Value -> Parser PromptMessage)
-> (Object -> Parser PromptMessage)
-> Value
-> Parser PromptMessage
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
role <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"role"
PromptContent
content <- Object
o Object -> Key -> Parser PromptContent
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
return $ ProtocolVersion -> PromptContent -> PromptMessage
PromptMessage ProtocolVersion
role PromptContent
content
data Root = Root
{
Root -> ProtocolVersion
rootUri :: Text,
Root -> ProtocolVersion
rootName :: Text
}
deriving (Int -> Root -> ShowS
[Root] -> ShowS
Root -> String
(Int -> Root -> ShowS)
-> (Root -> String) -> ([Root] -> ShowS) -> Show Root
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Root -> ShowS
showsPrec :: Int -> Root -> ShowS
$cshow :: Root -> String
show :: Root -> String
$cshowList :: [Root] -> ShowS
showList :: [Root] -> ShowS
Show, Root -> Root -> Bool
(Root -> Root -> Bool) -> (Root -> Root -> Bool) -> Eq Root
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Root -> Root -> Bool
== :: Root -> Root -> Bool
$c/= :: Root -> Root -> Bool
/= :: Root -> Root -> Bool
Eq, (forall x. Root -> Rep Root x)
-> (forall x. Rep Root x -> Root) -> Generic Root
forall x. Rep Root x -> Root
forall x. Root -> Rep Root x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Root -> Rep Root x
from :: forall x. Root -> Rep Root x
$cto :: forall x. Rep Root x -> Root
to :: forall x. Rep Root x -> Root
Generic)
instance ToJSON Root where
toJSON :: Root -> Value
toJSON Root {ProtocolVersion
$sel:rootUri:Root :: Root -> ProtocolVersion
$sel:rootName:Root :: Root -> ProtocolVersion
rootUri :: ProtocolVersion
rootName :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
rootUri,
Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
rootName
]
instance FromJSON Root where
parseJSON :: Value -> Parser Root
parseJSON = String -> (Object -> Parser Root) -> Value -> Parser Root
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Root" ((Object -> Parser Root) -> Value -> Parser Root)
-> (Object -> Parser Root) -> Value -> Parser Root
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
return $ ProtocolVersion -> ProtocolVersion -> Root
Root ProtocolVersion
uri ProtocolVersion
name
data ServerInitializeOptions = ServerInitializeOptions
{
ServerInitializeOptions -> ProtocolVersion
serverInitProtocolVersion :: ProtocolVersion,
ServerInitializeOptions -> Implementation
serverInitInfo :: Implementation,
ServerInitializeOptions -> ServerCapabilities
serverInitCapabilities :: ServerCapabilities,
ServerInitializeOptions -> ProtocolVersion
serverInitInstructions :: Text
}
deriving (Int -> ServerInitializeOptions -> ShowS
[ServerInitializeOptions] -> ShowS
ServerInitializeOptions -> String
(Int -> ServerInitializeOptions -> ShowS)
-> (ServerInitializeOptions -> String)
-> ([ServerInitializeOptions] -> ShowS)
-> Show ServerInitializeOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ServerInitializeOptions -> ShowS
showsPrec :: Int -> ServerInitializeOptions -> ShowS
$cshow :: ServerInitializeOptions -> String
show :: ServerInitializeOptions -> String
$cshowList :: [ServerInitializeOptions] -> ShowS
showList :: [ServerInitializeOptions] -> ShowS
Show, ServerInitializeOptions -> ServerInitializeOptions -> Bool
(ServerInitializeOptions -> ServerInitializeOptions -> Bool)
-> (ServerInitializeOptions -> ServerInitializeOptions -> Bool)
-> Eq ServerInitializeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ServerInitializeOptions -> ServerInitializeOptions -> Bool
== :: ServerInitializeOptions -> ServerInitializeOptions -> Bool
$c/= :: ServerInitializeOptions -> ServerInitializeOptions -> Bool
/= :: ServerInitializeOptions -> ServerInitializeOptions -> Bool
Eq, (forall x.
ServerInitializeOptions -> Rep ServerInitializeOptions x)
-> (forall x.
Rep ServerInitializeOptions x -> ServerInitializeOptions)
-> Generic ServerInitializeOptions
forall x. Rep ServerInitializeOptions x -> ServerInitializeOptions
forall x. ServerInitializeOptions -> Rep ServerInitializeOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ServerInitializeOptions -> Rep ServerInitializeOptions x
from :: forall x. ServerInitializeOptions -> Rep ServerInitializeOptions x
$cto :: forall x. Rep ServerInitializeOptions x -> ServerInitializeOptions
to :: forall x. Rep ServerInitializeOptions x -> ServerInitializeOptions
Generic)
instance ToJSON ServerInitializeOptions where
toJSON :: ServerInitializeOptions -> Value
toJSON ServerInitializeOptions {ProtocolVersion
ServerCapabilities
Implementation
$sel:serverInitProtocolVersion:ServerInitializeOptions :: ServerInitializeOptions -> ProtocolVersion
$sel:serverInitInfo:ServerInitializeOptions :: ServerInitializeOptions -> Implementation
$sel:serverInitCapabilities:ServerInitializeOptions :: ServerInitializeOptions -> ServerCapabilities
$sel:serverInitInstructions:ServerInitializeOptions :: ServerInitializeOptions -> ProtocolVersion
serverInitProtocolVersion :: ProtocolVersion
serverInitInfo :: Implementation
serverInitCapabilities :: ServerCapabilities
serverInitInstructions :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"protocolVersion" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
serverInitProtocolVersion,
Key
"serverInfo" Key -> Implementation -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Implementation
serverInitInfo,
Key
"capabilities" Key -> ServerCapabilities -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ServerCapabilities
serverInitCapabilities,
Key
"instructions" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
serverInitInstructions
]
instance FromJSON ServerInitializeOptions where
parseJSON :: Value -> Parser ServerInitializeOptions
parseJSON = String
-> (Object -> Parser ServerInitializeOptions)
-> Value
-> Parser ServerInitializeOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ServerInitializeOptions" ((Object -> Parser ServerInitializeOptions)
-> Value -> Parser ServerInitializeOptions)
-> (Object -> Parser ServerInitializeOptions)
-> Value
-> Parser ServerInitializeOptions
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
version <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"protocolVersion"
Implementation
impl <- Object
o Object -> Key -> Parser Implementation
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"serverInfo"
ServerCapabilities
capabilities <- Object
o Object -> Key -> Parser ServerCapabilities
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"capabilities"
ProtocolVersion
instructions <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"instructions"
return $ ProtocolVersion
-> Implementation
-> ServerCapabilities
-> ProtocolVersion
-> ServerInitializeOptions
ServerInitializeOptions ProtocolVersion
version Implementation
impl ServerCapabilities
capabilities ProtocolVersion
instructions
data ClientInitializeOptions = ClientInitializeOptions
{
ClientInitializeOptions -> ProtocolVersion
clientInitProtocolVersion :: ProtocolVersion,
ClientInitializeOptions -> Implementation
clientInitInfo :: Implementation,
ClientInitializeOptions -> ClientCapabilities
clientInitCapabilities :: ClientCapabilities
}
deriving (Int -> ClientInitializeOptions -> ShowS
[ClientInitializeOptions] -> ShowS
ClientInitializeOptions -> String
(Int -> ClientInitializeOptions -> ShowS)
-> (ClientInitializeOptions -> String)
-> ([ClientInitializeOptions] -> ShowS)
-> Show ClientInitializeOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ClientInitializeOptions -> ShowS
showsPrec :: Int -> ClientInitializeOptions -> ShowS
$cshow :: ClientInitializeOptions -> String
show :: ClientInitializeOptions -> String
$cshowList :: [ClientInitializeOptions] -> ShowS
showList :: [ClientInitializeOptions] -> ShowS
Show, ClientInitializeOptions -> ClientInitializeOptions -> Bool
(ClientInitializeOptions -> ClientInitializeOptions -> Bool)
-> (ClientInitializeOptions -> ClientInitializeOptions -> Bool)
-> Eq ClientInitializeOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ClientInitializeOptions -> ClientInitializeOptions -> Bool
== :: ClientInitializeOptions -> ClientInitializeOptions -> Bool
$c/= :: ClientInitializeOptions -> ClientInitializeOptions -> Bool
/= :: ClientInitializeOptions -> ClientInitializeOptions -> Bool
Eq, (forall x.
ClientInitializeOptions -> Rep ClientInitializeOptions x)
-> (forall x.
Rep ClientInitializeOptions x -> ClientInitializeOptions)
-> Generic ClientInitializeOptions
forall x. Rep ClientInitializeOptions x -> ClientInitializeOptions
forall x. ClientInitializeOptions -> Rep ClientInitializeOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ClientInitializeOptions -> Rep ClientInitializeOptions x
from :: forall x. ClientInitializeOptions -> Rep ClientInitializeOptions x
$cto :: forall x. Rep ClientInitializeOptions x -> ClientInitializeOptions
to :: forall x. Rep ClientInitializeOptions x -> ClientInitializeOptions
Generic)
instance ToJSON ClientInitializeOptions where
toJSON :: ClientInitializeOptions -> Value
toJSON ClientInitializeOptions {ProtocolVersion
ClientCapabilities
Implementation
$sel:clientInitProtocolVersion:ClientInitializeOptions :: ClientInitializeOptions -> ProtocolVersion
$sel:clientInitInfo:ClientInitializeOptions :: ClientInitializeOptions -> Implementation
$sel:clientInitCapabilities:ClientInitializeOptions :: ClientInitializeOptions -> ClientCapabilities
clientInitProtocolVersion :: ProtocolVersion
clientInitInfo :: Implementation
clientInitCapabilities :: ClientCapabilities
..} =
[Pair] -> Value
object
[ Key
"protocolVersion" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
clientInitProtocolVersion,
Key
"clientInfo" Key -> Implementation -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Implementation
clientInitInfo,
Key
"capabilities" Key -> ClientCapabilities -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ClientCapabilities
clientInitCapabilities
]
instance FromJSON ClientInitializeOptions where
parseJSON :: Value -> Parser ClientInitializeOptions
parseJSON = String
-> (Object -> Parser ClientInitializeOptions)
-> Value
-> Parser ClientInitializeOptions
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ClientInitializeOptions" ((Object -> Parser ClientInitializeOptions)
-> Value -> Parser ClientInitializeOptions)
-> (Object -> Parser ClientInitializeOptions)
-> Value
-> Parser ClientInitializeOptions
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
version <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"protocolVersion"
Implementation
impl <- Object
o Object -> Key -> Parser Implementation
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"clientInfo"
ClientCapabilities
capabilities <- Object
o Object -> Key -> Parser ClientCapabilities
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"capabilities"
return $ ProtocolVersion
-> Implementation -> ClientCapabilities -> ClientInitializeOptions
ClientInitializeOptions ProtocolVersion
version Implementation
impl ClientCapabilities
capabilities
type ServerInitializeResult = ClientInitializeOptions
type ClientInitializeResult = ServerInitializeOptions
data ListResourcesRequest = ListResourcesRequest
deriving (Int -> ListResourcesRequest -> ShowS
[ListResourcesRequest] -> ShowS
ListResourcesRequest -> String
(Int -> ListResourcesRequest -> ShowS)
-> (ListResourcesRequest -> String)
-> ([ListResourcesRequest] -> ShowS)
-> Show ListResourcesRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListResourcesRequest -> ShowS
showsPrec :: Int -> ListResourcesRequest -> ShowS
$cshow :: ListResourcesRequest -> String
show :: ListResourcesRequest -> String
$cshowList :: [ListResourcesRequest] -> ShowS
showList :: [ListResourcesRequest] -> ShowS
Show, ListResourcesRequest -> ListResourcesRequest -> Bool
(ListResourcesRequest -> ListResourcesRequest -> Bool)
-> (ListResourcesRequest -> ListResourcesRequest -> Bool)
-> Eq ListResourcesRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListResourcesRequest -> ListResourcesRequest -> Bool
== :: ListResourcesRequest -> ListResourcesRequest -> Bool
$c/= :: ListResourcesRequest -> ListResourcesRequest -> Bool
/= :: ListResourcesRequest -> ListResourcesRequest -> Bool
Eq, (forall x. ListResourcesRequest -> Rep ListResourcesRequest x)
-> (forall x. Rep ListResourcesRequest x -> ListResourcesRequest)
-> Generic ListResourcesRequest
forall x. Rep ListResourcesRequest x -> ListResourcesRequest
forall x. ListResourcesRequest -> Rep ListResourcesRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListResourcesRequest -> Rep ListResourcesRequest x
from :: forall x. ListResourcesRequest -> Rep ListResourcesRequest x
$cto :: forall x. Rep ListResourcesRequest x -> ListResourcesRequest
to :: forall x. Rep ListResourcesRequest x -> ListResourcesRequest
Generic)
instance ToJSON ListResourcesRequest where
toJSON :: ListResourcesRequest -> Value
toJSON ListResourcesRequest
_ = [Pair] -> Value
object []
instance FromJSON ListResourcesRequest where
parseJSON :: Value -> Parser ListResourcesRequest
parseJSON = String
-> (Object -> Parser ListResourcesRequest)
-> Value
-> Parser ListResourcesRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListResourcesRequest" ((Object -> Parser ListResourcesRequest)
-> Value -> Parser ListResourcesRequest)
-> (Object -> Parser ListResourcesRequest)
-> Value
-> Parser ListResourcesRequest
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ListResourcesRequest -> Parser ListResourcesRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ListResourcesRequest
ListResourcesRequest
data ListResourcesResult = ListResourcesResult
{
ListResourcesResult -> [Resource]
listResourcesResult :: [Resource]
}
deriving (Int -> ListResourcesResult -> ShowS
[ListResourcesResult] -> ShowS
ListResourcesResult -> String
(Int -> ListResourcesResult -> ShowS)
-> (ListResourcesResult -> String)
-> ([ListResourcesResult] -> ShowS)
-> Show ListResourcesResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListResourcesResult -> ShowS
showsPrec :: Int -> ListResourcesResult -> ShowS
$cshow :: ListResourcesResult -> String
show :: ListResourcesResult -> String
$cshowList :: [ListResourcesResult] -> ShowS
showList :: [ListResourcesResult] -> ShowS
Show, ListResourcesResult -> ListResourcesResult -> Bool
(ListResourcesResult -> ListResourcesResult -> Bool)
-> (ListResourcesResult -> ListResourcesResult -> Bool)
-> Eq ListResourcesResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListResourcesResult -> ListResourcesResult -> Bool
== :: ListResourcesResult -> ListResourcesResult -> Bool
$c/= :: ListResourcesResult -> ListResourcesResult -> Bool
/= :: ListResourcesResult -> ListResourcesResult -> Bool
Eq, (forall x. ListResourcesResult -> Rep ListResourcesResult x)
-> (forall x. Rep ListResourcesResult x -> ListResourcesResult)
-> Generic ListResourcesResult
forall x. Rep ListResourcesResult x -> ListResourcesResult
forall x. ListResourcesResult -> Rep ListResourcesResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListResourcesResult -> Rep ListResourcesResult x
from :: forall x. ListResourcesResult -> Rep ListResourcesResult x
$cto :: forall x. Rep ListResourcesResult x -> ListResourcesResult
to :: forall x. Rep ListResourcesResult x -> ListResourcesResult
Generic)
instance ToJSON ListResourcesResult where
toJSON :: ListResourcesResult -> Value
toJSON ListResourcesResult {[Resource]
$sel:listResourcesResult:ListResourcesResult :: ListResourcesResult -> [Resource]
listResourcesResult :: [Resource]
..} =
[Pair] -> Value
object
[ Key
"resources" Key -> [Resource] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Resource]
listResourcesResult
]
instance FromJSON ListResourcesResult where
parseJSON :: Value -> Parser ListResourcesResult
parseJSON = String
-> (Object -> Parser ListResourcesResult)
-> Value
-> Parser ListResourcesResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListResourcesResult" ((Object -> Parser ListResourcesResult)
-> Value -> Parser ListResourcesResult)
-> (Object -> Parser ListResourcesResult)
-> Value
-> Parser ListResourcesResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[Resource]
resources <- Object
o Object -> Key -> Parser [Resource]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"resources"
return $ [Resource] -> ListResourcesResult
ListResourcesResult [Resource]
resources
data ReadResourceRequest = ReadResourceRequest
{
ReadResourceRequest -> ProtocolVersion
resourceReadUri :: Text
}
deriving (Int -> ReadResourceRequest -> ShowS
[ReadResourceRequest] -> ShowS
ReadResourceRequest -> String
(Int -> ReadResourceRequest -> ShowS)
-> (ReadResourceRequest -> String)
-> ([ReadResourceRequest] -> ShowS)
-> Show ReadResourceRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReadResourceRequest -> ShowS
showsPrec :: Int -> ReadResourceRequest -> ShowS
$cshow :: ReadResourceRequest -> String
show :: ReadResourceRequest -> String
$cshowList :: [ReadResourceRequest] -> ShowS
showList :: [ReadResourceRequest] -> ShowS
Show, ReadResourceRequest -> ReadResourceRequest -> Bool
(ReadResourceRequest -> ReadResourceRequest -> Bool)
-> (ReadResourceRequest -> ReadResourceRequest -> Bool)
-> Eq ReadResourceRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReadResourceRequest -> ReadResourceRequest -> Bool
== :: ReadResourceRequest -> ReadResourceRequest -> Bool
$c/= :: ReadResourceRequest -> ReadResourceRequest -> Bool
/= :: ReadResourceRequest -> ReadResourceRequest -> Bool
Eq, (forall x. ReadResourceRequest -> Rep ReadResourceRequest x)
-> (forall x. Rep ReadResourceRequest x -> ReadResourceRequest)
-> Generic ReadResourceRequest
forall x. Rep ReadResourceRequest x -> ReadResourceRequest
forall x. ReadResourceRequest -> Rep ReadResourceRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReadResourceRequest -> Rep ReadResourceRequest x
from :: forall x. ReadResourceRequest -> Rep ReadResourceRequest x
$cto :: forall x. Rep ReadResourceRequest x -> ReadResourceRequest
to :: forall x. Rep ReadResourceRequest x -> ReadResourceRequest
Generic)
instance ToJSON ReadResourceRequest where
toJSON :: ReadResourceRequest -> Value
toJSON ReadResourceRequest {ProtocolVersion
$sel:resourceReadUri:ReadResourceRequest :: ReadResourceRequest -> ProtocolVersion
resourceReadUri :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
resourceReadUri
]
instance FromJSON ReadResourceRequest where
parseJSON :: Value -> Parser ReadResourceRequest
parseJSON = String
-> (Object -> Parser ReadResourceRequest)
-> Value
-> Parser ReadResourceRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ReadResourceRequest" ((Object -> Parser ReadResourceRequest)
-> Value -> Parser ReadResourceRequest)
-> (Object -> Parser ReadResourceRequest)
-> Value
-> Parser ReadResourceRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
return $ ProtocolVersion -> ReadResourceRequest
ReadResourceRequest ProtocolVersion
uri
data ReadResourceResult = ReadResourceResult
{
ReadResourceResult -> [ResourceContent]
readResourceContents :: [ResourceContent]
}
deriving (Int -> ReadResourceResult -> ShowS
[ReadResourceResult] -> ShowS
ReadResourceResult -> String
(Int -> ReadResourceResult -> ShowS)
-> (ReadResourceResult -> String)
-> ([ReadResourceResult] -> ShowS)
-> Show ReadResourceResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ReadResourceResult -> ShowS
showsPrec :: Int -> ReadResourceResult -> ShowS
$cshow :: ReadResourceResult -> String
show :: ReadResourceResult -> String
$cshowList :: [ReadResourceResult] -> ShowS
showList :: [ReadResourceResult] -> ShowS
Show, ReadResourceResult -> ReadResourceResult -> Bool
(ReadResourceResult -> ReadResourceResult -> Bool)
-> (ReadResourceResult -> ReadResourceResult -> Bool)
-> Eq ReadResourceResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ReadResourceResult -> ReadResourceResult -> Bool
== :: ReadResourceResult -> ReadResourceResult -> Bool
$c/= :: ReadResourceResult -> ReadResourceResult -> Bool
/= :: ReadResourceResult -> ReadResourceResult -> Bool
Eq, (forall x. ReadResourceResult -> Rep ReadResourceResult x)
-> (forall x. Rep ReadResourceResult x -> ReadResourceResult)
-> Generic ReadResourceResult
forall x. Rep ReadResourceResult x -> ReadResourceResult
forall x. ReadResourceResult -> Rep ReadResourceResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ReadResourceResult -> Rep ReadResourceResult x
from :: forall x. ReadResourceResult -> Rep ReadResourceResult x
$cto :: forall x. Rep ReadResourceResult x -> ReadResourceResult
to :: forall x. Rep ReadResourceResult x -> ReadResourceResult
Generic)
instance ToJSON ReadResourceResult where
toJSON :: ReadResourceResult -> Value
toJSON ReadResourceResult {[ResourceContent]
$sel:readResourceContents:ReadResourceResult :: ReadResourceResult -> [ResourceContent]
readResourceContents :: [ResourceContent]
..} =
[Pair] -> Value
object
[ Key
"contents" Key -> [ResourceContent] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [ResourceContent]
readResourceContents
]
instance FromJSON ReadResourceResult where
parseJSON :: Value -> Parser ReadResourceResult
parseJSON = String
-> (Object -> Parser ReadResourceResult)
-> Value
-> Parser ReadResourceResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ReadResourceResult" ((Object -> Parser ReadResourceResult)
-> Value -> Parser ReadResourceResult)
-> (Object -> Parser ReadResourceResult)
-> Value
-> Parser ReadResourceResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[ResourceContent]
contents <- Object
o Object -> Key -> Parser [ResourceContent]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"contents"
return $ [ResourceContent] -> ReadResourceResult
ReadResourceResult [ResourceContent]
contents
data SubscribeResourceRequest = SubscribeResourceRequest
{
SubscribeResourceRequest -> ProtocolVersion
subscribeResourceUri :: Text
}
deriving (Int -> SubscribeResourceRequest -> ShowS
[SubscribeResourceRequest] -> ShowS
SubscribeResourceRequest -> String
(Int -> SubscribeResourceRequest -> ShowS)
-> (SubscribeResourceRequest -> String)
-> ([SubscribeResourceRequest] -> ShowS)
-> Show SubscribeResourceRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscribeResourceRequest -> ShowS
showsPrec :: Int -> SubscribeResourceRequest -> ShowS
$cshow :: SubscribeResourceRequest -> String
show :: SubscribeResourceRequest -> String
$cshowList :: [SubscribeResourceRequest] -> ShowS
showList :: [SubscribeResourceRequest] -> ShowS
Show, SubscribeResourceRequest -> SubscribeResourceRequest -> Bool
(SubscribeResourceRequest -> SubscribeResourceRequest -> Bool)
-> (SubscribeResourceRequest -> SubscribeResourceRequest -> Bool)
-> Eq SubscribeResourceRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscribeResourceRequest -> SubscribeResourceRequest -> Bool
== :: SubscribeResourceRequest -> SubscribeResourceRequest -> Bool
$c/= :: SubscribeResourceRequest -> SubscribeResourceRequest -> Bool
/= :: SubscribeResourceRequest -> SubscribeResourceRequest -> Bool
Eq, (forall x.
SubscribeResourceRequest -> Rep SubscribeResourceRequest x)
-> (forall x.
Rep SubscribeResourceRequest x -> SubscribeResourceRequest)
-> Generic SubscribeResourceRequest
forall x.
Rep SubscribeResourceRequest x -> SubscribeResourceRequest
forall x.
SubscribeResourceRequest -> Rep SubscribeResourceRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
SubscribeResourceRequest -> Rep SubscribeResourceRequest x
from :: forall x.
SubscribeResourceRequest -> Rep SubscribeResourceRequest x
$cto :: forall x.
Rep SubscribeResourceRequest x -> SubscribeResourceRequest
to :: forall x.
Rep SubscribeResourceRequest x -> SubscribeResourceRequest
Generic)
instance ToJSON SubscribeResourceRequest where
toJSON :: SubscribeResourceRequest -> Value
toJSON SubscribeResourceRequest {ProtocolVersion
$sel:subscribeResourceUri:SubscribeResourceRequest :: SubscribeResourceRequest -> ProtocolVersion
subscribeResourceUri :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
subscribeResourceUri
]
instance FromJSON SubscribeResourceRequest where
parseJSON :: Value -> Parser SubscribeResourceRequest
parseJSON = String
-> (Object -> Parser SubscribeResourceRequest)
-> Value
-> Parser SubscribeResourceRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SubscribeResourceRequest" ((Object -> Parser SubscribeResourceRequest)
-> Value -> Parser SubscribeResourceRequest)
-> (Object -> Parser SubscribeResourceRequest)
-> Value
-> Parser SubscribeResourceRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
return $ ProtocolVersion -> SubscribeResourceRequest
SubscribeResourceRequest ProtocolVersion
uri
data SubscribeResourceResult = SubscribeResourceResult
deriving (Int -> SubscribeResourceResult -> ShowS
[SubscribeResourceResult] -> ShowS
SubscribeResourceResult -> String
(Int -> SubscribeResourceResult -> ShowS)
-> (SubscribeResourceResult -> String)
-> ([SubscribeResourceResult] -> ShowS)
-> Show SubscribeResourceResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SubscribeResourceResult -> ShowS
showsPrec :: Int -> SubscribeResourceResult -> ShowS
$cshow :: SubscribeResourceResult -> String
show :: SubscribeResourceResult -> String
$cshowList :: [SubscribeResourceResult] -> ShowS
showList :: [SubscribeResourceResult] -> ShowS
Show, SubscribeResourceResult -> SubscribeResourceResult -> Bool
(SubscribeResourceResult -> SubscribeResourceResult -> Bool)
-> (SubscribeResourceResult -> SubscribeResourceResult -> Bool)
-> Eq SubscribeResourceResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SubscribeResourceResult -> SubscribeResourceResult -> Bool
== :: SubscribeResourceResult -> SubscribeResourceResult -> Bool
$c/= :: SubscribeResourceResult -> SubscribeResourceResult -> Bool
/= :: SubscribeResourceResult -> SubscribeResourceResult -> Bool
Eq, (forall x.
SubscribeResourceResult -> Rep SubscribeResourceResult x)
-> (forall x.
Rep SubscribeResourceResult x -> SubscribeResourceResult)
-> Generic SubscribeResourceResult
forall x. Rep SubscribeResourceResult x -> SubscribeResourceResult
forall x. SubscribeResourceResult -> Rep SubscribeResourceResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SubscribeResourceResult -> Rep SubscribeResourceResult x
from :: forall x. SubscribeResourceResult -> Rep SubscribeResourceResult x
$cto :: forall x. Rep SubscribeResourceResult x -> SubscribeResourceResult
to :: forall x. Rep SubscribeResourceResult x -> SubscribeResourceResult
Generic)
instance ToJSON SubscribeResourceResult where
toJSON :: SubscribeResourceResult -> Value
toJSON SubscribeResourceResult
_ = [Pair] -> Value
object []
instance FromJSON SubscribeResourceResult where
parseJSON :: Value -> Parser SubscribeResourceResult
parseJSON = String
-> (Object -> Parser SubscribeResourceResult)
-> Value
-> Parser SubscribeResourceResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"SubscribeResourceResult" ((Object -> Parser SubscribeResourceResult)
-> Value -> Parser SubscribeResourceResult)
-> (Object -> Parser SubscribeResourceResult)
-> Value
-> Parser SubscribeResourceResult
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
SubscribeResourceResult -> Parser SubscribeResourceResult
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return SubscribeResourceResult
SubscribeResourceResult
data UnsubscribeResourceRequest = UnsubscribeResourceRequest
{
UnsubscribeResourceRequest -> ProtocolVersion
unsubscribeResourceUri :: Text
}
deriving (Int -> UnsubscribeResourceRequest -> ShowS
[UnsubscribeResourceRequest] -> ShowS
UnsubscribeResourceRequest -> String
(Int -> UnsubscribeResourceRequest -> ShowS)
-> (UnsubscribeResourceRequest -> String)
-> ([UnsubscribeResourceRequest] -> ShowS)
-> Show UnsubscribeResourceRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnsubscribeResourceRequest -> ShowS
showsPrec :: Int -> UnsubscribeResourceRequest -> ShowS
$cshow :: UnsubscribeResourceRequest -> String
show :: UnsubscribeResourceRequest -> String
$cshowList :: [UnsubscribeResourceRequest] -> ShowS
showList :: [UnsubscribeResourceRequest] -> ShowS
Show, UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool
(UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool)
-> (UnsubscribeResourceRequest
-> UnsubscribeResourceRequest -> Bool)
-> Eq UnsubscribeResourceRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool
== :: UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool
$c/= :: UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool
/= :: UnsubscribeResourceRequest -> UnsubscribeResourceRequest -> Bool
Eq, (forall x.
UnsubscribeResourceRequest -> Rep UnsubscribeResourceRequest x)
-> (forall x.
Rep UnsubscribeResourceRequest x -> UnsubscribeResourceRequest)
-> Generic UnsubscribeResourceRequest
forall x.
Rep UnsubscribeResourceRequest x -> UnsubscribeResourceRequest
forall x.
UnsubscribeResourceRequest -> Rep UnsubscribeResourceRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
UnsubscribeResourceRequest -> Rep UnsubscribeResourceRequest x
from :: forall x.
UnsubscribeResourceRequest -> Rep UnsubscribeResourceRequest x
$cto :: forall x.
Rep UnsubscribeResourceRequest x -> UnsubscribeResourceRequest
to :: forall x.
Rep UnsubscribeResourceRequest x -> UnsubscribeResourceRequest
Generic)
instance ToJSON UnsubscribeResourceRequest where
toJSON :: UnsubscribeResourceRequest -> Value
toJSON UnsubscribeResourceRequest {ProtocolVersion
$sel:unsubscribeResourceUri:UnsubscribeResourceRequest :: UnsubscribeResourceRequest -> ProtocolVersion
unsubscribeResourceUri :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
unsubscribeResourceUri
]
instance FromJSON UnsubscribeResourceRequest where
parseJSON :: Value -> Parser UnsubscribeResourceRequest
parseJSON = String
-> (Object -> Parser UnsubscribeResourceRequest)
-> Value
-> Parser UnsubscribeResourceRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UnsubscribeResourceRequest" ((Object -> Parser UnsubscribeResourceRequest)
-> Value -> Parser UnsubscribeResourceRequest)
-> (Object -> Parser UnsubscribeResourceRequest)
-> Value
-> Parser UnsubscribeResourceRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
return $ ProtocolVersion -> UnsubscribeResourceRequest
UnsubscribeResourceRequest ProtocolVersion
uri
data UnsubscribeResourceResult = UnsubscribeResourceResult
deriving (Int -> UnsubscribeResourceResult -> ShowS
[UnsubscribeResourceResult] -> ShowS
UnsubscribeResourceResult -> String
(Int -> UnsubscribeResourceResult -> ShowS)
-> (UnsubscribeResourceResult -> String)
-> ([UnsubscribeResourceResult] -> ShowS)
-> Show UnsubscribeResourceResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UnsubscribeResourceResult -> ShowS
showsPrec :: Int -> UnsubscribeResourceResult -> ShowS
$cshow :: UnsubscribeResourceResult -> String
show :: UnsubscribeResourceResult -> String
$cshowList :: [UnsubscribeResourceResult] -> ShowS
showList :: [UnsubscribeResourceResult] -> ShowS
Show, UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool
(UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool)
-> (UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool)
-> Eq UnsubscribeResourceResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool
== :: UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool
$c/= :: UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool
/= :: UnsubscribeResourceResult -> UnsubscribeResourceResult -> Bool
Eq, (forall x.
UnsubscribeResourceResult -> Rep UnsubscribeResourceResult x)
-> (forall x.
Rep UnsubscribeResourceResult x -> UnsubscribeResourceResult)
-> Generic UnsubscribeResourceResult
forall x.
Rep UnsubscribeResourceResult x -> UnsubscribeResourceResult
forall x.
UnsubscribeResourceResult -> Rep UnsubscribeResourceResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
UnsubscribeResourceResult -> Rep UnsubscribeResourceResult x
from :: forall x.
UnsubscribeResourceResult -> Rep UnsubscribeResourceResult x
$cto :: forall x.
Rep UnsubscribeResourceResult x -> UnsubscribeResourceResult
to :: forall x.
Rep UnsubscribeResourceResult x -> UnsubscribeResourceResult
Generic)
instance ToJSON UnsubscribeResourceResult where
toJSON :: UnsubscribeResourceResult -> Value
toJSON UnsubscribeResourceResult
_ = [Pair] -> Value
object []
instance FromJSON UnsubscribeResourceResult where
parseJSON :: Value -> Parser UnsubscribeResourceResult
parseJSON = String
-> (Object -> Parser UnsubscribeResourceResult)
-> Value
-> Parser UnsubscribeResourceResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UnsubscribeResourceResult" ((Object -> Parser UnsubscribeResourceResult)
-> Value -> Parser UnsubscribeResourceResult)
-> (Object -> Parser UnsubscribeResourceResult)
-> Value
-> Parser UnsubscribeResourceResult
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
UnsubscribeResourceResult -> Parser UnsubscribeResourceResult
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return UnsubscribeResourceResult
UnsubscribeResourceResult
data ListToolsRequest = ListToolsRequest
deriving (Int -> ListToolsRequest -> ShowS
[ListToolsRequest] -> ShowS
ListToolsRequest -> String
(Int -> ListToolsRequest -> ShowS)
-> (ListToolsRequest -> String)
-> ([ListToolsRequest] -> ShowS)
-> Show ListToolsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListToolsRequest -> ShowS
showsPrec :: Int -> ListToolsRequest -> ShowS
$cshow :: ListToolsRequest -> String
show :: ListToolsRequest -> String
$cshowList :: [ListToolsRequest] -> ShowS
showList :: [ListToolsRequest] -> ShowS
Show, ListToolsRequest -> ListToolsRequest -> Bool
(ListToolsRequest -> ListToolsRequest -> Bool)
-> (ListToolsRequest -> ListToolsRequest -> Bool)
-> Eq ListToolsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListToolsRequest -> ListToolsRequest -> Bool
== :: ListToolsRequest -> ListToolsRequest -> Bool
$c/= :: ListToolsRequest -> ListToolsRequest -> Bool
/= :: ListToolsRequest -> ListToolsRequest -> Bool
Eq, (forall x. ListToolsRequest -> Rep ListToolsRequest x)
-> (forall x. Rep ListToolsRequest x -> ListToolsRequest)
-> Generic ListToolsRequest
forall x. Rep ListToolsRequest x -> ListToolsRequest
forall x. ListToolsRequest -> Rep ListToolsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListToolsRequest -> Rep ListToolsRequest x
from :: forall x. ListToolsRequest -> Rep ListToolsRequest x
$cto :: forall x. Rep ListToolsRequest x -> ListToolsRequest
to :: forall x. Rep ListToolsRequest x -> ListToolsRequest
Generic)
instance ToJSON ListToolsRequest where
toJSON :: ListToolsRequest -> Value
toJSON ListToolsRequest
_ = [Pair] -> Value
object []
instance FromJSON ListToolsRequest where
parseJSON :: Value -> Parser ListToolsRequest
parseJSON = String
-> (Object -> Parser ListToolsRequest)
-> Value
-> Parser ListToolsRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListToolsRequest" ((Object -> Parser ListToolsRequest)
-> Value -> Parser ListToolsRequest)
-> (Object -> Parser ListToolsRequest)
-> Value
-> Parser ListToolsRequest
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ListToolsRequest -> Parser ListToolsRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ListToolsRequest
ListToolsRequest
data ListToolsResult = ListToolsResult
{
ListToolsResult -> [Tool]
listToolsResult :: [Tool]
}
deriving (Int -> ListToolsResult -> ShowS
[ListToolsResult] -> ShowS
ListToolsResult -> String
(Int -> ListToolsResult -> ShowS)
-> (ListToolsResult -> String)
-> ([ListToolsResult] -> ShowS)
-> Show ListToolsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListToolsResult -> ShowS
showsPrec :: Int -> ListToolsResult -> ShowS
$cshow :: ListToolsResult -> String
show :: ListToolsResult -> String
$cshowList :: [ListToolsResult] -> ShowS
showList :: [ListToolsResult] -> ShowS
Show, ListToolsResult -> ListToolsResult -> Bool
(ListToolsResult -> ListToolsResult -> Bool)
-> (ListToolsResult -> ListToolsResult -> Bool)
-> Eq ListToolsResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListToolsResult -> ListToolsResult -> Bool
== :: ListToolsResult -> ListToolsResult -> Bool
$c/= :: ListToolsResult -> ListToolsResult -> Bool
/= :: ListToolsResult -> ListToolsResult -> Bool
Eq, (forall x. ListToolsResult -> Rep ListToolsResult x)
-> (forall x. Rep ListToolsResult x -> ListToolsResult)
-> Generic ListToolsResult
forall x. Rep ListToolsResult x -> ListToolsResult
forall x. ListToolsResult -> Rep ListToolsResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListToolsResult -> Rep ListToolsResult x
from :: forall x. ListToolsResult -> Rep ListToolsResult x
$cto :: forall x. Rep ListToolsResult x -> ListToolsResult
to :: forall x. Rep ListToolsResult x -> ListToolsResult
Generic)
instance ToJSON ListToolsResult where
toJSON :: ListToolsResult -> Value
toJSON ListToolsResult {[Tool]
$sel:listToolsResult:ListToolsResult :: ListToolsResult -> [Tool]
listToolsResult :: [Tool]
..} =
[Pair] -> Value
object
[ Key
"tools" Key -> [Tool] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Tool]
listToolsResult
]
instance FromJSON ListToolsResult where
parseJSON :: Value -> Parser ListToolsResult
parseJSON = String
-> (Object -> Parser ListToolsResult)
-> Value
-> Parser ListToolsResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListToolsResult" ((Object -> Parser ListToolsResult)
-> Value -> Parser ListToolsResult)
-> (Object -> Parser ListToolsResult)
-> Value
-> Parser ListToolsResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[Tool]
tools <- Object
o Object -> Key -> Parser [Tool]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"tools"
return $ [Tool] -> ListToolsResult
ListToolsResult [Tool]
tools
data CallToolRequest = CallToolRequest
{
CallToolRequest -> ProtocolVersion
callToolName :: Text,
CallToolRequest -> Value
callToolArguments :: Value
}
deriving (Int -> CallToolRequest -> ShowS
[CallToolRequest] -> ShowS
CallToolRequest -> String
(Int -> CallToolRequest -> ShowS)
-> (CallToolRequest -> String)
-> ([CallToolRequest] -> ShowS)
-> Show CallToolRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CallToolRequest -> ShowS
showsPrec :: Int -> CallToolRequest -> ShowS
$cshow :: CallToolRequest -> String
show :: CallToolRequest -> String
$cshowList :: [CallToolRequest] -> ShowS
showList :: [CallToolRequest] -> ShowS
Show, CallToolRequest -> CallToolRequest -> Bool
(CallToolRequest -> CallToolRequest -> Bool)
-> (CallToolRequest -> CallToolRequest -> Bool)
-> Eq CallToolRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CallToolRequest -> CallToolRequest -> Bool
== :: CallToolRequest -> CallToolRequest -> Bool
$c/= :: CallToolRequest -> CallToolRequest -> Bool
/= :: CallToolRequest -> CallToolRequest -> Bool
Eq, (forall x. CallToolRequest -> Rep CallToolRequest x)
-> (forall x. Rep CallToolRequest x -> CallToolRequest)
-> Generic CallToolRequest
forall x. Rep CallToolRequest x -> CallToolRequest
forall x. CallToolRequest -> Rep CallToolRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CallToolRequest -> Rep CallToolRequest x
from :: forall x. CallToolRequest -> Rep CallToolRequest x
$cto :: forall x. Rep CallToolRequest x -> CallToolRequest
to :: forall x. Rep CallToolRequest x -> CallToolRequest
Generic)
instance ToJSON CallToolRequest where
toJSON :: CallToolRequest -> Value
toJSON CallToolRequest {Value
ProtocolVersion
$sel:callToolName:CallToolRequest :: CallToolRequest -> ProtocolVersion
$sel:callToolArguments:CallToolRequest :: CallToolRequest -> Value
callToolName :: ProtocolVersion
callToolArguments :: Value
..} =
[Pair] -> Value
object
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
callToolName,
Key
"arguments" Key -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Value
callToolArguments
]
instance FromJSON CallToolRequest where
parseJSON :: Value -> Parser CallToolRequest
parseJSON = String
-> (Object -> Parser CallToolRequest)
-> Value
-> Parser CallToolRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CallToolRequest" ((Object -> Parser CallToolRequest)
-> Value -> Parser CallToolRequest)
-> (Object -> Parser CallToolRequest)
-> Value
-> Parser CallToolRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Value
arguments <- Object
o Object -> Key -> Parser Value
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"arguments"
return $ ProtocolVersion -> Value -> CallToolRequest
CallToolRequest ProtocolVersion
name Value
arguments
data CallToolResult = CallToolResult
{
CallToolResult -> [ToolContent]
callToolContent :: [ToolContent],
CallToolResult -> Bool
callToolIsError :: Bool
}
deriving (Int -> CallToolResult -> ShowS
[CallToolResult] -> ShowS
CallToolResult -> String
(Int -> CallToolResult -> ShowS)
-> (CallToolResult -> String)
-> ([CallToolResult] -> ShowS)
-> Show CallToolResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CallToolResult -> ShowS
showsPrec :: Int -> CallToolResult -> ShowS
$cshow :: CallToolResult -> String
show :: CallToolResult -> String
$cshowList :: [CallToolResult] -> ShowS
showList :: [CallToolResult] -> ShowS
Show, CallToolResult -> CallToolResult -> Bool
(CallToolResult -> CallToolResult -> Bool)
-> (CallToolResult -> CallToolResult -> Bool) -> Eq CallToolResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CallToolResult -> CallToolResult -> Bool
== :: CallToolResult -> CallToolResult -> Bool
$c/= :: CallToolResult -> CallToolResult -> Bool
/= :: CallToolResult -> CallToolResult -> Bool
Eq, (forall x. CallToolResult -> Rep CallToolResult x)
-> (forall x. Rep CallToolResult x -> CallToolResult)
-> Generic CallToolResult
forall x. Rep CallToolResult x -> CallToolResult
forall x. CallToolResult -> Rep CallToolResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CallToolResult -> Rep CallToolResult x
from :: forall x. CallToolResult -> Rep CallToolResult x
$cto :: forall x. Rep CallToolResult x -> CallToolResult
to :: forall x. Rep CallToolResult x -> CallToolResult
Generic)
instance ToJSON CallToolResult where
toJSON :: CallToolResult -> Value
toJSON CallToolResult {Bool
[ToolContent]
$sel:callToolContent:CallToolResult :: CallToolResult -> [ToolContent]
$sel:callToolIsError:CallToolResult :: CallToolResult -> Bool
callToolContent :: [ToolContent]
callToolIsError :: Bool
..} =
[Pair] -> Value
object
[ Key
"content" Key -> [ToolContent] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [ToolContent]
callToolContent,
Key
"isError" Key -> Bool -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Bool
callToolIsError
]
instance FromJSON CallToolResult where
parseJSON :: Value -> Parser CallToolResult
parseJSON = String
-> (Object -> Parser CallToolResult)
-> Value
-> Parser CallToolResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"CallToolResult" ((Object -> Parser CallToolResult)
-> Value -> Parser CallToolResult)
-> (Object -> Parser CallToolResult)
-> Value
-> Parser CallToolResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[ToolContent]
content <- Object
o Object -> Key -> Parser [ToolContent]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"content"
Bool
isError <- Object
o Object -> Key -> Parser Bool
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"isError"
return $ [ToolContent] -> Bool -> CallToolResult
CallToolResult [ToolContent]
content Bool
isError
data ListPromptsRequest = ListPromptsRequest
deriving (Int -> ListPromptsRequest -> ShowS
[ListPromptsRequest] -> ShowS
ListPromptsRequest -> String
(Int -> ListPromptsRequest -> ShowS)
-> (ListPromptsRequest -> String)
-> ([ListPromptsRequest] -> ShowS)
-> Show ListPromptsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListPromptsRequest -> ShowS
showsPrec :: Int -> ListPromptsRequest -> ShowS
$cshow :: ListPromptsRequest -> String
show :: ListPromptsRequest -> String
$cshowList :: [ListPromptsRequest] -> ShowS
showList :: [ListPromptsRequest] -> ShowS
Show, ListPromptsRequest -> ListPromptsRequest -> Bool
(ListPromptsRequest -> ListPromptsRequest -> Bool)
-> (ListPromptsRequest -> ListPromptsRequest -> Bool)
-> Eq ListPromptsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListPromptsRequest -> ListPromptsRequest -> Bool
== :: ListPromptsRequest -> ListPromptsRequest -> Bool
$c/= :: ListPromptsRequest -> ListPromptsRequest -> Bool
/= :: ListPromptsRequest -> ListPromptsRequest -> Bool
Eq, (forall x. ListPromptsRequest -> Rep ListPromptsRequest x)
-> (forall x. Rep ListPromptsRequest x -> ListPromptsRequest)
-> Generic ListPromptsRequest
forall x. Rep ListPromptsRequest x -> ListPromptsRequest
forall x. ListPromptsRequest -> Rep ListPromptsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListPromptsRequest -> Rep ListPromptsRequest x
from :: forall x. ListPromptsRequest -> Rep ListPromptsRequest x
$cto :: forall x. Rep ListPromptsRequest x -> ListPromptsRequest
to :: forall x. Rep ListPromptsRequest x -> ListPromptsRequest
Generic)
instance ToJSON ListPromptsRequest where
toJSON :: ListPromptsRequest -> Value
toJSON ListPromptsRequest
_ = [Pair] -> Value
object []
instance FromJSON ListPromptsRequest where
parseJSON :: Value -> Parser ListPromptsRequest
parseJSON = String
-> (Object -> Parser ListPromptsRequest)
-> Value
-> Parser ListPromptsRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListPromptsRequest" ((Object -> Parser ListPromptsRequest)
-> Value -> Parser ListPromptsRequest)
-> (Object -> Parser ListPromptsRequest)
-> Value
-> Parser ListPromptsRequest
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ListPromptsRequest -> Parser ListPromptsRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ListPromptsRequest
ListPromptsRequest
data ListPromptsResult = ListPromptsResult
{
ListPromptsResult -> [Prompt]
listPromptsResult :: [Prompt]
}
deriving (Int -> ListPromptsResult -> ShowS
[ListPromptsResult] -> ShowS
ListPromptsResult -> String
(Int -> ListPromptsResult -> ShowS)
-> (ListPromptsResult -> String)
-> ([ListPromptsResult] -> ShowS)
-> Show ListPromptsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListPromptsResult -> ShowS
showsPrec :: Int -> ListPromptsResult -> ShowS
$cshow :: ListPromptsResult -> String
show :: ListPromptsResult -> String
$cshowList :: [ListPromptsResult] -> ShowS
showList :: [ListPromptsResult] -> ShowS
Show, ListPromptsResult -> ListPromptsResult -> Bool
(ListPromptsResult -> ListPromptsResult -> Bool)
-> (ListPromptsResult -> ListPromptsResult -> Bool)
-> Eq ListPromptsResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListPromptsResult -> ListPromptsResult -> Bool
== :: ListPromptsResult -> ListPromptsResult -> Bool
$c/= :: ListPromptsResult -> ListPromptsResult -> Bool
/= :: ListPromptsResult -> ListPromptsResult -> Bool
Eq, (forall x. ListPromptsResult -> Rep ListPromptsResult x)
-> (forall x. Rep ListPromptsResult x -> ListPromptsResult)
-> Generic ListPromptsResult
forall x. Rep ListPromptsResult x -> ListPromptsResult
forall x. ListPromptsResult -> Rep ListPromptsResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListPromptsResult -> Rep ListPromptsResult x
from :: forall x. ListPromptsResult -> Rep ListPromptsResult x
$cto :: forall x. Rep ListPromptsResult x -> ListPromptsResult
to :: forall x. Rep ListPromptsResult x -> ListPromptsResult
Generic)
instance ToJSON ListPromptsResult where
toJSON :: ListPromptsResult -> Value
toJSON ListPromptsResult {[Prompt]
$sel:listPromptsResult:ListPromptsResult :: ListPromptsResult -> [Prompt]
listPromptsResult :: [Prompt]
..} =
[Pair] -> Value
object
[ Key
"prompts" Key -> [Prompt] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Prompt]
listPromptsResult
]
instance FromJSON ListPromptsResult where
parseJSON :: Value -> Parser ListPromptsResult
parseJSON = String
-> (Object -> Parser ListPromptsResult)
-> Value
-> Parser ListPromptsResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListPromptsResult" ((Object -> Parser ListPromptsResult)
-> Value -> Parser ListPromptsResult)
-> (Object -> Parser ListPromptsResult)
-> Value
-> Parser ListPromptsResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[Prompt]
prompts <- Object
o Object -> Key -> Parser [Prompt]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"prompts"
return $ [Prompt] -> ListPromptsResult
ListPromptsResult [Prompt]
prompts
data GetPromptRequest = GetPromptRequest
{
GetPromptRequest -> ProtocolVersion
getPromptName :: Text,
GetPromptRequest -> Map ProtocolVersion ProtocolVersion
getPromptArguments :: Map Text Text
}
deriving (Int -> GetPromptRequest -> ShowS
[GetPromptRequest] -> ShowS
GetPromptRequest -> String
(Int -> GetPromptRequest -> ShowS)
-> (GetPromptRequest -> String)
-> ([GetPromptRequest] -> ShowS)
-> Show GetPromptRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetPromptRequest -> ShowS
showsPrec :: Int -> GetPromptRequest -> ShowS
$cshow :: GetPromptRequest -> String
show :: GetPromptRequest -> String
$cshowList :: [GetPromptRequest] -> ShowS
showList :: [GetPromptRequest] -> ShowS
Show, GetPromptRequest -> GetPromptRequest -> Bool
(GetPromptRequest -> GetPromptRequest -> Bool)
-> (GetPromptRequest -> GetPromptRequest -> Bool)
-> Eq GetPromptRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetPromptRequest -> GetPromptRequest -> Bool
== :: GetPromptRequest -> GetPromptRequest -> Bool
$c/= :: GetPromptRequest -> GetPromptRequest -> Bool
/= :: GetPromptRequest -> GetPromptRequest -> Bool
Eq, (forall x. GetPromptRequest -> Rep GetPromptRequest x)
-> (forall x. Rep GetPromptRequest x -> GetPromptRequest)
-> Generic GetPromptRequest
forall x. Rep GetPromptRequest x -> GetPromptRequest
forall x. GetPromptRequest -> Rep GetPromptRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetPromptRequest -> Rep GetPromptRequest x
from :: forall x. GetPromptRequest -> Rep GetPromptRequest x
$cto :: forall x. Rep GetPromptRequest x -> GetPromptRequest
to :: forall x. Rep GetPromptRequest x -> GetPromptRequest
Generic)
instance ToJSON GetPromptRequest where
toJSON :: GetPromptRequest -> Value
toJSON GetPromptRequest {Map ProtocolVersion ProtocolVersion
ProtocolVersion
$sel:getPromptName:GetPromptRequest :: GetPromptRequest -> ProtocolVersion
$sel:getPromptArguments:GetPromptRequest :: GetPromptRequest -> Map ProtocolVersion ProtocolVersion
getPromptName :: ProtocolVersion
getPromptArguments :: Map ProtocolVersion ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"name" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
getPromptName,
Key
"arguments" Key -> Map ProtocolVersion ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= Map ProtocolVersion ProtocolVersion
getPromptArguments
]
instance FromJSON GetPromptRequest where
parseJSON :: Value -> Parser GetPromptRequest
parseJSON = String
-> (Object -> Parser GetPromptRequest)
-> Value
-> Parser GetPromptRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetPromptRequest" ((Object -> Parser GetPromptRequest)
-> Value -> Parser GetPromptRequest)
-> (Object -> Parser GetPromptRequest)
-> Value
-> Parser GetPromptRequest
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
name <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"name"
Map ProtocolVersion ProtocolVersion
arguments <- Object
o Object
-> Key -> Parser (Maybe (Map ProtocolVersion ProtocolVersion))
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"arguments" Parser (Maybe (Map ProtocolVersion ProtocolVersion))
-> Map ProtocolVersion ProtocolVersion
-> Parser (Map ProtocolVersion ProtocolVersion)
forall a. Parser (Maybe a) -> a -> Parser a
.!= Map ProtocolVersion ProtocolVersion
forall k a. Map k a
Map.empty
return $ ProtocolVersion
-> Map ProtocolVersion ProtocolVersion -> GetPromptRequest
GetPromptRequest ProtocolVersion
name Map ProtocolVersion ProtocolVersion
arguments
data GetPromptResult = GetPromptResult
{
GetPromptResult -> Maybe ProtocolVersion
getPromptDescription :: Maybe Text,
GetPromptResult -> [PromptMessage]
getPromptMessages :: [PromptMessage]
}
deriving (Int -> GetPromptResult -> ShowS
[GetPromptResult] -> ShowS
GetPromptResult -> String
(Int -> GetPromptResult -> ShowS)
-> (GetPromptResult -> String)
-> ([GetPromptResult] -> ShowS)
-> Show GetPromptResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> GetPromptResult -> ShowS
showsPrec :: Int -> GetPromptResult -> ShowS
$cshow :: GetPromptResult -> String
show :: GetPromptResult -> String
$cshowList :: [GetPromptResult] -> ShowS
showList :: [GetPromptResult] -> ShowS
Show, GetPromptResult -> GetPromptResult -> Bool
(GetPromptResult -> GetPromptResult -> Bool)
-> (GetPromptResult -> GetPromptResult -> Bool)
-> Eq GetPromptResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GetPromptResult -> GetPromptResult -> Bool
== :: GetPromptResult -> GetPromptResult -> Bool
$c/= :: GetPromptResult -> GetPromptResult -> Bool
/= :: GetPromptResult -> GetPromptResult -> Bool
Eq, (forall x. GetPromptResult -> Rep GetPromptResult x)
-> (forall x. Rep GetPromptResult x -> GetPromptResult)
-> Generic GetPromptResult
forall x. Rep GetPromptResult x -> GetPromptResult
forall x. GetPromptResult -> Rep GetPromptResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. GetPromptResult -> Rep GetPromptResult x
from :: forall x. GetPromptResult -> Rep GetPromptResult x
$cto :: forall x. Rep GetPromptResult x -> GetPromptResult
to :: forall x. Rep GetPromptResult x -> GetPromptResult
Generic)
instance ToJSON GetPromptResult where
toJSON :: GetPromptResult -> Value
toJSON GetPromptResult {[PromptMessage]
Maybe ProtocolVersion
$sel:getPromptDescription:GetPromptResult :: GetPromptResult -> Maybe ProtocolVersion
$sel:getPromptMessages:GetPromptResult :: GetPromptResult -> [PromptMessage]
getPromptDescription :: Maybe ProtocolVersion
getPromptMessages :: [PromptMessage]
..} =
[Pair] -> Value
object ([Pair] -> Value) -> [Pair] -> Value
forall a b. (a -> b) -> a -> b
$
[ Key
"messages" Key -> [PromptMessage] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [PromptMessage]
getPromptMessages
]
[Pair] -> [Pair] -> [Pair]
forall a. [a] -> [a] -> [a]
++ [Key
"description" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
d | ProtocolVersion
d <- Maybe ProtocolVersion -> [ProtocolVersion]
forall a. Maybe a -> [a]
maybeToList Maybe ProtocolVersion
getPromptDescription]
instance FromJSON GetPromptResult where
parseJSON :: Value -> Parser GetPromptResult
parseJSON = String
-> (Object -> Parser GetPromptResult)
-> Value
-> Parser GetPromptResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetPromptResult" ((Object -> Parser GetPromptResult)
-> Value -> Parser GetPromptResult)
-> (Object -> Parser GetPromptResult)
-> Value
-> Parser GetPromptResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
Maybe ProtocolVersion
description <- Object
o Object -> Key -> Parser (Maybe ProtocolVersion)
forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
.:? Key
"description"
[PromptMessage]
messages <- Object
o Object -> Key -> Parser [PromptMessage]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"messages"
return $ Maybe ProtocolVersion -> [PromptMessage] -> GetPromptResult
GetPromptResult Maybe ProtocolVersion
description [PromptMessage]
messages
data ListRootsRequest = ListRootsRequest
deriving (Int -> ListRootsRequest -> ShowS
[ListRootsRequest] -> ShowS
ListRootsRequest -> String
(Int -> ListRootsRequest -> ShowS)
-> (ListRootsRequest -> String)
-> ([ListRootsRequest] -> ShowS)
-> Show ListRootsRequest
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListRootsRequest -> ShowS
showsPrec :: Int -> ListRootsRequest -> ShowS
$cshow :: ListRootsRequest -> String
show :: ListRootsRequest -> String
$cshowList :: [ListRootsRequest] -> ShowS
showList :: [ListRootsRequest] -> ShowS
Show, ListRootsRequest -> ListRootsRequest -> Bool
(ListRootsRequest -> ListRootsRequest -> Bool)
-> (ListRootsRequest -> ListRootsRequest -> Bool)
-> Eq ListRootsRequest
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListRootsRequest -> ListRootsRequest -> Bool
== :: ListRootsRequest -> ListRootsRequest -> Bool
$c/= :: ListRootsRequest -> ListRootsRequest -> Bool
/= :: ListRootsRequest -> ListRootsRequest -> Bool
Eq, (forall x. ListRootsRequest -> Rep ListRootsRequest x)
-> (forall x. Rep ListRootsRequest x -> ListRootsRequest)
-> Generic ListRootsRequest
forall x. Rep ListRootsRequest x -> ListRootsRequest
forall x. ListRootsRequest -> Rep ListRootsRequest x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListRootsRequest -> Rep ListRootsRequest x
from :: forall x. ListRootsRequest -> Rep ListRootsRequest x
$cto :: forall x. Rep ListRootsRequest x -> ListRootsRequest
to :: forall x. Rep ListRootsRequest x -> ListRootsRequest
Generic)
instance ToJSON ListRootsRequest where
toJSON :: ListRootsRequest -> Value
toJSON ListRootsRequest
_ = [Pair] -> Value
object []
instance FromJSON ListRootsRequest where
parseJSON :: Value -> Parser ListRootsRequest
parseJSON = String
-> (Object -> Parser ListRootsRequest)
-> Value
-> Parser ListRootsRequest
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListRootsRequest" ((Object -> Parser ListRootsRequest)
-> Value -> Parser ListRootsRequest)
-> (Object -> Parser ListRootsRequest)
-> Value
-> Parser ListRootsRequest
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ListRootsRequest -> Parser ListRootsRequest
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ListRootsRequest
ListRootsRequest
data ListRootsResult = ListRootsResult
{
ListRootsResult -> [Root]
listRootsResult :: [Root]
}
deriving (Int -> ListRootsResult -> ShowS
[ListRootsResult] -> ShowS
ListRootsResult -> String
(Int -> ListRootsResult -> ShowS)
-> (ListRootsResult -> String)
-> ([ListRootsResult] -> ShowS)
-> Show ListRootsResult
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ListRootsResult -> ShowS
showsPrec :: Int -> ListRootsResult -> ShowS
$cshow :: ListRootsResult -> String
show :: ListRootsResult -> String
$cshowList :: [ListRootsResult] -> ShowS
showList :: [ListRootsResult] -> ShowS
Show, ListRootsResult -> ListRootsResult -> Bool
(ListRootsResult -> ListRootsResult -> Bool)
-> (ListRootsResult -> ListRootsResult -> Bool)
-> Eq ListRootsResult
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListRootsResult -> ListRootsResult -> Bool
== :: ListRootsResult -> ListRootsResult -> Bool
$c/= :: ListRootsResult -> ListRootsResult -> Bool
/= :: ListRootsResult -> ListRootsResult -> Bool
Eq, (forall x. ListRootsResult -> Rep ListRootsResult x)
-> (forall x. Rep ListRootsResult x -> ListRootsResult)
-> Generic ListRootsResult
forall x. Rep ListRootsResult x -> ListRootsResult
forall x. ListRootsResult -> Rep ListRootsResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ListRootsResult -> Rep ListRootsResult x
from :: forall x. ListRootsResult -> Rep ListRootsResult x
$cto :: forall x. Rep ListRootsResult x -> ListRootsResult
to :: forall x. Rep ListRootsResult x -> ListRootsResult
Generic)
instance ToJSON ListRootsResult where
toJSON :: ListRootsResult -> Value
toJSON ListRootsResult {[Root]
$sel:listRootsResult:ListRootsResult :: ListRootsResult -> [Root]
listRootsResult :: [Root]
..} =
[Pair] -> Value
object
[ Key
"roots" Key -> [Root] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [Root]
listRootsResult
]
instance FromJSON ListRootsResult where
parseJSON :: Value -> Parser ListRootsResult
parseJSON = String
-> (Object -> Parser ListRootsResult)
-> Value
-> Parser ListRootsResult
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ListRootsResult" ((Object -> Parser ListRootsResult)
-> Value -> Parser ListRootsResult)
-> (Object -> Parser ListRootsResult)
-> Value
-> Parser ListRootsResult
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
[Root]
roots <- Object
o Object -> Key -> Parser [Root]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"roots"
return $ [Root] -> ListRootsResult
ListRootsResult [Root]
roots
data ResourcesListChangedNotification = ResourcesListChangedNotification
deriving (Int -> ResourcesListChangedNotification -> ShowS
[ResourcesListChangedNotification] -> ShowS
ResourcesListChangedNotification -> String
(Int -> ResourcesListChangedNotification -> ShowS)
-> (ResourcesListChangedNotification -> String)
-> ([ResourcesListChangedNotification] -> ShowS)
-> Show ResourcesListChangedNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourcesListChangedNotification -> ShowS
showsPrec :: Int -> ResourcesListChangedNotification -> ShowS
$cshow :: ResourcesListChangedNotification -> String
show :: ResourcesListChangedNotification -> String
$cshowList :: [ResourcesListChangedNotification] -> ShowS
showList :: [ResourcesListChangedNotification] -> ShowS
Show, ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool
(ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool)
-> (ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool)
-> Eq ResourcesListChangedNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool
== :: ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool
$c/= :: ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool
/= :: ResourcesListChangedNotification
-> ResourcesListChangedNotification -> Bool
Eq, (forall x.
ResourcesListChangedNotification
-> Rep ResourcesListChangedNotification x)
-> (forall x.
Rep ResourcesListChangedNotification x
-> ResourcesListChangedNotification)
-> Generic ResourcesListChangedNotification
forall x.
Rep ResourcesListChangedNotification x
-> ResourcesListChangedNotification
forall x.
ResourcesListChangedNotification
-> Rep ResourcesListChangedNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ResourcesListChangedNotification
-> Rep ResourcesListChangedNotification x
from :: forall x.
ResourcesListChangedNotification
-> Rep ResourcesListChangedNotification x
$cto :: forall x.
Rep ResourcesListChangedNotification x
-> ResourcesListChangedNotification
to :: forall x.
Rep ResourcesListChangedNotification x
-> ResourcesListChangedNotification
Generic)
instance ToJSON ResourcesListChangedNotification where
toJSON :: ResourcesListChangedNotification -> Value
toJSON ResourcesListChangedNotification
_ = [Pair] -> Value
object []
instance FromJSON ResourcesListChangedNotification where
parseJSON :: Value -> Parser ResourcesListChangedNotification
parseJSON = String
-> (Object -> Parser ResourcesListChangedNotification)
-> Value
-> Parser ResourcesListChangedNotification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResourcesListChangedNotification" ((Object -> Parser ResourcesListChangedNotification)
-> Value -> Parser ResourcesListChangedNotification)
-> (Object -> Parser ResourcesListChangedNotification)
-> Value
-> Parser ResourcesListChangedNotification
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ResourcesListChangedNotification
-> Parser ResourcesListChangedNotification
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ResourcesListChangedNotification
ResourcesListChangedNotification
data ResourceUpdatedNotification = ResourceUpdatedNotification
{
ResourceUpdatedNotification -> ProtocolVersion
resourceUpdatedUri :: Text
}
deriving (Int -> ResourceUpdatedNotification -> ShowS
[ResourceUpdatedNotification] -> ShowS
ResourceUpdatedNotification -> String
(Int -> ResourceUpdatedNotification -> ShowS)
-> (ResourceUpdatedNotification -> String)
-> ([ResourceUpdatedNotification] -> ShowS)
-> Show ResourceUpdatedNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ResourceUpdatedNotification -> ShowS
showsPrec :: Int -> ResourceUpdatedNotification -> ShowS
$cshow :: ResourceUpdatedNotification -> String
show :: ResourceUpdatedNotification -> String
$cshowList :: [ResourceUpdatedNotification] -> ShowS
showList :: [ResourceUpdatedNotification] -> ShowS
Show, ResourceUpdatedNotification -> ResourceUpdatedNotification -> Bool
(ResourceUpdatedNotification
-> ResourceUpdatedNotification -> Bool)
-> (ResourceUpdatedNotification
-> ResourceUpdatedNotification -> Bool)
-> Eq ResourceUpdatedNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ResourceUpdatedNotification -> ResourceUpdatedNotification -> Bool
== :: ResourceUpdatedNotification -> ResourceUpdatedNotification -> Bool
$c/= :: ResourceUpdatedNotification -> ResourceUpdatedNotification -> Bool
/= :: ResourceUpdatedNotification -> ResourceUpdatedNotification -> Bool
Eq, (forall x.
ResourceUpdatedNotification -> Rep ResourceUpdatedNotification x)
-> (forall x.
Rep ResourceUpdatedNotification x -> ResourceUpdatedNotification)
-> Generic ResourceUpdatedNotification
forall x.
Rep ResourceUpdatedNotification x -> ResourceUpdatedNotification
forall x.
ResourceUpdatedNotification -> Rep ResourceUpdatedNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ResourceUpdatedNotification -> Rep ResourceUpdatedNotification x
from :: forall x.
ResourceUpdatedNotification -> Rep ResourceUpdatedNotification x
$cto :: forall x.
Rep ResourceUpdatedNotification x -> ResourceUpdatedNotification
to :: forall x.
Rep ResourceUpdatedNotification x -> ResourceUpdatedNotification
Generic)
instance ToJSON ResourceUpdatedNotification where
toJSON :: ResourceUpdatedNotification -> Value
toJSON ResourceUpdatedNotification {ProtocolVersion
$sel:resourceUpdatedUri:ResourceUpdatedNotification :: ResourceUpdatedNotification -> ProtocolVersion
resourceUpdatedUri :: ProtocolVersion
..} =
[Pair] -> Value
object
[ Key
"uri" Key -> ProtocolVersion -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= ProtocolVersion
resourceUpdatedUri
]
instance FromJSON ResourceUpdatedNotification where
parseJSON :: Value -> Parser ResourceUpdatedNotification
parseJSON = String
-> (Object -> Parser ResourceUpdatedNotification)
-> Value
-> Parser ResourceUpdatedNotification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ResourceUpdatedNotification" ((Object -> Parser ResourceUpdatedNotification)
-> Value -> Parser ResourceUpdatedNotification)
-> (Object -> Parser ResourceUpdatedNotification)
-> Value
-> Parser ResourceUpdatedNotification
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
ProtocolVersion
uri <- Object
o Object -> Key -> Parser ProtocolVersion
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"uri"
return $ ProtocolVersion -> ResourceUpdatedNotification
ResourceUpdatedNotification ProtocolVersion
uri
data ToolsListChangedNotification = ToolsListChangedNotification
deriving (Int -> ToolsListChangedNotification -> ShowS
[ToolsListChangedNotification] -> ShowS
ToolsListChangedNotification -> String
(Int -> ToolsListChangedNotification -> ShowS)
-> (ToolsListChangedNotification -> String)
-> ([ToolsListChangedNotification] -> ShowS)
-> Show ToolsListChangedNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ToolsListChangedNotification -> ShowS
showsPrec :: Int -> ToolsListChangedNotification -> ShowS
$cshow :: ToolsListChangedNotification -> String
show :: ToolsListChangedNotification -> String
$cshowList :: [ToolsListChangedNotification] -> ShowS
showList :: [ToolsListChangedNotification] -> ShowS
Show, ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool
(ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool)
-> (ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool)
-> Eq ToolsListChangedNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool
== :: ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool
$c/= :: ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool
/= :: ToolsListChangedNotification
-> ToolsListChangedNotification -> Bool
Eq, (forall x.
ToolsListChangedNotification -> Rep ToolsListChangedNotification x)
-> (forall x.
Rep ToolsListChangedNotification x -> ToolsListChangedNotification)
-> Generic ToolsListChangedNotification
forall x.
Rep ToolsListChangedNotification x -> ToolsListChangedNotification
forall x.
ToolsListChangedNotification -> Rep ToolsListChangedNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
ToolsListChangedNotification -> Rep ToolsListChangedNotification x
from :: forall x.
ToolsListChangedNotification -> Rep ToolsListChangedNotification x
$cto :: forall x.
Rep ToolsListChangedNotification x -> ToolsListChangedNotification
to :: forall x.
Rep ToolsListChangedNotification x -> ToolsListChangedNotification
Generic)
instance ToJSON ToolsListChangedNotification where
toJSON :: ToolsListChangedNotification -> Value
toJSON ToolsListChangedNotification
_ = [Pair] -> Value
object []
instance FromJSON ToolsListChangedNotification where
parseJSON :: Value -> Parser ToolsListChangedNotification
parseJSON = String
-> (Object -> Parser ToolsListChangedNotification)
-> Value
-> Parser ToolsListChangedNotification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"ToolsListChangedNotification" ((Object -> Parser ToolsListChangedNotification)
-> Value -> Parser ToolsListChangedNotification)
-> (Object -> Parser ToolsListChangedNotification)
-> Value
-> Parser ToolsListChangedNotification
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
ToolsListChangedNotification -> Parser ToolsListChangedNotification
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return ToolsListChangedNotification
ToolsListChangedNotification
data PromptsListChangedNotification = PromptsListChangedNotification
deriving (Int -> PromptsListChangedNotification -> ShowS
[PromptsListChangedNotification] -> ShowS
PromptsListChangedNotification -> String
(Int -> PromptsListChangedNotification -> ShowS)
-> (PromptsListChangedNotification -> String)
-> ([PromptsListChangedNotification] -> ShowS)
-> Show PromptsListChangedNotification
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PromptsListChangedNotification -> ShowS
showsPrec :: Int -> PromptsListChangedNotification -> ShowS
$cshow :: PromptsListChangedNotification -> String
show :: PromptsListChangedNotification -> String
$cshowList :: [PromptsListChangedNotification] -> ShowS
showList :: [PromptsListChangedNotification] -> ShowS
Show, PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool
(PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool)
-> (PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool)
-> Eq PromptsListChangedNotification
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool
== :: PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool
$c/= :: PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool
/= :: PromptsListChangedNotification
-> PromptsListChangedNotification -> Bool
Eq, (forall x.
PromptsListChangedNotification
-> Rep PromptsListChangedNotification x)
-> (forall x.
Rep PromptsListChangedNotification x
-> PromptsListChangedNotification)
-> Generic PromptsListChangedNotification
forall x.
Rep PromptsListChangedNotification x
-> PromptsListChangedNotification
forall x.
PromptsListChangedNotification
-> Rep PromptsListChangedNotification x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x.
PromptsListChangedNotification
-> Rep PromptsListChangedNotification x
from :: forall x.
PromptsListChangedNotification
-> Rep PromptsListChangedNotification x
$cto :: forall x.
Rep PromptsListChangedNotification x
-> PromptsListChangedNotification
to :: forall x.
Rep PromptsListChangedNotification x
-> PromptsListChangedNotification
Generic)
instance ToJSON PromptsListChangedNotification where
toJSON :: PromptsListChangedNotification -> Value
toJSON PromptsListChangedNotification
_ = [Pair] -> Value
object []
instance FromJSON PromptsListChangedNotification where
parseJSON :: Value -> Parser PromptsListChangedNotification
parseJSON = String
-> (Object -> Parser PromptsListChangedNotification)
-> Value
-> Parser PromptsListChangedNotification
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"PromptsListChangedNotification" ((Object -> Parser PromptsListChangedNotification)
-> Value -> Parser PromptsListChangedNotification)
-> (Object -> Parser PromptsListChangedNotification)
-> Value
-> Parser PromptsListChangedNotification
forall a b. (a -> b) -> a -> b
$ \Object
_ ->
PromptsListChangedNotification
-> Parser PromptsListChangedNotification
forall a. a -> Parser a
forall (m :: * -> *) a. Monad m => a -> m a
return PromptsListChangedNotification
PromptsListChangedNotification
maybeToList :: Maybe a -> [a]
maybeToList :: forall a. Maybe a -> [a]
maybeToList Maybe a
Nothing = []
maybeToList (Just a
x) = [a
x]