Skip to content
Snippets Groups Projects
Commit d989d3cc authored by Joachim Breitner's avatar Joachim Breitner
Browse files

html-test: Always set language

from ghc-9.2 on, the “default” langauge of GHC is expected to change
more wildly. To prepare for that (and unblock
ghc/ghc!4853), this sets the
language for all the test files to `Haskell2010`. This should insolate
this test suite against changes to the default.
parent bce435a3
No related branches found
No related tags found
No related merge requests found
Showing
with 55 additions and 0 deletions
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TypeOperators, TypeFamilies #-}
module Bug722 where
......
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
......
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeOperators #-}
module Bug825 where
......
{-# LANGUAGE Haskell2010 #-}
module Bug873 (($), ($$)) where
infixr 0 $$
......
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE PatternSynonyms #-}
module Bug946 (
AnInt(AnInt, Zero),
......
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE KindSignatures #-}
module Bug992 where
......
{-# LANGUAGE Haskell2010 #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
......
{-# LANGUAGE Haskell2010 #-}
module Classes where
......
{-# LANGUAGE Haskell2010 #-}
module Fixity where
......
{-# LANGUAGE Haskell2010 #-}
module Bar where
......
{-# LANGUAGE Haskell2010 #-}
module Foo where
......
{-# LANGUAGE Haskell2010 #-}
module ReaderT where
newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
{-# LANGUAGE Haskell2010 #-}
module ReaderTReexport (ReaderT(..), runReaderT) where
import ReaderT
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>A</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bold</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bug1</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bug1004</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bug1033</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bug1035</p
......
......@@ -38,6 +38,12 @@
><td
>Safe-Inferred</td
></tr
><tr
><th
>Language</th
><td
>Haskell2010</td
></tr
></table
><p class="caption"
>Bug1050</p
......
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