cachix-api-0.7.0: Servant HTTP API specification for https://cachix.org
Safe HaskellNone
LanguageHaskell2010

Cachix.API.WebSocketSubprotocol

Documentation

data Message cmd Source #

Constructors

Message 

Fields

Instances

Instances details
Eq cmd => Eq (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Methods

(==) :: Message cmd -> Message cmd -> Bool #

(/=) :: Message cmd -> Message cmd -> Bool #

Show cmd => Show (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Methods

showsPrec :: Int -> Message cmd -> ShowS #

show :: Message cmd -> String #

showList :: [Message cmd] -> ShowS #

Generic (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep (Message cmd) :: Type -> Type #

Methods

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

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

ToJSON cmd => ToJSON (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON cmd => FromJSON (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep (Message cmd) Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep (Message cmd) = D1 ('MetaData "Message" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "Message" 'PrefixI 'True) ((S1 ('MetaSel ('Just "method") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "command") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 cmd)) :*: (S1 ('MetaSel ('Just "agent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe UUID)) :*: S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID))))

data Cache Source #

Constructors

Cache 

Instances

Instances details
Eq Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Methods

(==) :: Cache -> Cache -> Bool #

(/=) :: Cache -> Cache -> Bool #

Show Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Methods

showsPrec :: Int -> Cache -> ShowS #

show :: Cache -> String #

showList :: [Cache] -> ShowS #

Generic Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep Cache :: Type -> Type #

Methods

from :: Cache -> Rep Cache x #

to :: Rep Cache x -> Cache #

ToJSON Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep Cache Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep Cache = D1 ('MetaData "Cache" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "Cache" 'PrefixI 'True) (S1 ('MetaSel ('Just "cacheName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "publicKey") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "isPublic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

data AgentInformation Source #

Constructors

AgentInformation 

Fields

Instances

Instances details
Eq AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Show AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Generic AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep AgentInformation :: Type -> Type #

ToJSON AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep AgentInformation Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep AgentInformation = D1 ('MetaData "AgentInformation" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "AgentInformation" 'PrefixI 'True) (S1 ('MetaSel ('Just "cache") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Cache)) :*: S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

data DeploymentDetails Source #

Constructors

DeploymentDetails 

Fields

Instances

Instances details
Eq DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Show DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Generic DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep DeploymentDetails :: Type -> Type #

ToJSON DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep DeploymentDetails Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep DeploymentDetails = D1 ('MetaData "DeploymentDetails" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "DeploymentDetails" 'PrefixI 'True) (S1 ('MetaSel ('Just "storePath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID) :*: S1 ('MetaSel ('Just "index") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64))))

data BackendCommand Source #

Instances

Instances details
Eq BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Show BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Generic BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep BackendCommand :: Type -> Type #

ToJSON BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep BackendCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep BackendCommand = D1 ('MetaData "BackendCommand" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "Deployment" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DeploymentDetails)) :+: C1 ('MetaCons "AgentRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AgentInformation)))

data AgentCommand Source #

Constructors

DeploymentStarted 

Fields

DeploymentFinished 

Fields

Instances

Instances details
Eq AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Show AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Generic AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep AgentCommand :: Type -> Type #

ToJSON AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep AgentCommand Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep AgentCommand = D1 ('MetaData "AgentCommand" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "DeploymentStarted" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID) :*: S1 ('MetaSel ('Just "time") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)) :+: C1 ('MetaCons "DeploymentFinished" 'PrefixI 'True) (S1 ('MetaSel ('Just "id") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID) :*: (S1 ('MetaSel ('Just "time") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime) :*: S1 ('MetaSel ('Just "hasSucceeded") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))

sendMessage :: ToJSON cmd => Connection -> Message cmd -> IO () Source #

data Log Source #

Constructors

Log 

Fields

Instances

Instances details
Show Log Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Methods

showsPrec :: Int -> Log -> ShowS #

show :: Log -> String #

showList :: [Log] -> ShowS #

Generic Log Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

Associated Types

type Rep Log :: Type -> Type #

Methods

from :: Log -> Rep Log x #

to :: Rep Log x -> Log #

ToJSON Log Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

FromJSON Log Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep Log Source # 
Instance details

Defined in Cachix.API.WebSocketSubprotocol

type Rep Log = D1 ('MetaData "Log" "Cachix.API.WebSocketSubprotocol" "cachix-api-0.7.0-BFFRP5WN6zAAytcfqK4iAg" 'False) (C1 ('MetaCons "Log" 'PrefixI 'True) (S1 ('MetaSel ('Just "line") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "time") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))