{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Hercules.API.State where
import Data.ByteString (ByteString)
import Data.Swagger (NamedSchema (NamedSchema), binarySchema)
import Data.Swagger.Schema (ToSchema (..))
import Hercules.API.Accounts.Account (Account)
import Hercules.API.Prelude
import Hercules.API.Projects.Project (Project)
import Hercules.API.SourceHostingSite.SourceHostingSite (SourceHostingSite)
import Hercules.API.State.ProjectState (ProjectState)
import Servant.API
import Servant.API.Generic
newtype RawBytes = RawBytes {RawBytes -> ByteString
fromRawBytes :: ByteString}
deriving newtype (MimeUnrender OctetStream, MimeRender OctetStream)
instance ToSchema RawBytes where
declareNamedSchema :: Proxy RawBytes -> Declare (Definitions Schema) NamedSchema
declareNamedSchema Proxy RawBytes
_ = NamedSchema -> Declare (Definitions Schema) NamedSchema
forall (f :: * -> *) a. Applicative f => a -> f a
pure (NamedSchema -> Declare (Definitions Schema) NamedSchema)
-> NamedSchema -> Declare (Definitions Schema) NamedSchema
forall a b. (a -> b) -> a -> b
$ Maybe Text -> Schema -> NamedSchema
NamedSchema (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"RawBytes") Schema
binarySchema
type ContentLength = Header "Content-Length" Integer
type ContentDisposition = Header "Content-Disposition" Text
data ProjectStateResourceGroup auth f = ProjectStateResourceGroup
{ ProjectStateResourceGroup auth f
-> f
:- (Summary "Upload a state file"
:> ("state"
:> (Capture' '[Required, Strict] "stateName" Text
:> ("data"
:> (StreamBody NoFraming OctetStream (SourceIO RawBytes)
:> (auth :> Put '[JSON] NoContent))))))
putStateData ::
f :- Summary "Upload a state file"
:> "state"
:> Capture' '[Required, Strict] "stateName" Text
:> "data"
:> StreamBody NoFraming OctetStream (SourceIO RawBytes)
:> auth
:> Put '[JSON] NoContent,
ProjectStateResourceGroup auth f
-> f
:- (Summary "List all state files"
:> ("states" :> (auth :> Get '[JSON] ProjectState)))
getStates ::
f :- Summary "List all state files"
:> "states"
:> auth
:> Get '[JSON] ProjectState,
ProjectStateResourceGroup auth f
-> f
:- (Summary "Download a state file"
:> ("state"
:> (Capture' '[Required, Strict] "stateName" Text
:> ("data"
:> (QueryParam' '[Optional, Strict] "version" Int
:> (auth
:> StreamGet
NoFraming
OctetStream
(Headers
'[ContentLength, ContentDisposition] (SourceIO RawBytes))))))))
getStateData ::
f :- Summary "Download a state file"
:> "state"
:> Capture' '[Required, Strict] "stateName" Text
:> "data"
:> QueryParam' '[Optional, Strict] "version" Int
:> auth
:> StreamGet NoFraming OctetStream (Headers '[ContentLength, ContentDisposition] (SourceIO RawBytes))
}
deriving ((forall x.
ProjectStateResourceGroup auth f
-> Rep (ProjectStateResourceGroup auth f) x)
-> (forall x.
Rep (ProjectStateResourceGroup auth f) x
-> ProjectStateResourceGroup auth f)
-> Generic (ProjectStateResourceGroup auth f)
forall x.
Rep (ProjectStateResourceGroup auth f) x
-> ProjectStateResourceGroup auth f
forall x.
ProjectStateResourceGroup auth f
-> Rep (ProjectStateResourceGroup auth f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x.
Rep (ProjectStateResourceGroup auth f) x
-> ProjectStateResourceGroup auth f
forall auth f x.
ProjectStateResourceGroup auth f
-> Rep (ProjectStateResourceGroup auth f) x
$cto :: forall auth f x.
Rep (ProjectStateResourceGroup auth f) x
-> ProjectStateResourceGroup auth f
$cfrom :: forall auth f x.
ProjectStateResourceGroup auth f
-> Rep (ProjectStateResourceGroup auth f) x
Generic)
data StateAPI auth f = StateAPI
{ StateAPI auth f
-> f
:- Substitute
("projects"
:> (Capture' '[Required, Strict] "projectId" (Id Project)
:> Placeholder))
(ToServantApi (ProjectStateResourceGroup auth))
byProjectId ::
f
:- Substitute
( "projects"
:> Capture' '[Required, Strict] "projectId" (Id Project)
:> Placeholder
)
(ToServantApi (ProjectStateResourceGroup auth)),
StateAPI auth f
-> f
:- Substitute
("site"
:> (Capture' '[Required, Strict] "site" (Name SourceHostingSite)
:> ("account"
:> (Capture' '[Required, Strict] "account" (Name Account)
:> ("project"
:> (Capture' '[Required, Strict] "project" (Name Project)
:> Placeholder))))))
(ToServantApi (ProjectStateResourceGroup auth))
byProjectName ::
f
:- Substitute
( "site"
:> Capture' '[Required, Strict] "site" (Name SourceHostingSite)
:> "account"
:> Capture' '[Required, Strict] "account" (Name Account)
:> "project"
:> Capture' '[Required, Strict] "project" (Name Project)
:> Placeholder
)
(ToServantApi (ProjectStateResourceGroup auth))
}
deriving ((forall x. StateAPI auth f -> Rep (StateAPI auth f) x)
-> (forall x. Rep (StateAPI auth f) x -> StateAPI auth f)
-> Generic (StateAPI auth f)
forall x. Rep (StateAPI auth f) x -> StateAPI auth f
forall x. StateAPI auth f -> Rep (StateAPI auth f) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall auth f x. Rep (StateAPI auth f) x -> StateAPI auth f
forall auth f x. StateAPI auth f -> Rep (StateAPI auth f) x
$cto :: forall auth f x. Rep (StateAPI auth f) x -> StateAPI auth f
$cfrom :: forall auth f x. StateAPI auth f -> Rep (StateAPI auth f) x
Generic)