{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
-- | A Shakespearean module for Roy, introducing type-safe,
-- compile-time variable and url interpolation. It is exactly the same as
-- "Text.Julius", except that the template is first compiled to Javascript with
-- the system tool @roy@.
--
-- To use this module, @roy@ must be installed on your system.
--
-- If you interpolate variables,
-- the template is first wrapped with a function containing javascript variables representing shakespeare variables,
-- then compiled with @roy@,
-- and then the value of the variables are applied to the function.
-- This means that in production the template can be compiled
-- once at compile time and there will be no dependency in your production
-- system on @roy@. 
--
-- Your code:
--
-- > let b = 1
-- > console.log(#{a} + b)
--
-- Final Result:
--
-- > ;(function(shakespeare_var_a){
-- >   var b = 1;
-- >   console.log(shakespeare_var_a + b);
-- > })(#{a});
--
-- Further reading:
--
-- 1. Shakespearean templates: <https://www.yesodweb.com/book/shakespearean-templates>
--
-- 2. Roy: <http://roy.brianmckenna.org/>
module Text.Roy
    ( -- * Functions
      -- ** Template-Reading Functions
      -- | These QuasiQuoter and Template Haskell methods return values of
      -- type @'JavascriptUrl' url@. See the Yesod book for details.
      roy
    , royFile
    , royFileReload

#ifdef TEST_EXPORT
    , roySettings
#endif
    ) where

import Language.Haskell.TH.Quote (QuasiQuoter (..))
import Language.Haskell.TH.Syntax
import Text.Shakespeare
import Text.Julius

-- | The Roy language compiles down to Javascript.
-- We do this compilation once at compile time to avoid needing to do it during the request.
-- We call this a preConversion because other shakespeare modules like Lucius use Haskell to compile during the request instead rather than a system call.
roySettings :: Q ShakespeareSettings
roySettings :: Q ShakespeareSettings
roySettings = do
  ShakespeareSettings
jsettings <- Q ShakespeareSettings
javascriptSettings
  ShakespeareSettings -> Q ShakespeareSettings
forall (m :: * -> *) a. Monad m => a -> m a
return (ShakespeareSettings -> Q ShakespeareSettings)
-> ShakespeareSettings -> Q ShakespeareSettings
forall a b. (a -> b) -> a -> b
$ ShakespeareSettings
jsettings { varChar :: Char
varChar = Char
'#'
  , preConversion :: Maybe PreConvert
preConversion = PreConvert -> Maybe PreConvert
forall a. a -> Maybe a
Just PreConvert :: PreConversion
-> [Char] -> [Char] -> Maybe WrapInsertion -> PreConvert
PreConvert {
      preConvert :: PreConversion
preConvert = [Char] -> [[Char]] -> PreConversion
ReadProcess [Char]
"roy" [[Char]
"--stdio", [Char]
"--browser"]
    , preEscapeIgnoreBalanced :: [Char]
preEscapeIgnoreBalanced = [Char]
"'\""
    , preEscapeIgnoreLine :: [Char]
preEscapeIgnoreLine = [Char]
"//"
    , wrapInsertion :: Maybe WrapInsertion
wrapInsertion = WrapInsertion -> Maybe WrapInsertion
forall a. a -> Maybe a
Just WrapInsertion :: Maybe [Char]
-> [Char] -> [Char] -> [Char] -> [Char] -> Bool -> WrapInsertion
WrapInsertion {
        wrapInsertionIndent :: Maybe [Char]
wrapInsertionIndent = [Char] -> Maybe [Char]
forall a. a -> Maybe a
Just [Char]
"  "
      , wrapInsertionStartBegin :: [Char]
wrapInsertionStartBegin = [Char]
"(\\"
      , wrapInsertionSeparator :: [Char]
wrapInsertionSeparator = [Char]
" "
      , wrapInsertionStartClose :: [Char]
wrapInsertionStartClose = [Char]
" ->\n"
      , wrapInsertionEnd :: [Char]
wrapInsertionEnd = [Char]
")"
      , wrapInsertionAddParens :: Bool
wrapInsertionAddParens = Bool
True
      }
    }
  }

-- | Read inline, quasiquoted Roy.
roy :: QuasiQuoter
roy :: QuasiQuoter
roy = QuasiQuoter :: ([Char] -> Q Exp)
-> ([Char] -> Q Pat)
-> ([Char] -> Q Type)
-> ([Char] -> Q [Dec])
-> QuasiQuoter
QuasiQuoter { quoteExp :: [Char] -> Q Exp
quoteExp = \[Char]
s -> do
    ShakespeareSettings
rs <- Q ShakespeareSettings
roySettings
    QuasiQuoter -> [Char] -> Q Exp
quoteExp (ShakespeareSettings -> QuasiQuoter
shakespeare ShakespeareSettings
rs) [Char]
s
    }

-- | Read in a Roy template file. This function reads the file once, at
-- compile time.
royFile :: FilePath -> Q Exp
royFile :: [Char] -> Q Exp
royFile [Char]
fp = do
    ShakespeareSettings
rs <- Q ShakespeareSettings
roySettings
    ShakespeareSettings -> [Char] -> Q Exp
shakespeareFile ShakespeareSettings
rs [Char]
fp

-- | Read in a Roy template file. This impure function uses
-- unsafePerformIO to re-read the file on every call, allowing for rapid
-- iteration.
royFileReload :: FilePath -> Q Exp
royFileReload :: [Char] -> Q Exp
royFileReload [Char]
fp = do
    ShakespeareSettings
rs <- Q ShakespeareSettings
roySettings
    ShakespeareSettings -> [Char] -> Q Exp
shakespeareFileReload ShakespeareSettings
rs [Char]
fp