{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}

module Cachix.API.Deploy where

import Cachix.API (CachixAuth)
import qualified Cachix.Types.ByteStringStreaming as ByteStringStreaming
import qualified Cachix.Types.Deploy as Deploy
import qualified Cachix.Types.DeployResponse as DeployResponse
import Conduit (ConduitT, ResourceT)
import qualified Data.UUID as UUID
import Protolude
import Servant.API
import Servant.API.Generic

data DeployAPI route = DeployAPI
  { DeployAPI route
-> route
   :- (CachixAuth
       :> ("deploy"
           :> ("activate"
               :> (ReqBody '[JSON] Deploy :> Post '[JSON] DeployResponse))))
activate ::
      route
        :- CachixAuth
        :> "deploy"
        :> "activate"
        :> ReqBody '[JSON] Deploy.Deploy
        :> Post '[JSON] DeployResponse.DeployResponse
  }
  deriving ((forall x. DeployAPI route -> Rep (DeployAPI route) x)
-> (forall x. Rep (DeployAPI route) x -> DeployAPI route)
-> Generic (DeployAPI route)
forall x. Rep (DeployAPI route) x -> DeployAPI route
forall x. DeployAPI route -> Rep (DeployAPI route) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall route x. Rep (DeployAPI route) x -> DeployAPI route
forall route x. DeployAPI route -> Rep (DeployAPI route) x
$cto :: forall route x. Rep (DeployAPI route) x -> DeployAPI route
$cfrom :: forall route x. DeployAPI route -> Rep (DeployAPI route) x
Generic)

type API = "api" :> "v1" :> ToServantApi DeployAPI

api :: Proxy API
api :: Proxy API
api = Proxy API
forall k (t :: k). Proxy t
Proxy