{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TupleSections #-}
module Text.URI.Types
(
URI (..)
, makeAbsolute
, isPathAbsolute
, Authority (..)
, UserInfo (..)
, QueryParam (..)
, ParseException (..)
, RText
, RTextLabel (..)
, mkScheme
, mkHost
, mkUsername
, mkPassword
, mkPathPiece
, mkQueryKey
, mkQueryValue
, mkFragment
, unRText
, RTextException (..)
, pHost )
where
import Control.DeepSeq
import Control.Monad
import Control.Monad.Catch (Exception (..), MonadThrow (..))
import Data.Char
import Data.Data (Data)
import Data.List (intercalate)
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe (fromMaybe, isJust, fromJust)
import Data.Proxy
import Data.Text (Text)
import Data.Typeable (Typeable, cast)
import Data.Void
import Data.Word (Word8, Word16)
import GHC.Generics
import Numeric (showInt, showHex)
import Test.QuickCheck
import Text.Megaparsec
import Text.URI.Parser.Text.Utils (pHost)
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T
import qualified Language.Haskell.TH.Syntax as TH
data URI = URI
{ uriScheme :: Maybe (RText 'Scheme)
, uriAuthority :: Either Bool Authority
, uriPath :: Maybe (Bool, NonEmpty (RText 'PathPiece))
, uriQuery :: [QueryParam]
, uriFragment :: Maybe (RText 'Fragment)
} deriving (Show, Eq, Ord, Data, Typeable, Generic)
instance Arbitrary URI where
arbitrary = URI
<$> arbitrary
<*> arbitrary
<*> (do mpieces <- NE.nonEmpty <$> arbitrary
trailingSlash <- arbitrary
return ((trailingSlash,) <$> mpieces))
<*> arbitrary
<*> arbitrary
instance NFData URI
instance TH.Lift URI where
lift = liftData
makeAbsolute :: RText 'Scheme -> URI -> URI
makeAbsolute scheme URI {..} = URI
{ uriScheme = pure (fromMaybe scheme uriScheme)
, .. }
isPathAbsolute :: URI -> Bool
isPathAbsolute = either id (const True) . uriAuthority
data Authority = Authority
{ authUserInfo :: Maybe UserInfo
, authHost :: RText 'Host
, authPort :: Maybe Word
} deriving (Show, Eq, Ord, Data, Typeable, Generic)
instance Arbitrary Authority where
arbitrary = Authority
<$> arbitrary
<*> arbitrary
<*> arbitrary
instance NFData Authority
instance TH.Lift Authority where
lift = liftData
data UserInfo = UserInfo
{ uiUsername :: RText 'Username
, uiPassword :: Maybe (RText 'Password)
} deriving (Show, Eq, Ord, Data, Typeable, Generic)
instance Arbitrary UserInfo where
arbitrary = UserInfo
<$> arbitrary
<*> arbitrary
instance NFData UserInfo
instance TH.Lift UserInfo where
lift = liftData
data QueryParam
= QueryFlag (RText 'QueryKey)
| QueryParam (RText 'QueryKey) (RText 'QueryValue)
deriving (Show, Eq, Ord, Data, Typeable, Generic)
instance Arbitrary QueryParam where
arbitrary = oneof
[ QueryFlag <$> arbitrary
, QueryParam <$> arbitrary <*> arbitrary ]
instance NFData QueryParam
instance TH.Lift QueryParam where
lift = liftData
newtype ParseException = ParseException (ParseErrorBundle Text Void)
deriving (Show, Eq, Data, Typeable, Generic)
instance Exception ParseException where
displayException (ParseException b) = errorBundlePretty b
instance NFData ParseException
newtype RText (l :: RTextLabel) = RText Text
deriving (Eq, Ord, Data, Typeable, Generic)
instance Show (RText l) where
show (RText txt) = show txt
instance NFData (RText l) where
instance Typeable l => TH.Lift (RText l) where
lift = liftData
data RTextLabel
= Scheme
| Host
| Username
| Password
| PathPiece
| QueryKey
| QueryValue
| Fragment
deriving (Show, Eq, Ord, Data, Typeable, Generic)
class RLabel (l :: RTextLabel) where
rcheck :: Proxy l -> Text -> Bool
rnormalize :: Proxy l -> Text -> Text
rlabel :: Proxy l -> RTextLabel
mkRText :: forall m l. (MonadThrow m, RLabel l) => Text -> m (RText l)
mkRText txt =
if rcheck lproxy txt
then return . RText $ rnormalize lproxy txt
else throwM (RTextException (rlabel lproxy) txt)
where
lproxy = Proxy :: Proxy l
mkScheme :: MonadThrow m => Text -> m (RText 'Scheme)
mkScheme = mkRText
instance RLabel 'Scheme where
rcheck Proxy = ifMatches $ do
void . satisfy $ \x ->
isAscii x && isAlpha x
skipMany . satisfy $ \x ->
isAscii x && isAlphaNum x || x == '+' || x == '-' || x == '.'
rnormalize Proxy = T.toLower
rlabel Proxy = Scheme
instance Arbitrary (RText 'Scheme) where
arbitrary = arbScheme
mkHost :: MonadThrow m => Text -> m (RText 'Host)
mkHost = mkRText
instance RLabel 'Host where
rcheck Proxy = (ifMatches . void . pHost) False
rnormalize Proxy = T.toLower
rlabel Proxy = Host
instance Arbitrary (RText 'Host) where
arbitrary = arbHost
mkUsername :: MonadThrow m => Text -> m (RText 'Username)
mkUsername = mkRText
instance RLabel 'Username where
rcheck Proxy = not . T.null
rnormalize Proxy = id
rlabel Proxy = Username
instance Arbitrary (RText 'Username) where
arbitrary = arbText' mkUsername
mkPassword :: MonadThrow m => Text -> m (RText 'Password)
mkPassword = mkRText
instance RLabel 'Password where
rcheck Proxy = const True
rnormalize Proxy = id
rlabel Proxy = Password
instance Arbitrary (RText 'Password) where
arbitrary = arbText mkPassword
mkPathPiece :: MonadThrow m => Text -> m (RText 'PathPiece)
mkPathPiece = mkRText
instance RLabel 'PathPiece where
rcheck Proxy = not . T.null
rnormalize Proxy = id
rlabel Proxy = PathPiece
instance Arbitrary (RText 'PathPiece) where
arbitrary = arbText' mkPathPiece
mkQueryKey :: MonadThrow m => Text -> m (RText 'QueryKey)
mkQueryKey = mkRText
instance RLabel 'QueryKey where
rcheck Proxy = not . T.null
rnormalize Proxy = id
rlabel Proxy = QueryKey
instance Arbitrary (RText 'QueryKey) where
arbitrary = arbText' mkQueryKey
mkQueryValue :: MonadThrow m => Text -> m (RText 'QueryValue)
mkQueryValue = mkRText
instance RLabel 'QueryValue where
rcheck Proxy = const True
rnormalize Proxy = id
rlabel Proxy = QueryValue
instance Arbitrary (RText 'QueryValue) where
arbitrary = arbText mkQueryValue
mkFragment :: MonadThrow m => Text -> m (RText 'Fragment)
mkFragment = mkRText
instance RLabel 'Fragment where
rcheck Proxy = const True
rnormalize Proxy = id
rlabel Proxy = Fragment
instance Arbitrary (RText 'Fragment) where
arbitrary = arbText mkFragment
unRText :: RText l -> Text
unRText (RText txt) = txt
data RTextException = RTextException RTextLabel Text
deriving (Show, Eq, Ord, Data, Typeable, Generic)
instance Exception RTextException where
displayException (RTextException lbl txt) = "The value \"" ++
T.unpack txt ++ "\" could not be lifted into a " ++ show lbl
ifMatches :: Parsec Void Text () -> Text -> Bool
ifMatches p = isJust . parseMaybe p
arbScheme :: Gen (RText 'Scheme)
arbScheme = do
let g = oneof [choose ('a','z'), choose ('A','Z')]
x <- g
xs <- listOf $
frequency [(3, g), (1, choose ('0','9'))]
return . fromJust . mkScheme . T.pack $ x:xs
arbHost :: Gen (RText 'Host)
arbHost = fromJust . mkHost . T.pack <$> frequency
[ (1, ipLiteral)
, (2, ipv4Address)
, (4, regName)
, (1, return "")
]
where
ipLiteral = do
xs <- oneof [ipv6Address, ipvFuture]
return ("[" ++ xs ++ "]")
ipv6Address =
intercalate ":" . fmap (`showHex` "") <$>
vectorOf 8 (arbitrary :: Gen Word16)
ipv4Address =
intercalate "." . fmap (`showInt` "") <$>
vectorOf 4 (arbitrary :: Gen Word8)
ipvFuture = do
v <- oneof [choose ('0', '9'), choose ('a', 'f')]
xs <- listOf1 $ frequency
[ (3, choose ('a', 'z'))
, (3, choose ('A', 'Z'))
, (2, choose ('0', '9'))
, (2, elements "-._~!$&'()*+,;=:") ]
return ("v" ++ [v] ++ "." ++ xs)
domainLabel = do
let g = arbitrary `suchThat` isAlphaNum
x <- g
xs <- listOf $
frequency [(3, g), (1, return '-')]
x' <- g
return ([x] ++ xs ++ [x'])
regName = intercalate "." <$> resize 5 (listOf1 domainLabel)
arbText :: (Text -> Maybe (RText l)) -> Gen (RText l)
arbText f = fromJust . f . T.pack <$> listOf arbitrary
arbText' :: (Text -> Maybe (RText l)) -> Gen (RText l)
arbText' f = fromJust . f . T.pack <$> listOf1 arbitrary
liftData :: Data a => a -> TH.Q TH.Exp
liftData = TH.dataToExpQ (fmap liftText . cast)
liftText :: Text -> TH.Q TH.Exp
liftText t = TH.AppE (TH.VarE 'T.pack) <$> TH.lift (T.unpack t)