{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-missing-fields #-}
-- | A Shakespearean module for CoffeeScript, 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 @coffee@.
--
-- To use this module, @coffee@ must be installed on your system.
--
-- @#{...}@ is the Shakespearean standard for variable interpolation, but
-- CoffeeScript already uses that sequence for string interpolation. Therefore,
-- Shakespearean interpolation is introduced with @%{...}@.
--
-- If you interpolate variables,
-- the template is first wrapped with a function containing javascript variables representing shakespeare variables,
-- then compiled with @coffee@,
-- 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 @coffee@. 
--
-- Your code:
--
-- >   b = 1
-- >   console.log(#{a} + b)
--
-- Function wrapper added to your coffeescript code:
--
-- > ((shakespeare_var_a) =>
-- >   b = 1
-- >   console.log(shakespeare_var_a + b)
-- > )
--
-- This is then compiled down to javascript, and the variables are applied:
--
-- > ;(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. CoffeeScript: <http://coffeescript.org/>
module Text.Coffee
    ( -- * Functions
      -- ** Template-Reading Functions
      -- | These QuasiQuoter and Template Haskell methods return values of
      -- type @'JavascriptUrl' url@. See the Yesod book for details.
      coffee
    , coffeeFile
    , coffeeFileReload
    , coffeeFileDebug

#ifdef TEST_EXPORT
    , coffeeSettings
#endif
    ) where

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

coffeeSettings :: Q ShakespeareSettings
coffeeSettings :: Q ShakespeareSettings
coffeeSettings = do
  ShakespeareSettings
jsettings <- Q ShakespeareSettings
javascriptSettings
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ShakespeareSettings
jsettings { varChar :: Char
varChar = Char
'%'
  , preConversion :: Maybe PreConvert
preConversion = forall a. a -> Maybe a
Just PreConvert {
      preConvert :: PreConversion
preConvert = String -> [String] -> PreConversion
ReadProcess String
"coffee" [String
"-spb"]
    , preEscapeIgnoreBalanced :: String
preEscapeIgnoreBalanced = String
"'\"`"     -- don't insert backtacks for variable already inside strings or backticks.
    , preEscapeIgnoreLine :: String
preEscapeIgnoreLine = String
"#"            -- ignore commented lines
    , wrapInsertion :: Maybe WrapInsertion
wrapInsertion = forall a. a -> Maybe a
Just WrapInsertion { 
        wrapInsertionIndent :: Maybe String
wrapInsertionIndent = forall a. a -> Maybe a
Just String
"  "
      , wrapInsertionStartBegin :: String
wrapInsertionStartBegin = String
"("
      , wrapInsertionSeparator :: String
wrapInsertionSeparator = String
", "
      , wrapInsertionStartClose :: String
wrapInsertionStartClose = String
") =>"
      , wrapInsertionEnd :: String
wrapInsertionEnd = String
""
      , wrapInsertionAddParens :: Bool
wrapInsertionAddParens = Bool
False
      }
    }
  }

-- | Read inline, quasiquoted CoffeeScript.
coffee :: QuasiQuoter
coffee :: QuasiQuoter
coffee = QuasiQuoter { quoteExp :: String -> Q Exp
quoteExp = \String
s -> do
    ShakespeareSettings
rs <- Q ShakespeareSettings
coffeeSettings
    QuasiQuoter -> String -> Q Exp
quoteExp (ShakespeareSettings -> QuasiQuoter
shakespeare ShakespeareSettings
rs) String
s
    }

-- | Read in a CoffeeScript template file. This function reads the file once, at
-- compile time.
coffeeFile :: FilePath -> Q Exp
coffeeFile :: String -> Q Exp
coffeeFile String
fp = do
    ShakespeareSettings
rs <- Q ShakespeareSettings
coffeeSettings
    ShakespeareSettings -> String -> Q Exp
shakespeareFile ShakespeareSettings
rs String
fp

-- | Read in a CoffeeScript template file. This impure function uses
-- unsafePerformIO to re-read the file on every call, allowing for rapid
-- iteration.
coffeeFileReload :: FilePath -> Q Exp
coffeeFileReload :: String -> Q Exp
coffeeFileReload String
fp = do
    ShakespeareSettings
rs <- Q ShakespeareSettings
coffeeSettings
    ShakespeareSettings -> String -> Q Exp
shakespeareFileReload ShakespeareSettings
rs String
fp

-- | Deprecated synonym for 'coffeeFileReload'
coffeeFileDebug :: FilePath -> Q Exp
coffeeFileDebug :: String -> Q Exp
coffeeFileDebug = String -> Q Exp
coffeeFileReload
{-# DEPRECATED coffeeFileDebug "Please use coffeeFileReload instead." #-}