#if __GLASGOW_HASKELL__ < 800
{-# LANGUAGE RecordWildCards, TemplateHaskell, ViewPatterns #-}
#else
{-# LANGUAGE RecordWildCards, TemplateHaskellQuotes, ViewPatterns #-}
#endif
#if MIN_VERSION_template_haskell(2,12,0)
{-# LANGUAGE Safe #-}
#elif __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE Trustworthy #-}
#endif
module Network.URI.Static
(
uri
#if __GLASGOW_HASKELL__ >= 708
, staticURI
#endif
, staticURI'
, relativeReference
#if __GLASGOW_HASKELL__ >= 708
, staticRelativeReference
#endif
, staticRelativeReference'
) where
import Language.Haskell.TH.Lib (ExpQ)
import Language.Haskell.TH.Quote (QuasiQuoter(..))
import Network.URI (URI(..), parseURI, parseRelativeReference)
#if __GLASGOW_HASKELL__ >= 708
import Language.Haskell.TH.Syntax.Compat (SpliceQ, unTypeCode, toCode)
#endif
#if __GLASGOW_HASKELL__ >= 708
staticURI :: String
-> SpliceQ URI
staticURI :: String -> SpliceQ URI
staticURI (String -> Maybe URI
parseURI -> Just URI
u) = [|| URI
u ||]
staticURI String
s = String -> SpliceQ URI
forall a. HasCallStack => String -> a
error (String -> SpliceQ URI) -> String -> SpliceQ URI
forall a b. (a -> b) -> a -> b
$ String
"Invalid URI: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s
#endif
staticURI' :: String
-> ExpQ
#if __GLASGOW_HASKELL__ >= 708
staticURI' :: String -> ExpQ
staticURI' = SpliceQ URI -> ExpQ
forall a (m :: * -> *). Quote m => Code m a -> m Exp
unTypeCode (SpliceQ URI -> ExpQ) -> (String -> SpliceQ URI) -> String -> ExpQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpliceQ URI -> SpliceQ URI
forall (q :: * -> *) a c. IsCode q a c => c -> Code q a
toCode (SpliceQ URI -> SpliceQ URI)
-> (String -> SpliceQ URI) -> String -> SpliceQ URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SpliceQ URI
staticURI
#else
staticURI' (parseURI -> Just u) = [| u |]
staticURI' s = fail $ "Invalid URI: " ++ s
#endif
uri :: QuasiQuoter
uri :: QuasiQuoter
uri = QuasiQuoter {
quoteExp :: String -> ExpQ
quoteExp = String -> ExpQ
staticURI',
quotePat :: String -> Q Pat
quotePat = String -> Q Pat
forall a. HasCallStack => a
undefined,
quoteType :: String -> Q Type
quoteType = String -> Q Type
forall a. HasCallStack => a
undefined,
quoteDec :: String -> Q [Dec]
quoteDec = String -> Q [Dec]
forall a. HasCallStack => a
undefined
}
#if __GLASGOW_HASKELL__ >= 708
staticRelativeReference :: String
-> SpliceQ URI
staticRelativeReference :: String -> SpliceQ URI
staticRelativeReference (String -> Maybe URI
parseRelativeReference -> Just URI
ref) = [|| URI
ref ||]
staticRelativeReference String
ref = String -> SpliceQ URI
forall a. HasCallStack => String -> a
error (String -> SpliceQ URI) -> String -> SpliceQ URI
forall a b. (a -> b) -> a -> b
$ String
"Invalid relative reference: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ref
#endif
staticRelativeReference' :: String
-> ExpQ
#if __GLASGOW_HASKELL__ >= 708
staticRelativeReference' :: String -> ExpQ
staticRelativeReference' = SpliceQ URI -> ExpQ
forall a (m :: * -> *). Quote m => Code m a -> m Exp
unTypeCode (SpliceQ URI -> ExpQ) -> (String -> SpliceQ URI) -> String -> ExpQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpliceQ URI -> SpliceQ URI
forall (q :: * -> *) a c. IsCode q a c => c -> Code q a
toCode (SpliceQ URI -> SpliceQ URI)
-> (String -> SpliceQ URI) -> String -> SpliceQ URI
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SpliceQ URI
staticRelativeReference
#else
staticRelativeReference' (parseRelativeReference -> Just ref) = [| ref |]
staticRelativeReference' ref = fail $ "Invalid relative reference: " ++ ref
#endif
relativeReference :: QuasiQuoter
relativeReference :: QuasiQuoter
relativeReference = QuasiQuoter {
quoteExp :: String -> ExpQ
quoteExp = String -> ExpQ
staticRelativeReference',
quotePat :: String -> Q Pat
quotePat = String -> Q Pat
forall a. HasCallStack => a
undefined,
quoteType :: String -> Q Type
quoteType = String -> Q Type
forall a. HasCallStack => a
undefined,
quoteDec :: String -> Q [Dec]
quoteDec = String -> Q [Dec]
forall a. HasCallStack => a
undefined
}