Skip to content
Snippets Groups Projects

Draft: Servant Api Specification

Open Emily Pillmore requested to merge emily/modular-servant-api into master
Files
11
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Distribution.Skete.Haskell.API.Features.Core
( -- * Core API
CoreApi(..)
, coreApi
, coreApiHandlers
, coreApiServer
-- ** Package list endpoints
, GetPackagesIndexApi
, getPackagesIndexApi
-- ** Package index endpoints
, GetIndexGzipApi
, getIndexGzipApi
, GetIndexTarballApi
, getIndexTarballApi
-- ** Get package endpoints
, GetPackagesApi
, getPackagesApi
, PostPackagesApi
, postPackagesApi
-- ** Package info endpoints
, GetPackageIdApi
, getPackageIdApi
, GetPackageIdGzipApi
, getPackageIdGzipApi
, PutPackageIdGzipApi
, putPackageIdGzipApi
, GetPackageIdCabalApi
, getPackageIdCabalApi
, PutPackageIdCabalApi
, putPackageIdCabalApi
, GetPackageIdRevisionsApi
, getPackageIdRevisionsApi
, GetPackageIdRevisionApi
, getPackageIdRevisionApi
) where
import Distribution.Skete.Haskell.API.Types.Core
import Servant
import Servant.API.Generic
import Servant.HTML.Blaze
import Servant.Server.Generic
data CoreApi route
= CoreApi
{ getPackagesIndex :: route :- GetPackagesIndexApi
, getIndexGzip :: route :- GetIndexGzipApi
, getIndexTarball :: route :- GetIndexTarballApi
, getPackages :: route :- GetPackagesApi
, postPackages :: route :- PostPackagesApi
, getPackageId :: route :- GetPackageIdApi
, getPackageIdGzip :: route :- GetPackageIdGzipApi
, putPackageIdGzip :: route :- PutPackageIdGzipApi
, getPackageIdCabal :: route :- GetPackageIdCabalApi
, putPackageIdCabal :: route :- PutPackageIdCabalApi
, getPackageIdRevisions :: route :- GetPackageIdRevisionsApi
, getPackageIdRevision :: route :- GetPackageIdRevisionApi
} deriving Generic
-- | Singleton instance for 'CoreApi'.
--
coreApi :: Proxy (ToServantApi CoreApi)
coreApi = genericApi (Proxy :: Proxy CoreApi)
-- | Core Api Handlers.
--
-- TODO: Stubbed in Distribution.Skete.Haskell.API.Features.Core.Server
--
coreApiHandlers :: CoreApi AsServer
coreApiHandlers = CoreApi
{ getPackagesIndex = error "TODO: handler not yet written"
, getIndexGzip = error "TODO: handler not yet written"
, getIndexTarball = error "TODO: handler not yet written"
, getPackages = error "TODO: handler not yet written"
, postPackages = error "TODO: handler not yet written"
, getPackageId = error "TODO: handler not yet written"
, getPackageIdGzip = error "TODO: handler not yet written"
, putPackageIdGzip = error "TODO: handler not yet written"
, getPackageIdCabal = error "TODO: handler not yet written"
, putPackageIdCabal = error "TODO: handler not yet written"
, getPackageIdRevisions = error "TODO: handler not yet written"
, getPackageIdRevision = error "TODO: handler not yet written"
}
-- | Core API server instance
--
coreApiServer :: ToServant CoreApi AsServer
coreApiServer = genericServer coreApiHandlers
-- -------------------------------------------------------------------- --
-- GET /packages/index.tar.gz
type GetPackagesIndexApi
= Summary "Get gzip of package index."
:> Description "Get gzip of package descriptions from Hackage server."
:> "packages"
:> "index.tar.gz"
:> Get '[Gzip] Gzip
getPackagesIndexApi :: Proxy GetPackagesIndexApi
getPackagesIndexApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /packages/index.tar.gz
type GetIndexGzipApi
= Summary "Get gzip of package index."
:> Description "Get gzip of the package index for Hackage server."
:> "01-index.tar.gz"
:> Get '[Gzip] Gzip
getIndexGzipApi :: Proxy GetIndexGzipApi
getIndexGzipApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /packages/index.tar
type GetIndexTarballApi
= Summary "Get tarball of package index."
:> Description "Get tarball of the package index for Hackage server."
:> "01-index.tar"
:> Get '[Tarball] Tarball
getIndexTarballApi :: Proxy GetIndexTarballApi
getIndexTarballApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /packages/
type GetPackagesApi
= Summary "Get list of all packages"
:> Description "Get list of all packages for Hackage server."
:> "packages"
:> Get '[JSON, HTML] [PkgInfo]
getPackagesApi :: Proxy GetPackagesApi
getPackagesApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /packages/
type PostPackagesApi
= Summary "Upload a package"
:> Description "Upload a package to a Hackage server."
:> "packages"
:> ReqBody '[HTML] PkgInfo
:> Post '[HTML] PkgInfo
postPackagesApi :: Proxy PostPackagesApi
postPackagesApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /package/:package
type GetPackageIdApi
= Summary "Show detailed package info."
:> Description "Show detailed description of a Hackage package."
:> "package"
:> Capture "package"
:> Get '[HTML] [PkgInfo]
getPackageIdApi :: Proxy GetPackageIdApi
getPackageIdApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /package/:package/:tarball.tar.gz
type GetPackageIdGzipApi
= Summary "Get package tarball"
:> Description "Get package description tarball for a Hackage package."
:> "package"
:> Capture "package"
:> Capture "tarball.tar.gz"
:> Get '[Gzip] Gzip
getPackageIdGzipApi :: Proxy GetPackageIdGzipApi
getPackageIdGzipApi = Proxy
-- -------------------------------------------------------------------- --
-- PUT /package/:package/:tarball.tar.gz
type PutPackageIdGzipApi
= Summary "Get package tarball"
:> Description "Get package description tarball for a Hackage package."
:> "package"
:> Capture "package"
:> Capture "tarball.tar.gz"
:> Put '[Gzip] Gzip
putPackageIdGzipApi :: Proxy PutPackageIdGzipApi
putPackageIdGzipApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /package/:package/:cabal.cabal
type GetPackageIdCabalApi
= Summary "Get package .cabal file"
:> Description "Get package description .cabal file for a Hackage package."
:> "package"
:> Capture "package"
:> Capture "cabal.cabal"
:> Get '[OctetStream] CabalFileText
getPackageIdCabalApi :: Proxy GetPackageIdCabalApi
getPackageIdCabalApi = Proxy
-- -------------------------------------------------------------------- --
-- Put /package/:package/:cabal.cabal
type PutPackageIdCabalApi
= Summary "Get package .cabal file"
:> Description "Get package description .cabal file for a Hackage package."
:> "package"
:> Capture "package"
:> Capture "cabal.cabal"
:> Put '[CabalFileText] CabalFileText
putPackageIdCabalApi :: Proxy PutPackageIdCabalApi
putPackageIdCabalApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /package/:package/revisions
type GetPackageIdRevisionsApi
= Summary "Get package .cabal file"
:> Description "Get package description .cabal file for a Hackage package."
:> "package"
:> Capture "package"
:> "revisions"
:> Get '[JSON, HTML] [CabalFileText]
getPackageIdRevisionsApi :: Proxy GetPackageIdRevisionsApi
getPackageIdRevisionsApi = Proxy
-- -------------------------------------------------------------------- --
-- GET /package/:package/revisions/:revision
type GetPackageIdRevisionApi
= Summary "Get package .cabal file"
:> Description "Get package description .cabal file for a Hackage package."
:> "package"
:> Capture "package"
:> "revisions"
:> Capture "revision"
:> Get '[CabalFileText] CabalFileText
getPackageIdRevisionApi :: Proxy GetPackageIdRevisionApi
getPackageIdRevisionApi = Proxy
Loading