Skip to content
Snippets Groups Projects
Commit d46e34d0 authored by Andrea Condoluci's avatar Andrea Condoluci Committed by Marge Bot
Browse files

Add tests for T17820

parent c668fd2c
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE TemplateHaskell #-}
module Main where
data D = C ()
$( const mempty C )
T17820a.hs:7:17: error:
GHC stage restriction:
‘C’ is used in a top-level splice, quasi-quote, or annotation,
and must be imported, not defined locally
{-# LANGUAGE TemplateHaskell #-}
module Main where
data D = C { f :: () }
$( const mempty f )
T17820b.hs:7:17: error:
GHC stage restriction:
‘f’ is used in a top-level splice, quasi-quote, or annotation,
and must be imported, not defined locally
{-# LANGUAGE TemplateHaskell #-}
module Main where
class C t where
meth :: t ()
$( const mempty (meth :: forall t. C t => t ()) )
T17820c.hs:8:18: error:
GHC stage restriction:
‘meth’ is used in a top-level splice, quasi-quote, or annotation,
and must be imported, not defined locally
{-# LANGUAGE TemplateHaskell #-}
module Main where
decls = [d| data D = MkD { foo :: Int }
blargh = $(const [| 0 |] foo) |]
T17820d.hs:6:38: error:
• Stage error: ‘foo’ is bound at stage 2 but used at stage 1
• In the untyped splice: $(const [| 0 |] foo)
In the Template Haskell quotation
[d| data D = MkD {foo :: Int}
blargh = $(const [| 0 |] foo) |]
{-# LANGUAGE TemplateHaskell, TypeFamilies #-}
module Main where
data family F a
data instance F () = C ()
$( const mempty C )
T17820e.hs:9:17: error:
GHC stage restriction:
‘C’ is used in a top-level splice, quasi-quote, or annotation,
and must be imported, not defined locally
......@@ -534,3 +534,8 @@ test('T19737', normal, compile, [''])
test('T19759', normal, compile, [''])
test('T20060', normal, compile, [''])
test('T20179', normal, compile_fail, [''])
test('T17820a', normal, compile_fail, [''])
test('T17820b', normal, compile_fail, [''])
test('T17820c', normal, compile_fail, [''])
test('T17820d', normal, compile_fail, [''])
test('T17820e', normal, compile_fail, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment