From cdf4445a877428f5969f712a95830af38029b9a0 Mon Sep 17 00:00:00 2001 From: Alec Theriault Date: Mon, 7 Oct 2019 20:45:40 -0400 Subject: Add Hyperlinker test cases for TH-related stuff Hopefully this will guard against regressions around quasiquotes, TH quotes, and TH splices. --- hypsrc-test/ref/src/CallingQuotes.html | 104 ++++ hypsrc-test/ref/src/Quasiquoter.html | 415 +++++++++++++ .../ref/src/TemplateHaskellQuasiquotes.html | 659 +++++++++++++++++++++ hypsrc-test/ref/src/TemplateHaskellSplices.html | 135 +++++ hypsrc-test/ref/src/UsingQuasiquotes.html | 104 ++++ hypsrc-test/src/Quasiquoter.hs | 16 + hypsrc-test/src/TemplateHaskellQuasiquotes.hs | 39 ++ hypsrc-test/src/TemplateHaskellSplices.hs | 8 + hypsrc-test/src/UsingQuasiquotes.hs | 9 + 9 files changed, 1489 insertions(+) create mode 100644 hypsrc-test/ref/src/CallingQuotes.html create mode 100644 hypsrc-test/ref/src/Quasiquoter.html create mode 100644 hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html create mode 100644 hypsrc-test/ref/src/TemplateHaskellSplices.html create mode 100644 hypsrc-test/ref/src/UsingQuasiquotes.html create mode 100644 hypsrc-test/src/Quasiquoter.hs create mode 100644 hypsrc-test/src/TemplateHaskellQuasiquotes.hs create mode 100644 hypsrc-test/src/TemplateHaskellSplices.hs create mode 100644 hypsrc-test/src/UsingQuasiquotes.hs (limited to 'hypsrc-test') diff --git a/hypsrc-test/ref/src/CallingQuotes.html b/hypsrc-test/ref/src/CallingQuotes.html new file mode 100644 index 00000000..9b2e3209 --- /dev/null +++ b/hypsrc-test/ref/src/CallingQuotes.html @@ -0,0 +1,104 @@ +
{-# LANGUAGE QuasiQuotes #-}
+module CallingQuotes where
+
+import Quasiquoter
+
+baz :: [Char]
+baz  = [string| foo bar |] [Char] -> [Char] -> [Char]
+forall a. [a] -> [a] -> [a]
+++ [string| some
+  mulitline
+  quasiquote
+|]
+
\ No newline at end of file diff --git a/hypsrc-test/ref/src/Quasiquoter.html b/hypsrc-test/ref/src/Quasiquoter.html new file mode 100644 index 00000000..ab631e8c --- /dev/null +++ b/hypsrc-test/ref/src/Quasiquoter.html @@ -0,0 +1,415 @@ +
module Quasiquoter ( string ) where
+
+import Language.Haskell.TH.Quote
+import Language.Haskell.TH.Syntax
+
+-- | Quoter for constructing multiline string literals
+string :: QuasiQuoter
+string :: QuasiQuoter
+string = QuasiQuoter :: (String -> Q Exp)
+-> (String -> Q Pat)
+-> (String -> Q Type)
+-> (String -> Q [Dec])
+-> QuasiQuoter
+QuasiQuoter
+  { quoteExp :: String -> Q Exp
+quoteExp = Exp -> Q Exp
+forall (f :: * -> *) a. Applicative f => a -> f a
+pure (Exp -> Q Exp) -> (String -> Exp) -> String -> Q Exp
+forall b c a. (b -> c) -> (a -> b) -> a -> c
+. Lit -> Exp
+LitE (Lit -> Exp) -> (String -> Lit) -> String -> Exp
+forall b c a. (b -> c) -> (a -> b) -> a -> c
+. String -> Lit
+StringL
+  , quotePat :: String -> Q Pat
+quotePat = String -> Q Pat
+forall a. String -> Q a
+invalidDomain
+  , quoteType :: String -> Q Type
+quoteType = String -> Q Type
+forall a. String -> Q a
+invalidDomain
+  , quoteDec :: String -> Q [Dec]
+quoteDec = String -> Q [Dec]
+forall a. String -> Q a
+invalidDomain
+  }
+  where
+    invalidDomain :: String -> Q a
+    invalidDomain :: String -> Q a
+invalidDomain _ = String -> Q a
+forall (m :: * -> *) a. MonadFail m => String -> m a
+fail "stringQuoter: only valid in expression context"
+
\ No newline at end of file diff --git a/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html b/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html new file mode 100644 index 00000000..6552b676 --- /dev/null +++ b/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html @@ -0,0 +1,659 @@ +
{-# LANGUAGE TemplateHaskell #-}
+
+module TemplateHaskellQuasiquotes where
+
+import Language.Haskell.TH
+
+aDecl :: DecsQ
+aDecl :: DecsQ
+aDecl = [d|
+    bar :: $aType -> [ (Int, String) ]
+    bar $aPattern = $anExpression
+  |]
+
+aPattern :: PatQ
+aPattern :: PatQ
+aPattern = [p|
+    [ aCrazyLongVariableName
+    , _unused
+    , (y, z)
+    , ( $aNumberPattern, "hello")
+    ]
+  |]
+
+aNumberPattern :: PatQ
+aNumberPattern :: PatQ
+aNumberPattern = [p|
+    w @ v @ 4.5
+  |]
+
+anExpression, anExpression2 :: ExpQ
+anExpression :: ExpQ
+anExpression = [e|
+    [ (1 + $anExpression2, "world") ]
+  |]
+anExpression2 :: ExpQ
+anExpression2 = [| (1 + round pi) |]
+
+aType :: TypeQ
+aType :: TypeQ
+aType = [t|
+    [ (Double, String) ]
+  |]
+
+
+
+
\ No newline at end of file diff --git a/hypsrc-test/ref/src/TemplateHaskellSplices.html b/hypsrc-test/ref/src/TemplateHaskellSplices.html new file mode 100644 index 00000000..85288453 --- /dev/null +++ b/hypsrc-test/ref/src/TemplateHaskellSplices.html @@ -0,0 +1,135 @@ +
{-# LANGUAGE TemplateHaskell #-}
+module TemplateHaskellSplices where
+
+import TemplateHaskellQuasiquotes
+
+$([(Double, String)] -> [(Int, String)]
+aDecl)
+
+foo :: Integer
+foo = Integer -> Integer
+forall a. a -> a
+id $(Double
+Double -> Integer
+Integer -> Integer -> Integer
+forall a. Floating a => a
+forall a. Num a => a -> a -> a
+forall a b. (RealFrac a, Integral b) => a -> b
++ :: forall a. Num a => a -> a -> a
+round :: forall a b. (RealFrac a, Integral b) => a -> b
+pi :: forall a. Floating a => a
+anExpression2)
+
\ No newline at end of file diff --git a/hypsrc-test/ref/src/UsingQuasiquotes.html b/hypsrc-test/ref/src/UsingQuasiquotes.html new file mode 100644 index 00000000..a5c791c4 --- /dev/null +++ b/hypsrc-test/ref/src/UsingQuasiquotes.html @@ -0,0 +1,104 @@ +
{-# LANGUAGE QuasiQuotes #-}
+module UsingQuasiquotes where
+
+import Quasiquoter
+
+baz :: [Char]
+baz  = [string| foo bar |] [Char] -> [Char] -> [Char]
+forall a. [a] -> [a] -> [a]
+++ [string| some
+  mulitline
+  quasiquote
+|]
+
\ No newline at end of file diff --git a/hypsrc-test/src/Quasiquoter.hs b/hypsrc-test/src/Quasiquoter.hs new file mode 100644 index 00000000..d0a46c33 --- /dev/null +++ b/hypsrc-test/src/Quasiquoter.hs @@ -0,0 +1,16 @@ +module Quasiquoter ( string ) where + +import Language.Haskell.TH.Quote +import Language.Haskell.TH.Syntax + +-- | Quoter for constructing multiline string literals +string :: QuasiQuoter +string = QuasiQuoter + { quoteExp = pure . LitE . StringL + , quotePat = invalidDomain + , quoteType = invalidDomain + , quoteDec = invalidDomain + } + where + invalidDomain :: String -> Q a + invalidDomain _ = fail "stringQuoter: only valid in expression context" diff --git a/hypsrc-test/src/TemplateHaskellQuasiquotes.hs b/hypsrc-test/src/TemplateHaskellQuasiquotes.hs new file mode 100644 index 00000000..a1661895 --- /dev/null +++ b/hypsrc-test/src/TemplateHaskellQuasiquotes.hs @@ -0,0 +1,39 @@ +{-# LANGUAGE TemplateHaskell #-} + +module TemplateHaskellQuasiquotes where + +import Language.Haskell.TH + +aDecl :: DecsQ +aDecl = [d| + bar :: $aType -> [ (Int, String) ] + bar $aPattern = $anExpression + |] + +aPattern :: PatQ +aPattern = [p| + [ aCrazyLongVariableName + , _unused + , (y, z) + , ( $aNumberPattern, "hello") + ] + |] + +aNumberPattern :: PatQ +aNumberPattern = [p| + w @ v @ 4.5 + |] + +anExpression, anExpression2 :: ExpQ +anExpression = [e| + [ (1 + $anExpression2, "world") ] + |] +anExpression2 = [| (1 + round pi) |] + +aType :: TypeQ +aType = [t| + [ (Double, String) ] + |] + + + diff --git a/hypsrc-test/src/TemplateHaskellSplices.hs b/hypsrc-test/src/TemplateHaskellSplices.hs new file mode 100644 index 00000000..bbd3948e --- /dev/null +++ b/hypsrc-test/src/TemplateHaskellSplices.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TemplateHaskell #-} +module TemplateHaskellSplices where + +import TemplateHaskellQuasiquotes + +$(aDecl) + +foo = id $(anExpression2) diff --git a/hypsrc-test/src/UsingQuasiquotes.hs b/hypsrc-test/src/UsingQuasiquotes.hs new file mode 100644 index 00000000..34872d4d --- /dev/null +++ b/hypsrc-test/src/UsingQuasiquotes.hs @@ -0,0 +1,9 @@ +{-# LANGUAGE QuasiQuotes #-} +module UsingQuasiquotes where + +import Quasiquoter + +baz = [string| foo bar |] ++ [string| some + mulitline + quasiquote +|] -- cgit v1.2.3