{-# LANGUAGE QuasiQuotes #-} module HSXSpec ( hsxSpec ) where import Control.Monad import qualified Data.HashMap.Strict as HM import Control.Monad.Reader import Data.IORef import Test.Hspec import Web.Framework.Plzwrk hsxSpec = describe "HSXParser" $ do it "Parses simple hsx" $ do let dom = [hsx|

Hello world!

|] -- we use () for an empty state _elt_tag (dom ()) `shouldBe` "p" _tn_text (head (_elt_children (dom ())) ()) `shouldBe` "Hello world!" it "Parses hsx with an event listener" $ do let dom = [hsx|

return $ x + 41)}#>Hello

|] _elt_tag (dom 3) `shouldBe` "h1" _elt_tag (((_elt_children (dom 5)) !! 0) 3) `shouldBe` "a" let attrs = (_elt_attrs (((_elt_children (dom 1)) !! 0) 1)) let clickAttr = (filter (\(x, _) -> x == "click") attrs) !! 0 let mf (PwFunctionAttribute f) = f let cf = mf ((snd clickAttr) 0) res <- cf () 1 res `shouldBe` 42 it "Parses hsx with sub-hsx" $ do let mylink = [hsx| return $ x + 41)}#>Hello|] let dom = [hsx|

#e{mylink}# #t{"hello world"}#

|] _elt_tag (dom 3) `shouldBe` "h1" _elt_tag (head (_elt_children (dom 5)) 3) `shouldBe` "a" _tn_text ((_elt_children (dom 5) !! 1) 3) `shouldBe` "hello world" 1 `shouldBe` 1 it "Parses hsx with a list of elements" $ do let mylink = [hsx| return $ x + 41)}#>Hello|] let dom = [hsx|

#el{take 10 $ repeat mylink}# #t{"hello world"}#

|] _elt_tag (dom 3) `shouldBe` "h1" _elt_tag (head (_elt_children (dom 5)) 3) `shouldBe` "a" _elt_tag ((_elt_children (dom 5) !! 6) 3) `shouldBe` "a" _tn_text ((_elt_children (dom 5) !! 10) 3) `shouldBe` "hello world" it "Parses hsx mixing text and not text" $ do let mylink = [hsx| return $ x + 41)}#>Hello|] let dom = [hsx|

Hello world

|] _elt_tag (dom 3) `shouldBe` "h1" _elt_tag (head (_elt_children (dom 5)) 3) `shouldBe` "div" _elt_tag ((_elt_children (head (_elt_children (dom 5)) 3) !! 1) 5) `shouldBe` "span" it "Parses hsx'" $ do let mylink = [hsx| return $ x + 41)}#>Hello|] let dom = (\st -> [hsx'|

#e{mylink}#

|]) _elt_tag (dom 3) `shouldBe` "h1" _elt_tag (head (_elt_children (dom 5)) 3) `shouldBe` "a"