diff options
author | Gregor Kleen <gkleen@yggdrasil.li> | 2022-05-26 13:58:07 +0200 |
---|---|---|
committer | Gregor Kleen <gkleen@yggdrasil.li> | 2022-05-26 13:58:07 +0200 |
commit | fc6cf6169868e60c189e4b243330c3717ff159f3 (patch) | |
tree | 3f6dea9c1420e23756257b5abea27ec9ed92d58a /overlays/spm/lib/Spm | |
parent | 84f2affd66a0ff3947b91a30308cb8e6a8ff7594 (diff) | |
download | nixos-fc6cf6169868e60c189e4b243330c3717ff159f3.tar nixos-fc6cf6169868e60c189e4b243330c3717ff159f3.tar.gz nixos-fc6cf6169868e60c189e4b243330c3717ff159f3.tar.bz2 nixos-fc6cf6169868e60c189e4b243330c3717ff159f3.tar.xz nixos-fc6cf6169868e60c189e4b243330c3717ff159f3.zip |
...
Diffstat (limited to 'overlays/spm/lib/Spm')
-rw-r--r-- | overlays/spm/lib/Spm/Api.hs | 91 |
1 files changed, 91 insertions, 0 deletions
diff --git a/overlays/spm/lib/Spm/Api.hs b/overlays/spm/lib/Spm/Api.hs new file mode 100644 index 00000000..14acfac4 --- /dev/null +++ b/overlays/spm/lib/Spm/Api.hs | |||
@@ -0,0 +1,91 @@ | |||
1 | {-# LANGUAGE TemplateHaskell, OverloadedStrings #-} | ||
2 | |||
3 | module Spm.Api | ||
4 | ( SpmStyle(..), _SpmWords, _SpmConsonants | ||
5 | , SpmMailbox | ||
6 | , SpmApi, spmApi | ||
7 | ) where | ||
8 | |||
9 | import Prelude | ||
10 | |||
11 | import Servant.API | ||
12 | |||
13 | import Data.Proxy (Proxy(..)) | ||
14 | |||
15 | import Data.Text (Text) | ||
16 | |||
17 | import GHC.Generics (Generic) | ||
18 | import Type.Reflection (Typeable) | ||
19 | |||
20 | import Control.Lens.TH | ||
21 | |||
22 | import Data.CaseInsensitive (CI) | ||
23 | import qualified Data.CaseInsensitive as CI | ||
24 | import Data.CaseInsensitive.Instances () | ||
25 | |||
26 | import Crypto.JOSE.JWK (JWKSet) | ||
27 | import Crypto.JWT (SignedJWT) | ||
28 | import Crypto.JWT.Instances () | ||
29 | |||
30 | import Data.UUID (UUID) | ||
31 | import Data.UUID.Instances () | ||
32 | |||
33 | -- import Data.Aeson (ToJSON, FromJSON) | ||
34 | |||
35 | |||
36 | data SpmStyle = SpmWords | SpmConsonants | ||
37 | deriving (Eq, Ord, Read, Show, Bounded, Enum) | ||
38 | makePrisms ''SpmStyle | ||
39 | |||
40 | instance ToHttpApiData SpmStyle where | ||
41 | toUrlPiece = \case | ||
42 | SpmWords -> "words" | ||
43 | SpmConsonants -> "consonants" | ||
44 | instance FromHttpApiData SpmStyle where | ||
45 | parseUrlPiece t@(CI.mk -> t') | ||
46 | | t' == "words" = Right SpmWords | ||
47 | | t' == "consonants" = Right SpmConsonants | ||
48 | | otherwise = Left $ "Expected one of ‘words’ or ‘consonants’ but got ‘" <> t <> "’" | ||
49 | |||
50 | |||
51 | newtype SpmMailbox = SpmMailbox { unSpmMailbox :: CI Text } | ||
52 | deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
53 | deriving newtype (MimeRender JSON, MimeRender PlainText) | ||
54 | makeWrapped ''SpmMailbox | ||
55 | -- newtype SpmLocal = SpmLocal | ||
56 | -- { unSpmLocal :: CI Text | ||
57 | -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
58 | -- deriving newtype (ToJSON, FromJSON) | ||
59 | -- makeWrapped ''SpmLocal | ||
60 | -- newtype SpmExtension = SpmExtension | ||
61 | -- { unSpmExtension :: CI Text | ||
62 | -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
63 | -- deriving newtype (ToJSON, FromJSON) | ||
64 | -- makeWrapped ''SpmExtension | ||
65 | |||
66 | -- newtype SpmMappingListing = SpmMappingListing { unSpmMappingListing :: Set SpmMapping } | ||
67 | -- deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
68 | -- instance ToJSON SpmMappingList where | ||
69 | -- toJSON SpmMappingListing{..} = object [ "mappings" .= unSpmMappingListing ] | ||
70 | |||
71 | -- data SpmMapping = SpmMapping | ||
72 | -- { spmMappingLocal :: Maybe SpmLocal | ||
73 | -- , spmMappingExtension :: Maybe SpmExtension | ||
74 | -- } deriving stock (Eq, Ord, Read, Show, Generic, Typeable) | ||
75 | -- instance ToJSON SpmMapping where | ||
76 | -- toJSON SpmMapping{..} = object | ||
77 | -- [ "local" .= spmMappingLocal | ||
78 | -- , "extension" .= spmMappingExtension | ||
79 | -- ] | ||
80 | |||
81 | type SpmApi = "whoami" :> Get '[PlainText, JSON] SpmMailbox | ||
82 | :<|> "jwks.json" :> Get '[JSON] JWKSet | ||
83 | :<|> "instance-id" :> Get '[PlainText, JSON, OctetStream] UUID | ||
84 | :<|> "spm" :> "generate" :> QueryParam "style" SpmStyle :> Get '[PlainText, JSON, OctetStream] SignedJWT | ||
85 | :<|> "spm" :> "claim" :> ReqBody '[PlainText, JSON, OctetStream] SignedJWT :> PostNoContent | ||
86 | -- :<|> "mappings" :> Get '[PlainText, JSON] SpmMappingListing | ||
87 | -- :<|> "mappings" :> Capture SpmMapping :> GetNoContent | ||
88 | -- :<|> "mappings" :> Capture SpmMapping :> DeleteNoContent | ||
89 | |||
90 | spmApi :: Proxy SpmApi | ||
91 | spmApi = Proxy | ||