{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveLift #-}
{-# LANGUAGE ViewPatterns #-}
module Servant.Client.Core.BaseUrl (
BaseUrl (..),
Scheme (..),
showBaseUrl,
parseBaseUrl,
InvalidBaseUrlException (..),
) where
import Control.DeepSeq
(NFData (..))
import Control.Monad.Catch
(Exception, MonadThrow, throwM)
import Data.Aeson
(FromJSON (..), FromJSONKey (..), ToJSON (..), ToJSONKey (..))
import Data.Aeson.Types
(FromJSONKeyFunction (..), contramapToJSONKeyFunction,
withText)
import Data.Data
(Data)
import Data.List
import qualified Data.Text as T
import GHC.Generics
import Language.Haskell.TH.Syntax
(Lift)
import Network.URI hiding
(path)
import Safe
import Text.Read
data Scheme =
Http
| Https
deriving (Show, Eq, Ord, Generic, Lift, Data)
data BaseUrl = BaseUrl
{ baseUrlScheme :: Scheme
, baseUrlHost :: String
, baseUrlPort :: Int
, baseUrlPath :: String
} deriving (Show, Ord, Generic, Lift, Data)
instance NFData BaseUrl where
rnf (BaseUrl a b c d) = a `seq` rnf b `seq` rnf c `seq` rnf d
instance Eq BaseUrl where
BaseUrl a b c path == BaseUrl a' b' c' path'
= a == a' && b == b' && c == c' && s path == s path'
where s ('/':x) = x
s x = x
instance ToJSON BaseUrl where
toJSON = toJSON . showBaseUrl
toEncoding = toEncoding . showBaseUrl
instance FromJSON BaseUrl where
parseJSON = withText "BaseUrl" $ \t -> case parseBaseUrl (T.unpack t) of
Just u -> return u
Nothing -> fail $ "Invalid base url: " ++ T.unpack t
instance ToJSONKey BaseUrl where
toJSONKey = contramapToJSONKeyFunction showBaseUrl toJSONKey
instance FromJSONKey BaseUrl where
fromJSONKey = FromJSONKeyTextParser $ \t -> case parseBaseUrl (T.unpack t) of
Just u -> return u
Nothing -> fail $ "Invalid base url: " ++ T.unpack t
showBaseUrl :: BaseUrl -> String
showBaseUrl (BaseUrl urlscheme host port path) =
schemeString ++ "//" ++ host ++ (portString </> path)
where
a </> b = if "/" `isPrefixOf` b || null b then a ++ b else a ++ '/':b
schemeString = case urlscheme of
Http -> "http:"
Https -> "https:"
portString = case (urlscheme, port) of
(Http, 80) -> ""
(Https, 443) -> ""
_ -> ":" ++ show port
newtype InvalidBaseUrlException = InvalidBaseUrlException String deriving (Show)
instance Exception InvalidBaseUrlException
parseBaseUrl :: MonadThrow m => String -> m BaseUrl
parseBaseUrl s = case parseURI (removeTrailingSlash s) of
Just (URI "http:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) path "" "") ->
return (BaseUrl Http host port path)
Just (URI "http:" (Just (URIAuth "" host "")) path "" "") ->
return (BaseUrl Http host 80 path)
Just (URI "https:" (Just (URIAuth "" host (':' : (readMaybe -> Just port)))) path "" "") ->
return (BaseUrl Https host port path)
Just (URI "https:" (Just (URIAuth "" host "")) path "" "") ->
return (BaseUrl Https host 443 path)
_ -> if "://" `isInfixOf` s
then throwM (InvalidBaseUrlException $ "Invalid base URL: " ++ s)
else parseBaseUrl ("http://" ++ s)
where
removeTrailingSlash str = case lastMay str of
Just '/' -> init str
_ -> str