implemented decodeGemURL
This commit is contained in:
@@ -24,10 +24,11 @@ License along with this program. If not, see
|
||||
|
||||
-}
|
||||
|
||||
{-# LANGUAGE LambdaCase #-}
|
||||
{-# LANGUAGE LambdaCase, OverloadedStrings, RecordWildCards #-}
|
||||
|
||||
module Network.GemServ (
|
||||
encodeGemURL,
|
||||
decodeGemURL,
|
||||
escapeString,
|
||||
unescapeString
|
||||
) where
|
||||
@@ -56,6 +57,49 @@ encodeGemURL url =
|
||||
Nothing -> ""
|
||||
Just q -> '?' : escapeString q
|
||||
|
||||
-- | 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 {..}
|
||||
|
||||
-- | add required escape sequences to a string
|
||||
escapeString :: String -> String
|
||||
escapeString = concatMap
|
||||
|
||||
Reference in New Issue
Block a user