#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
    (
    -- * Absolute URIs
      uri
#if __GLASGOW_HASKELL__ >= 708
    , staticURI
#endif
    , staticURI'
    -- * Relative URIs
    , 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

-- $setup
-- >>> :set -XTemplateHaskell
-- >>> :set -XQuasiQuotes

----------------------------------------------------------------------------
-- Absolute URIs
----------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 708
-- | 'staticURI' parses a specified string at compile time
--   and return an expression representing the URI when it's a valid URI.
--   Otherwise, it emits an error.
--
-- >>> $$(staticURI "http://www.google.com/")
-- http://www.google.com/
--
-- >>> $$(staticURI "http://www.google.com/##")
-- <BLANKLINE>
-- <interactive>...
-- ... Invalid URI: http://www.google.com/##
-- ...
staticURI :: String      -- ^ String representation of a URI
          -> SpliceQ URI -- ^ URI
staticURI :: String -> SpliceQ URI
staticURI (String -> Maybe URI
parseURI -> Just URI
u) = [|| 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'' parses a specified string at compile time.
--
-- The typed template haskell 'staticURI' is available only with GHC-7.8+.
staticURI' :: String    -- ^ String representation of a URI
           -> ExpQ      -- ^ URI
#if __GLASGOW_HASKELL__ >= 708
staticURI' :: String -> ExpQ
staticURI' = Code Q URI -> ExpQ
forall a (m :: * -> *). Quote m => Code m a -> m Exp
unTypeCode (Code Q URI -> ExpQ) -> (String -> Code Q URI) -> String -> ExpQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpliceQ URI -> Code Q URI
forall (q :: * -> *) a c. IsCode q a c => c -> Code q a
toCode (SpliceQ URI -> Code Q URI)
-> (String -> SpliceQ URI) -> String -> Code Q 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' is a quasi quoter for 'staticURI'.
--
-- >>> [uri|http://www.google.com/|]
-- http://www.google.com/
--
-- >>> [uri|http://www.google.com/##|]
-- <BLANKLINE>
-- <interactive>...
-- ... Invalid URI: http://www.google.com/##
-- ...
uri :: QuasiQuoter
uri :: QuasiQuoter
uri = QuasiQuoter :: (String -> ExpQ)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
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
}

----------------------------------------------------------------------------
-- Relative URIs
----------------------------------------------------------------------------

#if __GLASGOW_HASKELL__ >= 708
-- | 'staticRelativeReference' parses a specified string at compile time and
--   return an expression representing the URI when it's a valid relative
--   reference. Otherwise, it emits an error.
--
-- >>> $$(staticRelativeReference "/foo?bar=baz#quux")
-- /foo?bar=baz#quux
--
-- >>> $$(staticRelativeReference "http://www.google.com/")
-- <BLANKLINE>
-- <interactive>...
-- ... Invalid relative reference: http://www.google.com/
-- ...
staticRelativeReference :: String      -- ^ String representation of a reference
                        -> SpliceQ URI -- ^ Refererence
staticRelativeReference :: String -> SpliceQ URI
staticRelativeReference (String -> Maybe URI
parseRelativeReference -> Just URI
ref) = [|| 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'' parses a specified string at compile time and
--   return an expression representing the URI when it's a valid relative
--   reference. Otherwise, it emits an error.
--
-- The typed template haskell 'staticRelativeReference' is available only with GHC-7.8+.
staticRelativeReference' :: String -- ^ String representation of a reference
                         -> ExpQ   -- ^ Refererence
#if __GLASGOW_HASKELL__ >= 708
staticRelativeReference' :: String -> ExpQ
staticRelativeReference' = Code Q URI -> ExpQ
forall a (m :: * -> *). Quote m => Code m a -> m Exp
unTypeCode (Code Q URI -> ExpQ) -> (String -> Code Q URI) -> String -> ExpQ
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SpliceQ URI -> Code Q URI
forall (q :: * -> *) a c. IsCode q a c => c -> Code q a
toCode (SpliceQ URI -> Code Q URI)
-> (String -> SpliceQ URI) -> String -> Code Q 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' is a quasi quoter for 'staticRelativeReference'.
--
-- >>> [relativeReference|/foo?bar=baz#quux|]
-- /foo?bar=baz#quux
--
-- >>> [relativeReference|http://www.google.com/|]
-- <BLANKLINE>
-- <interactive>...
-- ... Invalid relative reference: http://www.google.com/
-- ...
relativeReference :: QuasiQuoter
relativeReference :: QuasiQuoter
relativeReference = QuasiQuoter :: (String -> ExpQ)
-> (String -> Q Pat)
-> (String -> Q Type)
-> (String -> Q [Dec])
-> QuasiQuoter
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
}