summaryrefslogtreecommitdiffhomepage
path: root/HTTP.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2016-08-20 17:28:19 -0400
committerJoey Hess <joeyh@joeyh.name>2016-08-20 17:32:55 -0400
commit3633c44893bfbd50f25b84ac353012975388332c (patch)
treedf4ee463ce728fc58214b1e20ce23f48a4e71e60 /HTTP.hs
parente6097d694ca24b9546f9b7b25fc73768af9f017b (diff)
downloadkeysafe-3633c44893bfbd50f25b84ac353012975388332c.tar.gz
initial http api using servant
Diffstat (limited to 'HTTP.hs')
-rw-r--r--HTTP.hs77
1 files changed, 77 insertions, 0 deletions
diff --git a/HTTP.hs b/HTTP.hs
new file mode 100644
index 0000000..ac4eeab
--- /dev/null
+++ b/HTTP.hs
@@ -0,0 +1,77 @@
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE DeriveGeneric #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-# LANGUAGE TypeOperators #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+
+{- Copyright 2016 Joey Hess <id@joeyh.name>
+ -
+ - Licensed under the GNU AGPL version 3 or higher.
+ -}
+
+module HTTP where
+
+import Types
+import Types.Storage
+import Serialization ()
+import Raaz.Core.Encode
+import Servant.API
+import Data.Text
+import Data.Aeson.Types
+import GHC.Generics hiding (V1)
+import qualified Data.Text.Encoding as T
+import qualified Data.ByteString.Lazy as L
+
+-- | Keysafe's http API
+type HttpAPI =
+ "keysafe" :> "apiversion" :> Get '[JSON] APIVersion
+ :<|> "keysafe" :> V1 :> "motd" :> Get '[JSON] Motd
+ :<|> "keysafe" :> V1 :> "proofofwork" :> "requirement"
+ :> Get '[JSON] (Maybe ProofOfWorkRequirement)
+ :<|> "keysafe" :> V1 :> "objects" :> ObjectIdent :> POWParam
+ :> Get '[OctetStream] StorableObject
+ :<|> "keysafe" :> V1 :> "objects" :> ObjectIdent :> POWParam
+ :> ReqBody '[OctetStream] StorableObject
+ :> Put '[JSON] StoreResult
+ :<|> "keysafe" :> V1 :> "stats" :> "countobjects" :> POWParam
+ :> Get '[JSON] CountResult
+
+newtype APIVersion = APIVersion Int
+ deriving (Generic)
+
+type V1 = "v1"
+
+newtype Motd = Motd Text
+ deriving (Generic)
+
+data ProofOfWorkRequirement = ProofOfWorkRequirement
+ { leadingZeros :: Int
+ , argon2Iterations :: Int
+ }
+ deriving (Generic)
+
+newtype ProofOfWork = ProofOfWork Text
+
+type POWParam = QueryParam "proofofwork" ProofOfWork
+
+type ObjectIdent = Capture "ident" StorableObjectIdent
+
+instance ToJSON APIVersion
+instance FromJSON APIVersion
+instance ToJSON Motd
+instance FromJSON Motd
+instance ToJSON ProofOfWorkRequirement
+instance FromJSON ProofOfWorkRequirement
+
+instance FromHttpApiData ProofOfWork where
+ parseUrlPiece = Right . ProofOfWork
+
+instance FromHttpApiData StorableObjectIdent where
+ parseUrlPiece = Right . StorableObjectIdent . T.encodeUtf8
+
+instance MimeRender OctetStream StorableObject where
+ mimeRender _ = L.fromStrict . toByteString
+
+instance MimeUnrender OctetStream StorableObject where
+ mimeUnrender _ = maybe (Left "object encoding error") Right
+ . fromByteString . L.toStrict