{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.URI.QQ
( uri
, scheme
, host
, username
, password
, pathPiece
, queryKey
, queryValue
, fragment )
where
import Control.Exception (SomeException, Exception (..))
import Data.Text (Text)
import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax (Lift (..))
import Text.URI.Parser.Text
import Text.URI.Types
import qualified Data.Text as T
uri :: QuasiQuoter
uri = liftToQQ mkURI
scheme :: QuasiQuoter
scheme = liftToQQ mkScheme
host :: QuasiQuoter
host = liftToQQ mkHost
username :: QuasiQuoter
username = liftToQQ mkUsername
password :: QuasiQuoter
password = liftToQQ mkPassword
pathPiece :: QuasiQuoter
pathPiece = liftToQQ mkPathPiece
queryKey :: QuasiQuoter
queryKey = liftToQQ mkQueryKey
queryValue :: QuasiQuoter
queryValue = liftToQQ mkQueryValue
fragment :: QuasiQuoter
fragment = liftToQQ mkFragment
liftToQQ :: Lift a => (Text -> Either SomeException a) -> QuasiQuoter
liftToQQ f = QuasiQuoter
{ quoteExp = \str ->
case f (T.pack str) of
Left err -> fail (displayException err)
Right x -> lift x
, quotePat = error "This usage is not supported"
, quoteType = error "This usage is not supported"
, quoteDec = error "This usage is not supported" }