gemcap/src/Network/GemServ.hs

229 lines
6.5 KiB
Haskell
Raw Normal View History

2021-10-22 12:49:03 -04:00
{-|
Module : Network.GemServ
Description : Gemini Server Stuff
Copyright : (C) Jonathan Lamothe
License : AGPL-3.0-or-later
Maintainer : jonathan@jlamothe.net
Stability : experimental
Portability : POSIX
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public
License along with this program. If not, see
<https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE
LambdaCase,
OverloadedStrings,
ScopedTypeVariables,
RecordWildCards #-}
2021-10-24 12:47:37 -04:00
module Network.GemServ (
-- * Running a Gemini Server
runGemServer,
-- * Encoding/Decoding Functions
encodeGemURL,
2021-10-24 22:04:56 -04:00
decodeGemURL,
2021-10-24 12:47:37 -04:00
escapeString,
unescapeString
) where
import Control.Concurrent (forkIO)
import Control.Exception (IOException, try)
2021-11-10 15:04:00 -05:00
import Control.Exception.Base (bracket, finally)
import Control.Monad (void)
2021-10-24 12:47:37 -04:00
import qualified Data.ByteString as BS
import Data.ByteString.Builder (charUtf8, stringUtf8, toLazyByteString)
2021-10-24 12:47:37 -04:00
import qualified Data.ByteString.Lazy as BSL
import Data.Char (chr, ord, toLower)
2021-11-10 15:04:00 -05:00
import qualified Data.Connection as C
import Data.IORef (IORef, newIORef, readIORef, writeIORef)
2021-10-24 12:47:37 -04:00
import Data.List (find, intercalate)
import Data.Maybe (fromJust)
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8')
import Data.TLSSetting (makeServerParams)
import Data.X509 (Certificate, CertificateChain (..), getSigned, signedObject)
2021-11-10 15:04:00 -05:00
import qualified Network.Socket as S
import Network.TLS (ServerParams, onClientCertificate, serverHooks)
import System.IO.Streams.TCP (bindAndListen)
2021-11-10 15:04:00 -05:00
import System.IO.Streams.TLS (TLSConnection, accept)
import Network.GemServ.Internal
import Network.GemServ.Types
-- | Builds and runs a Gemini server
runGemServer
:: GemServSettings
-- ^ The server settings
-> GemHandler
-- ^ The handler
-> IO a
runGemServer settings handler = bracket
( bindAndListen
(servConnections settings)
(fromIntegral $ servPort settings)
)
2021-11-10 15:04:00 -05:00
S.close
( \sock -> do
params <- makeServerParams
(servCert settings)
(servCertChain settings)
(servKey settings)
listenLoop sock params handler
)
-- | Encodes a 'GemURL' into a 'String'
encodeGemURL :: GemURL -> String
encodeGemURL url =
"gemini://" ++ authority ++ "/" ++ path ++ query
where
authority = gemHost url ++ case gemPort url of
Just port -> ':' : show port
Nothing -> ""
path = intercalate "/" $ map escapeString $ gemPath url
query = case gemQuery url of
Nothing -> ""
Just q -> '?' : escapeString q
2021-10-22 12:49:03 -04:00
2021-10-24 22:04:56 -04:00
-- | Decodes a 'GemURL' from a 'String' (if possible)
decodeGemURL :: String -> Maybe GemURL
decodeGemURL str = do
let txt = T.pack str
noProt <- case T.splitOn "://" txt of
[prot, rest] -> if T.toLower prot == "gemini"
then Just rest
else Nothing
_ -> Nothing
noFrag <- case T.splitOn "#" noProt of
[x, _] -> Just x
[x] -> Just x
_ -> Nothing
(noQuery, query) <- case T.splitOn "?" noFrag of
[nq, q] -> Just (nq, Just q)
[nq] -> Just (nq, Nothing)
_ -> Nothing
gemQuery <- case query of
Just q -> Just <$> unescapeString (T.unpack q)
Nothing -> Just Nothing
(auth, path) <- case T.splitOn "/" noQuery of
[a] -> Just (a, [])
[a, ""] -> Just (a, [])
a:ps -> Just (a, ps)
_ -> Nothing
gemPath <- mapM (unescapeString . T.unpack) path
(host, gemPort) <- case T.splitOn ":" auth of
[h, p] -> case reads $ T.unpack p of
[(n, "")] -> Just (h, Just n)
_ -> Nothing
[h] -> Just (h, Nothing)
_ -> Nothing
let gemHost = T.unpack host
Just GemURL {..}
2021-10-22 16:40:44 -04:00
-- | add required escape sequences to a string
escapeString :: String -> String
escapeString = concatMap
( \n -> let ch = chr $ fromIntegral n in
if ch `elem` unescaped
then [ch]
else '%' : toHex n
) . BSL.unpack . toLazyByteString . stringUtf8
2021-10-22 16:40:44 -04:00
where
unescaped = ['0'..'9'] ++ ['A'..'Z'] ++ ['a'..'z'] ++ "~-_."
toHex =
( \n -> let
high = n `div` 16
low = n `mod` 16
in [hexDigits !! high, hexDigits !! low]
) . fromIntegral
2021-10-22 16:40:44 -04:00
2021-10-24 12:47:37 -04:00
-- | decode an escaped string back to its original value
unescapeString :: String -> Maybe String
unescapeString str = case decodeUtf8' $ BS.pack $ toBytes str of
Right t -> Just $ T.unpack t
_ -> Nothing
where
toBytes = \case
"" -> []
'%':h:l:sub -> let
h' = toLower h
l' = toLower l
in if h' `elem` hexDigits && l' `elem` hexDigits
then toByte h' l' : toBytes sub
else fromIntegral (ord '%') : toBytes (h : l : sub)
ch:sub ->
BSL.unpack (toLazyByteString $ charUtf8 ch) ++ toBytes sub
toByte h l = toNum h * 16 + toNum l
toNum ch = fst $ fromJust $
find (\x -> snd x == ch) $ zip [0..] hexDigits
2021-11-10 15:04:00 -05:00
listenLoop :: S.Socket -> ServerParams -> GemHandler -> IO a
listenLoop sock params handler = do
certRef <- newIORef Nothing
let params' = adjustServerParams certRef params
try (accept params' sock) >>= \case
Left (_ :: IOException) -> return ()
2021-11-10 15:04:00 -05:00
Right conn -> void $ forkIO $ finally
(readIORef certRef >>= runConnection conn handler)
(C.close conn)
listenLoop sock params handler
adjustServerParams
:: IORef (Maybe Certificate)
-> ServerParams
-> ServerParams
adjustServerParams certRef params = let
hooks = serverHooks params
certHook = onClientCertificate hooks
2021-11-12 19:52:09 -05:00
certHook' chain = do
case chain of
CertificateChain [] -> return ()
CertificateChain (se:_) -> do
let cert = signedObject $ getSigned se
writeIORef certRef (Just cert)
certHook chain
hooks' = hooks { onClientCertificate = certHook' }
in params { serverHooks = hooks' }
2021-11-10 15:04:00 -05:00
runConnection
:: TLSConnection
-> GemHandler
-> Maybe Certificate
-> IO ()
runConnection conn handler mCert =
( readURL conn >>= \case
Nothing -> return $ newGemResponse
{ respStatus = 59
, respMeta = "bad request"
}
Just url -> handler (newGemRequest url) { reqCert = mCert }
) >>= sendResponse conn
2021-10-22 16:40:44 -04:00
hexDigits :: String
hexDigits = ['0'..'9'] ++ ['a'..'f']
2021-10-22 12:49:03 -04:00
--jl