shrub/pkg/hs-urbit/lib/Vere/Http/Server.hs

129 lines
3.3 KiB
Haskell
Raw Normal View History

2019-05-16 03:00:10 +03:00
-- +http-server ----------------------------------------------------------------
module Vere.Http.Server where
import ClassyPrelude
2019-07-12 22:18:14 +03:00
import Noun
import Vere.Http
2019-05-16 03:00:10 +03:00
2019-07-12 22:24:44 +03:00
import Control.Concurrent (ThreadId, forkIO, killThread)
2019-05-31 05:53:00 +03:00
import qualified Network.HTTP.Types as H
import qualified Network.Wai as W
import qualified Network.Wai.Handler.Warp as W
2019-05-25 02:03:46 +03:00
import qualified Network.Wai.Handler.WarpTLS as W
2019-05-24 02:58:18 +03:00
2019-07-12 22:18:14 +03:00
-- Types -----------------------------------------------------------------------
2019-07-22 21:10:27 +03:00
type ServerId = Word
2019-05-16 03:00:10 +03:00
type ConnectionId = Word
2019-07-22 21:10:27 +03:00
type RequestId = Word
2019-05-16 03:00:10 +03:00
data Foo = A | B | C
2019-05-16 03:00:10 +03:00
data Eff = Eff ServerId ConnectionId RequestId ServerRequest
2019-06-28 00:28:58 +03:00
deriving (Eq, Ord, Show)
2019-05-16 03:00:10 +03:00
-- | An http server effect is configuration, or it sends an outbound response
data ServerRequest
= SetConfig Config
| Response Event
2019-06-28 00:28:58 +03:00
deriving (Eq, Ord, Show)
2019-05-16 03:00:10 +03:00
data Config = Config
{ secure :: Maybe (Key, Cert)
, proxy :: Bool
, log :: Bool
, redirect :: Bool
}
2019-06-28 00:28:58 +03:00
deriving (Eq, Ord, Show)
2019-05-16 03:00:10 +03:00
2019-05-16 03:04:21 +03:00
-- Note: We need to parse PEM-encoded RSA private keys and cert or cert chain
-- from Wain
2019-06-19 03:04:57 +03:00
type Key = PEM
type Cert = PEM
2019-07-22 21:10:27 +03:00
newtype Wain = Wain [Cord]
2019-06-28 00:28:58 +03:00
deriving newtype (Eq, Ord, Show, ToNoun, FromNoun)
2019-05-16 03:00:10 +03:00
newtype PEM = PEM Cord
2019-06-28 00:28:58 +03:00
deriving newtype (Eq, Ord, Show, ToNoun, FromNoun)
deriveNoun ''ServerRequest
deriveNoun ''Config
deriveNoun ''Eff
2019-05-16 03:04:21 +03:00
2019-05-16 03:00:10 +03:00
data ClientResponse
= Progress ResponseHeader Int (Maybe Int) (Maybe ByteString)
| Finished ResponseHeader (Maybe MimeData)
| Cancel
data MimeData = MimeData Text ByteString
2019-05-24 02:58:18 +03:00
2019-05-25 02:03:46 +03:00
data Ev
data State = State
{ thread :: MVar (Maybe (Config, ThreadId))
, sChan :: MVar Ev
}
2019-07-12 22:18:14 +03:00
--------------------------------------------------------------------------------
2019-05-25 02:03:46 +03:00
init :: IO State
init =
-- When we initialize things, we send an event into arvo
-- When we receive the set-config event, then we start stuff up
-- This works for now, but we need to actually do stuff per above.
State <$> newMVar Nothing
<*> newEmptyMVar
onSetConfig :: State -> Config -> IO ()
onSetConfig s c = do
v <- takeMVar (thread s)
maybe (pure ()) (killThread . snd) v
putMVar (thread s) Nothing
startServer s c
2019-07-22 21:10:27 +03:00
cordBytes :: Cord -> ByteString
cordBytes = encodeUtf8 . unCord
2019-05-25 02:03:46 +03:00
startServer :: State -> Config -> IO ()
startServer s c = do
tls <- case (secure c) of
Nothing -> error "no wai"
2019-06-19 03:04:57 +03:00
Just (PEM key, PEM cert) ->
2019-07-22 21:10:27 +03:00
pure (W.tlsSettingsMemory (cordBytes cert) (cordBytes key))
2019-05-25 02:03:46 +03:00
-- we need to do the dance where we do the socket checking dance. or shove a
-- socket into it.
2019-05-25 02:08:59 +03:00
tid <- forkIO $ W.runTLS tls W.defaultSettings (app s)
putMVar (thread s) (Just (c, tid))
2019-05-25 02:03:46 +03:00
app :: State -> W.Application
app s req respond = bracket_
(pure ())
(pure ())
(respond $ W.responseLBS H.status200 [] "Hello World")
cookMeth :: W.Request -> Maybe Method
2019-05-24 02:58:18 +03:00
cookMeth re =
2019-05-25 02:03:46 +03:00
case H.parseMethod (W.requestMethod re) of
2019-07-12 22:24:44 +03:00
Left _ -> Nothing
2019-05-24 02:58:18 +03:00
Right m -> Just m
2019-05-25 02:03:46 +03:00
readEvents :: W.Request -> IO Request
2019-07-22 21:10:27 +03:00
readEvents req = do
let Just meth = cookMeth req
url = Cord $ decodeUtf8 $ W.rawPathInfo req
headers = convertHeaders (W.requestHeaders req)
bodyLbs <- W.strictRequestBody req
2019-05-24 02:58:18 +03:00
let body = if length bodyLbs == 0 then Nothing
2019-07-22 21:10:27 +03:00
else Just $ Octs (toStrict bodyLbs)
2019-05-24 02:58:18 +03:00
-- TODO: Check if wai just deletes the 'host': header like h2o does?
2019-07-22 21:10:27 +03:00
pure (Request meth url headers body)