diff --git a/testsuite/tests/polykinds/PolyKinds06.hs b/testsuite/tests/polykinds/PolyKinds06.hs index 9691d45ebb0dd332284000de60894c67d5e4ee3f..691d103d6f01cfe0575e7c28d68c97d9137fa554 100644 --- a/testsuite/tests/polykinds/PolyKinds06.hs +++ b/testsuite/tests/polykinds/PolyKinds06.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DataKinds, KindSignatures #-} {-# LANGUAGE GADTs #-} module PolyKinds06 where diff --git a/testsuite/tests/polykinds/T5935.hs b/testsuite/tests/polykinds/T5935.hs new file mode 100644 index 0000000000000000000000000000000000000000..3f9184d1c77fabba8db35312484ce85a2b3eaa82 --- /dev/null +++ b/testsuite/tests/polykinds/T5935.hs @@ -0,0 +1,13 @@ +{-# LANGUAGE PolyKinds, + GADTs, + DataKinds, + KindSignatures + #-} + +module T5935 where + +data SList a where + SNil :: SList '[] + +x :: SList ('[] :: [Bool]) +x = SNil diff --git a/testsuite/tests/polykinds/T5937.hs b/testsuite/tests/polykinds/T5937.hs new file mode 100644 index 0000000000000000000000000000000000000000..20bc59e6f1f772d9972cadbf3e3d50771092d4dd --- /dev/null +++ b/testsuite/tests/polykinds/T5937.hs @@ -0,0 +1,6 @@ +{-# LANGUAGE PolyKinds, KindSignatures, DataKinds, GADTs #-} +module T5937 where + +data SMaybe :: (k -> *) -> Maybe k -> * where + SNothing :: SMaybe s 'Nothing + SJust :: s a -> SMaybe s ('Just a) diff --git a/testsuite/tests/polykinds/all.T b/testsuite/tests/polykinds/all.T index 5767f8c9aa739ae1c9e4688316e549801882e840..7162b289fd63b5b7897acb1da99e04a929b359ca 100644 --- a/testsuite/tests/polykinds/all.T +++ b/testsuite/tests/polykinds/all.T @@ -29,4 +29,7 @@ test('T5862', normal, compile, ['']) test('T5912', normal, compile, ['']) test('T5881', normal, run_command, ['$MAKE -s --no-print-directory T5881']) test('T5716', normal, compile_fail, ['']) +test('T5937', normal, compile, ['']) +test('T5935', normal, compile, ['']) + diff --git a/testsuite/tests/simplCore/should_run/T5915.hs b/testsuite/tests/simplCore/should_run/T5915.hs new file mode 100644 index 0000000000000000000000000000000000000000..b7ae885830b26e3d6644a27e08993cfdc5fe3546 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T5915.hs @@ -0,0 +1,5 @@ +module Main where + +test = seq (seq id (\a -> undefined a)) + +main = print (test [0]) diff --git a/testsuite/tests/simplCore/should_run/T5915.stdout b/testsuite/tests/simplCore/should_run/T5915.stdout new file mode 100644 index 0000000000000000000000000000000000000000..111bb868654241e737bb212a92db19039329a914 --- /dev/null +++ b/testsuite/tests/simplCore/should_run/T5915.stdout @@ -0,0 +1 @@ +[0] diff --git a/testsuite/tests/simplCore/should_run/all.T b/testsuite/tests/simplCore/should_run/all.T index fb04d89ec590264894692a2a86b90ec41a1ae20c..aa3cc7f2362785268f9d493bbbbd6739a7b4084c 100644 --- a/testsuite/tests/simplCore/should_run/all.T +++ b/testsuite/tests/simplCore/should_run/all.T @@ -50,6 +50,7 @@ test('T5441', extra_clean(['T5441a.o','T5441a.hi']), multimod_compile_and_run, ['T5441','']) test('T5603', normal, compile_and_run, ['']) -# Run this test *without* optimisation too +# Run these tests *without* optimisation too test('T5625', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, ['']) test('T5587', [ only_ways(['normal','optasm']), exit_code(1) ], compile_and_run, ['']) +test('T5915', only_ways(['normal','optasm']), compile_and_run, ['']) diff --git a/testsuite/tests/th/T1541.hs b/testsuite/tests/th/T1541.hs new file mode 100644 index 0000000000000000000000000000000000000000..c570e75b22f2126adeb92ae787621590ef6a9531 --- /dev/null +++ b/testsuite/tests/th/T1541.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE TemplateHaskell #-} +module T1541 where + +$( [d| infixr 3 +++ + (+++) :: Int -> Bool -> Bool + (+++) x y = error "ruk" + |]) + +-- This definition will only typecheck if the +-- the fixity of (+++) is infixr +foo p q r = p +++ q +++ r diff --git a/testsuite/tests/th/T5882.hs b/testsuite/tests/th/T5882.hs new file mode 100644 index 0000000000000000000000000000000000000000..73805bf082fdca720ddac8011038d11ca4ed4222 --- /dev/null +++ b/testsuite/tests/th/T5882.hs @@ -0,0 +1,11 @@ +{-# LANGUAGE GADTSyntax, TemplateHaskell, KindSignatures #-} + +module T5882 where +data Foo :: * -> * where + Foo :: a -> Foo a + +$( [d| data Bar :: * -> * where + Bar :: a -> Bar a + |] ) + +f (Bar x) = Foo x diff --git a/testsuite/tests/th/T5883.hs b/testsuite/tests/th/T5883.hs new file mode 100644 index 0000000000000000000000000000000000000000..c33cc69ab6fcebd732c81af18d245df8dd55d019 --- /dev/null +++ b/testsuite/tests/th/T5883.hs @@ -0,0 +1,12 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} +module T5883 where + +import Language.Haskell.TH + +$( [d| + data Unit = Unit + instance Show Unit where + show _ = "" + {-# INLINE show #-} + |]) diff --git a/testsuite/tests/th/T5883.stderr b/testsuite/tests/th/T5883.stderr new file mode 100644 index 0000000000000000000000000000000000000000..0b0f7058230327f43cb3dd9a3e0764faaf3166d4 --- /dev/null +++ b/testsuite/tests/th/T5883.stderr @@ -0,0 +1,12 @@ +T5883.hs:1:1: Splicing declarations + [d| data Unit = Unit + + instance Show Unit where + show _ = "" + {-# INLINE show #-} |] + ======> + T5883.hs:(7,4)-(12,4) + data Unit = Unit + instance Show Unit where + {-# INLINE show #-} + show _ = "" diff --git a/testsuite/tests/th/T5886.hs b/testsuite/tests/th/T5886.hs new file mode 100644 index 0000000000000000000000000000000000000000..5465815ae3579d239707d2d215bbabf92b904117 --- /dev/null +++ b/testsuite/tests/th/T5886.hs @@ -0,0 +1,8 @@ +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} + +module T5886 where + +import T5886a + +$(bang) diff --git a/testsuite/tests/th/T5886a.hs b/testsuite/tests/th/T5886a.hs new file mode 100644 index 0000000000000000000000000000000000000000..4c6f433b5f385c368bafac9a8fc76ea0f1ce54c7 --- /dev/null +++ b/testsuite/tests/th/T5886a.hs @@ -0,0 +1,14 @@ +{-# LANGUAGE UnicodeSyntax #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} + +module T5886a where + +import Language.Haskell.TH + +class C α where + type AT α ∷ ★ + +bang ∷ DecsQ +bang = return [InstanceD [] (AppT (ConT ''C) (ConT ''Int)) + [TySynInstD ''AT [ConT ''Int] (ConT ''Int)]] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 03d7bdb2e06a331d689078ecdd9390fb3e61afdb..6fb56a8fa72751852847550f984dcec8824efe30 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -220,4 +220,9 @@ test('T5665', extra_clean(['T5665a.hi','T5665a.o']), test('T5700', extra_clean(['T5700a.hi','T5700a.o']), multimod_compile, ['T5700','-v0 -ddump-splices']) test('T5721', normal, compile, ['-v0']) +test('T1541', normal, compile, ['-v0']) +test('T5883', normal, compile, ['-v0 -dsuppress-uniques -ddump-splices']) +test('T5882', normal, compile, ['-v0']) +test('T5886', extra_clean(['T5886a.hi','T5886a.o']), + multimod_compile, ['T5886','-v0'])