{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeOperators    #-}
{-# LANGUAGE DataKinds        #-}

module Main where

import Html

import qualified Html.Attribute as A

import Data.Proxy
import Test.Hspec
import Test.QuickCheck

main :: IO ()
main = hspec spec

spec :: Spec
spec = parallel $ do

  describe "render" $ do

    it "is id on strings without escaping" $ do

      property $ \x ->
        renderString (Raw x)
        ===
        x

    it "handles single elements" $ do

      property $ \x ->
        renderString (div_ (Raw x))
        ===
        "<div>" ++ x ++ "</div>"

    it "handles nested elements" $ do

      property $ \x ->
        renderString (div_ (div_ (Raw x)))
        ===
        "<div><div>" ++ x ++ "</div></div>"

    it "handles parallel elements" $ do

      property $ \x y ->
        renderString (div_ (Raw x) # div_ (Raw y))
        ===
        "<div>" ++ x ++ "</div><div>" ++ y ++ "</div>"

    it "doesn't use closing tags for empty elements" $ do

      renderString area_
        `shouldBe`
        "<area>"

      renderString base_
       `shouldBe`
        "<base>"

      renderString br_
       `shouldBe`
        "<br>"

      renderString col_
       `shouldBe`
        "<col>"

      renderString embed_
       `shouldBe`
        "<embed>"

      renderString hr_
       `shouldBe`
        "<hr>"

      renderString iframe_
       `shouldBe`
        "<iframe>"

      renderString img_
       `shouldBe`
        "<img>"

      renderString link_
       `shouldBe`
        "<link>"

      renderString menuitem_
       `shouldBe`
        "<menuitem>"

      renderString meta_
       `shouldBe`
        "<meta>"

      renderString param_
       `shouldBe`
        "<param>"

      renderString source_
       `shouldBe`
        "<source>"

      renderString track_
       `shouldBe`
        "<track>"

      renderString wbr_
       `shouldBe`
        "<wbr>"

    it "handles trailing text" $ do

      property $ \x y ->
        renderString (td_ (Raw x) # (Raw y))
        ===
        "<td>" ++ x ++ "</td>" ++ y

    it "handles a single compile time text" $ do

      renderString (Proxy :: Proxy "a")
       `shouldBe`
        "a"

    it "handles trailing compile time text" $ do

      renderString (div_ "a" # (Proxy :: Proxy "b"))
       `shouldBe`
        "<div>a</div>b"

    it "handles nested compile time text" $ do

      renderString (div_ (Proxy :: Proxy "a"))
       `shouldBe`
        "<div>a</div>"

    it "handles an empty list" $ do

      renderString (tail [td_ "a"])
       `shouldBe`
        ""

    it "handles a list with a single element" $ do

      renderString [td_ "a"]
       `shouldBe`
        "<td>a</td>"

    it "handles tags in a list with parallel elements" $ do

      renderString [div_ "a" # i_ "b"]
       `shouldBe`
        "<div>a</div><i>b</i>"

    it "handles nested lists" $ do

      renderString (div_ [div_ [div_ (4 :: Int)]])
       `shouldBe`
        "<div><div><div>4</div></div></div>"

    it "handles utf8 correctly" $ do

      renderString (div_ "a ä € 𝄞")
       `shouldBe`
        "<div>a ä € 𝄞</div>"

      renderString (img_A (A.id_ "a ä € 𝄞"))
       `shouldBe`
        "<img id=\"a ä € 𝄞\">"

    it "handles Chars" $ do

      property $ \x ->
        renderString (div_ [x :: Char])
        ===
        renderString (div_ x)

    it "handles Ints" $ do

      property $ \x ->
        renderString (div_ (x :: Int))
        ===
        renderString (div_ (show x))

    it "handles complex compile time documents" $ do

      renderString (div_ () # i_ ())
       `shouldBe`
        "<div></div><i></i>"

      renderString (div_ () # "a")
       `shouldBe`
        "<div></div>a"

      renderString ("a" # i_ ())
       `shouldBe`
        "a<i></i>"

      renderString (div_ () # i_ (Proxy @"a"))
       `shouldBe`
        "<div></div><i>a</i>"

      renderString (div_ (Proxy @"a") # i_ ())
       `shouldBe`
        "<div>a</div><i></i>"

      renderString (Proxy @"1" # "2")
       `shouldBe`
        "12"

      renderString ("1" # Proxy @"2")
       `shouldBe`
        "12"

      renderString (div_ () # td_ (Proxy @"1" # "2" # div_ () # i_A (A.id_ (Proxy @"3")) "4"))
       `shouldBe`
        "<div></div><td>12<div></div><i id=\"3\">4</i></td>"