module Servant.Common.BaseUrl where
import Data.List
import GHC.Generics
import Network.URI
import Safe
import Text.Read
data Scheme =
Http
| Https
deriving (Show, Eq, Ord, Generic)
data BaseUrl = BaseUrl
{ baseUrlScheme :: Scheme
, baseUrlHost :: String
, baseUrlPort :: Int
} deriving (Show, Eq, Ord, Generic)
showBaseUrl :: BaseUrl -> String
showBaseUrl (BaseUrl urlscheme host port) =
schemeString ++ "//" ++ host ++ portString
where
schemeString = case urlscheme of
Http -> "http:"
Https -> "https:"
portString = case (urlscheme, port) of
(Http, 80) -> ""
(Https, 443) -> ""
_ -> ":" ++ show port
parseBaseUrl :: String -> Either String BaseUrl
parseBaseUrl s = case parseURI (removeTrailingSlash s) of
Just (URI "http:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) "" "" "") ->
Right (BaseUrl Http host port)
Just (URI "http:" (Just (URIAuth "" host "")) "" "" "") ->
Right (BaseUrl Http host 80)
Just (URI "https:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) "" "" "") ->
Right (BaseUrl Https host port)
Just (URI "https:" (Just (URIAuth "" host "")) "" "" "") ->
Right (BaseUrl Https host 443)
_ -> if "://" `isInfixOf` s
then Left ("invalid base url: " ++ s)
else parseBaseUrl ("http://" ++ s)
where
removeTrailingSlash str = case lastMay str of
Just '/' -> init str
_ -> str