{-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE TemplateHaskell #-} module HamletTest (specs) where import Test.HUnit hiding (Test) import Test.Hspec.Core import Test.Hspec.HUnit import Prelude hiding (reverse) import Text.Hamlet import Data.List (intercalate) import qualified Data.Text.Lazy as T import qualified Data.List import qualified Data.List as L import qualified Data.Map as Map import Data.Text (Text, pack, unpack) import Data.Monoid (mappend,mconcat) import qualified Data.Set as Set import qualified Text.Blaze.Html.Renderer.Text import Text.Blaze.Html (toHtml) import Text.Blaze.Internal (preEscapedString) import Text.Blaze specs = describe "hamlet" [ it "empty" caseEmpty , it "static" caseStatic , it "tag" caseTag , it "var" caseVar , it "var chain " caseVarChain , it "url" caseUrl , it "url chain " caseUrlChain , it "embed" caseEmbed , it "embed chain " caseEmbedChain , it "if" caseIf , it "if chain " caseIfChain , it "else" caseElse , it "else chain " caseElseChain , it "elseif" caseElseIf , it "elseif chain " caseElseIfChain , it "list" caseList , it "list chain" caseListChain , it "with" caseWith , it "with multi" caseWithMulti , it "with chain" caseWithChain , it "with comma string" caseWithCommaString , it "with multi scope" caseWithMultiBindingScope , it "script not empty" caseScriptNotEmpty , it "meta empty" caseMetaEmpty , it "input empty" caseInputEmpty , it "multiple classes" caseMultiClass , it "attrib order" caseAttribOrder , it "nothing" caseNothing , it "nothing chain " caseNothingChain , it "just" caseJust , it "just chain " caseJustChain , it "constructor" caseConstructor , it "url + params" caseUrlParams , it "escape" caseEscape , it "empty statement list" caseEmptyStatementList , it "attribute conditionals" caseAttribCond , it "non-ascii" caseNonAscii , it "maybe function" caseMaybeFunction , it "trailing dollar sign" caseTrailingDollarSign , it "non leading percent sign" caseNonLeadingPercent , it "quoted attributes" caseQuotedAttribs , it "spaced derefs" caseSpacedDerefs , it "attrib vars" caseAttribVars , it "strings and html" caseStringsAndHtml , it "nesting" caseNesting , it "trailing space" caseTrailingSpace , it "currency symbols" caseCurrency , it "external" caseExternal , it "parens" caseParens , it "hamlet literals" caseHamletLiterals , it "hamlet' and xhamlet'" caseHamlet' , it "hamlet tuple" caseTuple , it "comments" $ do -- FIXME reconsider Hamlet comment syntax? helper "" [hamlet|$# this is a comment $# another comment $#a third one|] , it "ignores a blank line" $ do helper "

foo

\n" [hamlet|

foo |] , it "angle bracket syntax" $ helper "

HELLO

" [hamlet| $newline never HELLO |] , it "hamlet module names" $ let foo = "foo" in helper "oof oof 3.14 -5" [hamlet| $newline never #{Data.List.reverse foo} # #{L.reverse foo} # #{show 3.14} #{show -5}|] , it "single dollar at and caret" $ do helper "$@^" [hamlet|\$@^|] helper "#{@{^{" [hamlet|#\{@\{^\{|] , it "dollar operator" $ do let val = (1, (2, 3)) helper "2" [hamlet|#{ show $ fst $ snd val }|] helper "2" [hamlet|#{ show $ fst $ snd $ val}|] , it "in a row" $ do helper "1" [hamlet|#{ show $ const 1 2 }|] , it "embedded slash" $ do helper "///" [hamlet|///|] {- compile-time error , it "tag with slash" $ do helper "" [hamlet|

Text

|] -} , it "string literals" $ do helper "string" [hamlet|#{"string"}|] helper "string" [hamlet|#{id "string"}|] helper "gnirts" [hamlet|#{L.reverse $ id "string"}|] helper "str"ing" [hamlet|#{"str\"ing"}|] helper "str<ing" [hamlet|#{"str1

2 not ignored

" [hamlet| $newline never

1

2 not ignored |] , it "nested maybes" $ do let muser = Just "User" :: Maybe String mprof = Nothing :: Maybe Int m3 = Nothing :: Maybe String helper "justnothing" [hamlet| $maybe user <- muser $maybe profile <- mprof First two are Just $maybe desc <- m3 \ and left us a description:

#{desc} $nothing and has left us no description. $nothing justnothing $nothing

No such Person exists. |] , it "conditional class" $ do helper "

\n" [hamlet|

|] helper "

\n" [hamlet|

|] helper "

\n" [hamlet|

|] , it "forall on Foldable" $ do let set = Set.fromList [1..5 :: Int] helper "12345" [hamlet| $forall x <- set #{x} |] , it "non-poly HTML" $ do helperHtml "

HELLO WORLD

\n" [shamlet|

HELLO WORLD |] helperHtml "

HELLO WORLD

\n" $(shamletFile "test/hamlets/nonpolyhtml.hamlet") , it "non-poly Hamlet" $ do let embed = [hamlet|

EMBEDDED|] helper "

url

\n

EMBEDDED

\n" [hamlet|

@{Home} ^{embed} |] helper "

url

\n" $(hamletFile "test/hamlets/nonpolyhamlet.hamlet") , it "non-poly IHamlet" $ do let embed = [ihamlet|

EMBEDDED|] ihelper "

Adios

\n

EMBEDDED

\n" [ihamlet|

_{Goodbye} ^{embed} |] ihelper "

Hola

\n" $(ihamletFile "test/hamlets/nonpolyihamlet.hamlet") , it "pattern-match tuples: forall" $ do let people = [("Michael", 26), ("Miriam", 25)] helper "
Michael
26
Miriam
25
" [hamlet| $newline never
$forall (name, age) <- people
#{name}
#{show age} |] , it "pattern-match tuples: maybe" $ do let people = Just ("Michael", 26) helper "
Michael
26
" [hamlet| $newline never
$maybe (name, age) <- people
#{name}
#{show age} |] , it "pattern-match tuples: with" $ do let people = ("Michael", 26) helper "
Michael
26
" [hamlet| $newline never
$with (name, age) <- people
#{name}
#{show age} |] , it "list syntax for interpolation" $ do helper "
  • 1
  • 2
  • 3
" [hamlet| $newline never
    $forall num <- [1, 2, 3]
  • #{show num} |] , it "infix operators" $ helper "5" [hamlet|#{show $ (4 + 5) - (2 + 2)}|] , it "infix operators with parens" $ helper "5" [hamlet|#{show ((+) 1 1 + 3)}|] , it "doctypes" $ helper "\n\n" [hamlet| $newline never $doctype 5 $doctype strict |] , it "case on Maybe" $ let nothing = Nothing justTrue = Just True in helper "



    " [hamlet| $newline never $case nothing $of Just val $of Nothing
    $case justTrue $of Just val $if val
    $of Nothing $case (Just $ not False) $of Nothing $of Just val $if val
    $case Nothing $of Just val $of _
    |] , it "case on Url" $ let url1 = Home url2 = Sub SubUrl in helper "
    \n
    \n" [hamlet| $newline always $case url1 $of Home
    $of _ $case url2 $of Sub sub $case sub $of SubUrl
    $of Home |] , it "pattern-match constructors: forall" $ do let people = [Pair "Michael" 26, Pair "Miriam" 25] helper "
    Michael
    26
    Miriam
    25
    " [hamlet| $newline text
    $forall Pair name age <- people
    #{name}
    #{show age} |] , it "pattern-match constructors: maybe" $ do let people = Just $ Pair "Michael" 26 helper "
    Michael
    26
    " [hamlet| $newline text
    $maybe Pair name age <- people
    #{name}
    #{show age} |] , it "pattern-match constructors: with" $ do let people = Pair "Michael" 26 helper "
    Michael
    26
    " [hamlet| $newline text
    $with Pair name age <- people
    #{name}
    #{show age} |] , it "multiline tags" $ helper "content\n" [hamlet| content |] , let attrs = [("bar", "baz"), ("bin", "<>\"&")] in it "*{...} attributes" $ helper "content\n" [hamlet| content |] , it "blank attr values" $ helper "\n" [hamlet||] , it "greater than in attr" $ helper "\n" [hamlet|