{-# LANGUAGE TemplateHaskell, OverloadedStrings #-} module Spm.Api ( SpmStyle(..), _SpmWords, _SpmConsonants , SpmMailbox , SpmApi, spmApi ) where import Prelude import Servant.API import Data.Proxy (Proxy(..)) import Data.Text (Text) import GHC.Generics (Generic) import Type.Reflection (Typeable) import Control.Lens.TH import Data.CaseInsensitive (CI) import qualified Data.CaseInsensitive as CI import Data.CaseInsensitive.Instances () import Crypto.JOSE.JWK (JWKSet) import Crypto.JWT (SignedJWT) import Crypto.JWT.Instances () import Data.UUID (UUID) import Data.UUID.Instances () -- import Data.Aeson (ToJSON, FromJSON) data SpmStyle = SpmWords | SpmConsonants deriving (Eq, Ord, Read, Show, Bounded, Enum) makePrisms ''SpmStyle instance ToHttpApiData SpmStyle where toUrlPiece = \case SpmWords -> "words" SpmConsonants -> "consonants" instance FromHttpApiData SpmStyle where parseUrlPiece t@(CI.mk -> t') | t' == "words" = Right SpmWords | t' == "consonants" = Right SpmConsonants | otherwise = Left $ "Expected one of ‘words’ or ‘consonants’ but got ‘" <> t <> "’" newtype SpmMailbox = SpmMailbox { unSpmMailbox :: CI Text } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) deriving newtype (MimeRender JSON, MimeRender PlainText) makeWrapped ''SpmMailbox -- newtype SpmLocal = SpmLocal -- { unSpmLocal :: CI Text -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) -- deriving newtype (ToJSON, FromJSON) -- makeWrapped ''SpmLocal -- newtype SpmExtension = SpmExtension -- { unSpmExtension :: CI Text -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) -- deriving newtype (ToJSON, FromJSON) -- makeWrapped ''SpmExtension -- newtype SpmMappingListing = SpmMappingListing { unSpmMappingListing :: Set SpmMapping } -- deriving stock (Eq, Ord, Read, Show, Generic, Typeable) -- instance ToJSON SpmMappingList where -- toJSON SpmMappingListing{..} = object [ "mappings" .= unSpmMappingListing ] -- data SpmMapping = SpmMapping -- { spmMappingLocal :: Maybe SpmLocal -- , spmMappingExtension :: Maybe SpmExtension -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) -- instance ToJSON SpmMapping where -- toJSON SpmMapping{..} = object -- [ "local" .= spmMappingLocal -- , "extension" .= spmMappingExtension -- ] type SpmApi = "whoami" :> Get '[PlainText, JSON] SpmMailbox :<|> "jwks.json" :> Get '[JSON] JWKSet :<|> "instance-id" :> Get '[PlainText, JSON, OctetStream] UUID :<|> "spm" :> "generate" :> QueryParam "style" SpmStyle :> Get '[PlainText, JSON, OctetStream] SignedJWT :<|> "spm" :> "claim" :> ReqBody '[PlainText, JSON, OctetStream] SignedJWT :> PostNoContent -- :<|> "mappings" :> Get '[PlainText, JSON] SpmMappingListing -- :<|> "mappings" :> Capture SpmMapping :> GetNoContent -- :<|> "mappings" :> Capture SpmMapping :> DeleteNoContent spmApi :: Proxy SpmApi spmApi = Proxy