[initial import of happstack-jmacro. Not quite ready for general consuption yet.
jeremy@n-heptane.com**20110514233135
Ignore-this: 1ae1c2725af0abd249f1fc616ee98dd9
] adddir ./happstack-jmacro
adddir ./happstack-jmacro/Happstack
adddir ./happstack-jmacro/Happstack/Server
adddir ./happstack-jmacro/Happstack/Server/HSP
addfile ./happstack-jmacro/Happstack/Server/HSP/JMacro.hs
addfile ./happstack-jmacro/LICENSE
addfile ./happstack-jmacro/Setup.hs
adddir ./happstack-jmacro/examples
addfile ./happstack-jmacro/examples/Examples.lhs
addfile ./happstack-jmacro/happstack-jmacro.cabal
hunk ./happstack-jmacro/Happstack/Server/HSP/JMacro.hs 1
+{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-}
+{-# OPTIONS_GHC -F -pgmFtrhsx -fno-warn-orphans #-}
+module Happstack.Server.HSP.JMacro where
+
+import qualified Data.ByteString.Char8 as S
+import Data.ByteString.Lazy.UTF8 as LB (fromString)
+import Control.Monad.Trans (lift)
+import Control.Monad.State (MonadState(get,put))
+import Happstack.Server (ToMessage(..))
+import HSP
+import Language.Javascript.JMacro (JStat(..), jsToDoc, jsSaturate, renderJs)
+import Text.PrettyPrint.HughesPJ
+
+class IntegerSupply m where
+ nextInteger :: m Integer
+
+nextInteger' :: (MonadState Integer m) => m Integer
+nextInteger' =
+ do i <- get
+ put (succ i)
+ return i
+
+instance (XMLGenerator m, IntegerSupply m) => EmbedAsChild m JStat where
+ asChild jstat =
+ do i <- lift nextInteger
+ asChild $
+
+
+instance (EmbedAsAttr m Attribute, IntegerSupply m, IsName n) => EmbedAsAttr m (Attr n JStat) where
+ asAttr (n := jstat) =
+ do i <- lift nextInteger
+ asAttr $ MkAttr (toName n, pAttrVal $ renderStyle lineStyle $ jsToDoc $ jsSaturate (Just ('i' : show i)) jstat)
+ where
+ lineStyle = style { mode= OneLineMode }
+
+
+instance ToMessage JStat where
+ toContentType _ = S.pack "text/javascript; charset=UTF-8"
+ toMessage js = LB.fromString (show $ renderJs js)
hunk ./happstack-jmacro/LICENSE 1
+Copyright Jeremy Shaw 2011
+
+All rights reserved.
+
+Redistribution and use in source and binary forms, with or without
+modification, are permitted provided that the following conditions are met:
+
+ * Redistributions of source code must retain the above copyright
+ notice, this list of conditions and the following disclaimer.
+
+ * Redistributions in binary form must reproduce the above
+ copyright notice, this list of conditions and the following
+ disclaimer in the documentation and/or other materials provided
+ with the distribution.
+
+ * Neither the name of Jeremy Shaw nor the names of other
+ contributors may be used to endorse or promote products derived
+ from this software without specific prior written permission.
+
+THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+"AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR
+A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE COPYRIGHT
+OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL,
+SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT
+LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
+DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
+THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
+(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
+OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
hunk ./happstack-jmacro/Setup.hs 1
+#!/usr/bin/env runhaskell
+import Distribution.Simple
+main = defaultMain
hunk ./happstack-jmacro/examples/Examples.lhs 1
+JMacro is a library that makes it easy to generate javascript in
+Haskell. This is useful even if are just trying to add a little bit of
+javascript code to your HTML templates.
+
+The syntax used by JMacro is almost identical to javascript. So, you
+do not have to learn some special DSL to use it. In fact, JMacro can
+work with most javascript you find in the wild.
+
+
+ * syntax checking ensures that your javascript is syntactically valid
+ at compile time. That eliminates many comman javascript errors and
+ reduces development time
+
+ * hygienic names and scoping automatically and transparently ensures
+ that blocks of javascript code do not accidentally create variables
+ and functions with conflicting names.
+
+ * Antiquotation, Marshalling, and Shared scope make it easy to pass
+ Haskell values into the javascript code. It also makes it easy to
+ programmatically generate javascript code.
+
+The happstack-jmacro library makes it easy to use JMacro with Happstack and HSP.
+
+The following should get you started.
+
+The JMacro library does not require any external
+pre-processors. Instead it uses the magic of QuasiQuotation.
+http://haskell.org/haskellwiki/Quasiquotation
+
+So, we need to enabled the QuasiQuotes LANGUAGE extension:
+
+> {-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, TypeSynonymInstances, QuasiQuotes #-}
+
+In this example we are also using HSX, which does require a
+pre-processor. The following line will automatically run the
+pre-processor for us (and also suppress warnings about orphan
+instances):
+
+> {-# OPTIONS_GHC -F -pgmFtrhsx -fno-warn-orphans #-}
+
+Next we have a boatload if imports:
+
+> import Control.Applicative ((<$>), optional)
+> import Control.Monad (msum)
+> import Control.Monad.State (StateT, evalStateT)
+> import Control.Monad.Trans (liftIO)
+> import qualified Data.Map as Map
+> import Data.Maybe (fromMaybe)
+> import Happstack.Server
+> import Happstack.Server.HSP.HTML (defaultTemplate) -- ^ also imports ToMessage instance for XML type
+> import Happstack.Server.HSP.JMacro (IntegerSupply(..), nextInteger')
+> import HSP
+> import HSP.ServerPartT () -- ^ XMLGenerator instance for ServerPartT
+> import Language.Javascript.JMacro
+> import System.Random
+
+In order to ensure that each