diff --git a/hoogle-test/src/Bug722/Bug722.hs b/hoogle-test/src/Bug722/Bug722.hs
index a33d5b24ad17e0a7bfd3c6156ebafa4d609c4b0f..ef7e9a2f3e2701147aac08b0c77d4318d8471db0 100644
--- a/hoogle-test/src/Bug722/Bug722.hs
+++ b/hoogle-test/src/Bug722/Bug722.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeOperators, TypeFamilies #-}
 module Bug722 where
 
diff --git a/hoogle-test/src/Bug806/Bug806.hs b/hoogle-test/src/Bug806/Bug806.hs
index 45efda7759c955de5b3484c85269ffa8b766100f..6deb98c1e9306dfcb39738431273407a64c221e3 100644
--- a/hoogle-test/src/Bug806/Bug806.hs
+++ b/hoogle-test/src/Bug806/Bug806.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE KindSignatures #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE UndecidableInstances #-}
diff --git a/hoogle-test/src/Bug825/Bug825.hs b/hoogle-test/src/Bug825/Bug825.hs
index bfe071390b308d8f8d93314de38dba5e566e88cf..48c0930540390d2c0e7de53946d784494fd2825a 100644
--- a/hoogle-test/src/Bug825/Bug825.hs
+++ b/hoogle-test/src/Bug825/Bug825.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE TypeOperators #-}
 module Bug825 where
diff --git a/hoogle-test/src/Bug873/Bug873.hs b/hoogle-test/src/Bug873/Bug873.hs
index 3a9a538367d99c56760ef4e5149150deb1e3feb2..4df1b772d7679e49997112eec74d987438faea17 100644
--- a/hoogle-test/src/Bug873/Bug873.hs
+++ b/hoogle-test/src/Bug873/Bug873.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug873 (($), ($$)) where
 infixr 0 $$
 
diff --git a/hoogle-test/src/Bug946/Bug946.hs b/hoogle-test/src/Bug946/Bug946.hs
index 606b5ac48794c39733e27e7ab8afd49eac70da00..ec567d6df10a29692695b2e2bb8c88a7b3056079 100644
--- a/hoogle-test/src/Bug946/Bug946.hs
+++ b/hoogle-test/src/Bug946/Bug946.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE PatternSynonyms #-}
 module Bug946 (
   AnInt(AnInt, Zero),
diff --git a/hoogle-test/src/Bug992/Bug992.hs b/hoogle-test/src/Bug992/Bug992.hs
index bd7724276db5d4c380c77a34f0f60a0f7183dd5e..0b03964bacb694c887ac48bdf194c5415ee1fd22 100644
--- a/hoogle-test/src/Bug992/Bug992.hs
+++ b/hoogle-test/src/Bug992/Bug992.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE KindSignatures #-}
 
 module Bug992 where
diff --git a/hoogle-test/src/assoc-types/AssocTypes.hs b/hoogle-test/src/assoc-types/AssocTypes.hs
index ceacc8346be95f2aa98e6774542823c9c5121716..3fa5f034711ce194d70fc2e2e7e94beacfbd384f 100644
--- a/hoogle-test/src/assoc-types/AssocTypes.hs
+++ b/hoogle-test/src/assoc-types/AssocTypes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 {-# LANGUAGE AllowAmbiguousTypes #-}
 
diff --git a/hoogle-test/src/classes/Classes.hs b/hoogle-test/src/classes/Classes.hs
index 23f68499407974ac25de926bb1c8248010d9094d..2bd726a286cbbd8661a3b788e1cb3fd5af2112a8 100644
--- a/hoogle-test/src/classes/Classes.hs
+++ b/hoogle-test/src/classes/Classes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Classes where
 
 
diff --git a/hoogle-test/src/fixity/Fixity.hs b/hoogle-test/src/fixity/Fixity.hs
index 3af38117cf2f942aaf2b66ecf72888083833a841..122bd4f8b42e2811ab4866274ab0f30a1388491c 100644
--- a/hoogle-test/src/fixity/Fixity.hs
+++ b/hoogle-test/src/fixity/Fixity.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Fixity where
 
 
diff --git a/hoogle-test/src/modules/Bar.hs b/hoogle-test/src/modules/Bar.hs
index 156a835f62964e9dd91015dacb817957fd9ea9cb..86e2648be021b0d8debbff244a6f895cc6d57817 100644
--- a/hoogle-test/src/modules/Bar.hs
+++ b/hoogle-test/src/modules/Bar.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bar where
 
 
diff --git a/hoogle-test/src/modules/Foo.hs b/hoogle-test/src/modules/Foo.hs
index 6581fe4c41b26d1e95e26d97d1ac4826a290bf0c..947da4cef0c4759813d2b5ae0c04a209356f64cc 100644
--- a/hoogle-test/src/modules/Foo.hs
+++ b/hoogle-test/src/modules/Foo.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Foo where
 
 
diff --git a/hoogle-test/src/type-sigs/ReaderT.hs b/hoogle-test/src/type-sigs/ReaderT.hs
index 009c7ed217586e067165f8f9fd42744701f63ef2..fb09bac028bff640e8c1ae19f448ed06d6c568a5 100644
--- a/hoogle-test/src/type-sigs/ReaderT.hs
+++ b/hoogle-test/src/type-sigs/ReaderT.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module ReaderT where
 
 newtype ReaderT r m a = ReaderT { runReaderT :: r -> m a }
diff --git a/hoogle-test/src/type-sigs/ReaderTReexport.hs b/hoogle-test/src/type-sigs/ReaderTReexport.hs
index 21fa44eed5fd4cb5b20f546d47c8a80151a02d5d..b995bba8bb9d6ab058f55954196899c46907f1db 100644
--- a/hoogle-test/src/type-sigs/ReaderTReexport.hs
+++ b/hoogle-test/src/type-sigs/ReaderTReexport.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module ReaderTReexport (ReaderT(..), runReaderT) where
 
 import ReaderT
diff --git a/html-test/ref/A.html b/html-test/ref/A.html
index c27f1888389a22c16d16d2e78dce5420ee78fcb1..d3dc54ff3a82dcfe4f2b8156d4e60c134fa1bd10 100644
--- a/html-test/ref/A.html
+++ b/html-test/ref/A.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>A</p
diff --git a/html-test/ref/Bold.html b/html-test/ref/Bold.html
index 2bbe37a4fc9aadab4e35e02151788952f1ca0c2b..00f9301a5787163220a9ae6ab67223984091905b 100644
--- a/html-test/ref/Bold.html
+++ b/html-test/ref/Bold.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bold</p
diff --git a/html-test/ref/Bug1.html b/html-test/ref/Bug1.html
index a14ac3871b7541896c07437056bf4cd70b4a11ff..c3e350d8f10740850e1fc066c3790254e77b644b 100644
--- a/html-test/ref/Bug1.html
+++ b/html-test/ref/Bug1.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1</p
diff --git a/html-test/ref/Bug1004.html b/html-test/ref/Bug1004.html
index f074f006acd89124f54f4e026a454cf716e291ed..d1f51003ae288b0a21a71141bd484ad17b287161 100644
--- a/html-test/ref/Bug1004.html
+++ b/html-test/ref/Bug1004.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1004</p
diff --git a/html-test/ref/Bug1033.html b/html-test/ref/Bug1033.html
index 362544477a1275020e1b93578404bb4f5171b3c9..327739a8863a0d808c9dccc70b2dfeea3fb56d60 100644
--- a/html-test/ref/Bug1033.html
+++ b/html-test/ref/Bug1033.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1033</p
diff --git a/html-test/ref/Bug1035.html b/html-test/ref/Bug1035.html
index 5e4d6f8217d6905e6052746953f9bf79f38c8ff0..891e230d2cc683e668d0cee52daf17d5d1e7c528 100644
--- a/html-test/ref/Bug1035.html
+++ b/html-test/ref/Bug1035.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1035</p
diff --git a/html-test/ref/Bug1050.html b/html-test/ref/Bug1050.html
index da7ae1d2192627bae48f8ff98232bdfffc099804..89fa19ce304c71ed515c58f6556dbb422bd3adde 100644
--- a/html-test/ref/Bug1050.html
+++ b/html-test/ref/Bug1050.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1050</p
diff --git a/html-test/ref/Bug1054.html b/html-test/ref/Bug1054.html
index df3fae0a7d65fe27286e985a6dd3828fa91791a9..8d31c62e0f9cba8d28b515ff11eb32b7a6d2b95a 100644
--- a/html-test/ref/Bug1054.html
+++ b/html-test/ref/Bug1054.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1054</p
diff --git a/html-test/ref/Bug1063.html b/html-test/ref/Bug1063.html
index f311373a48e8ad6a60a50ca0cd45b613dfa7fe18..7f2b46cf368aaeba0cf29e5f0358c3d07e84c327 100644
--- a/html-test/ref/Bug1063.html
+++ b/html-test/ref/Bug1063.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1063</p
diff --git a/html-test/ref/Bug1067A.html b/html-test/ref/Bug1067A.html
index 96b8d49596e06cab4accfd8da145c85933470ebf..0ccff963730220930c81325bca525a3669b56c85 100644
--- a/html-test/ref/Bug1067A.html
+++ b/html-test/ref/Bug1067A.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1067A</p
diff --git a/html-test/ref/Bug1067B.html b/html-test/ref/Bug1067B.html
index f3bf821afe8e4a0013225717340be44633927580..ab48c202418350fc20dbd1c7a2ddac38a33fa96a 100644
--- a/html-test/ref/Bug1067B.html
+++ b/html-test/ref/Bug1067B.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1067B</p
diff --git a/html-test/ref/Bug1103.html b/html-test/ref/Bug1103.html
index c17eb7b83cb29ae22cd6611206d5712fdd4cca44..60af9b86e5ac93b45933bc82d839fd047fb6e6bf 100644
--- a/html-test/ref/Bug1103.html
+++ b/html-test/ref/Bug1103.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1103</p
diff --git a/html-test/ref/Bug1206.html b/html-test/ref/Bug1206.html
index 8a57993d442737019520a862cd20468bc4841bb7..7a55ff302091ed130d2b94d2b86d0323e5e25dc1 100644
--- a/html-test/ref/Bug1206.html
+++ b/html-test/ref/Bug1206.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug1206</p
diff --git a/html-test/ref/Bug195.html b/html-test/ref/Bug195.html
index af595d5d9aef9e96fe07730e6b056023a29c0a70..3428b31dce3cc6da6ebc0584312c723d21241811 100644
--- a/html-test/ref/Bug195.html
+++ b/html-test/ref/Bug195.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug195</p
diff --git a/html-test/ref/Bug2.html b/html-test/ref/Bug2.html
index c0c192c920d323c165bf39048a7bc956ef75dcd4..f8da696da01ae8cac18f39f177e9183ae599e8bb 100644
--- a/html-test/ref/Bug2.html
+++ b/html-test/ref/Bug2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug2</p
diff --git a/html-test/ref/Bug201.html b/html-test/ref/Bug201.html
index 13ad455620cfb425e6daf472805297b838ab87e7..0f2b3878cde0d95512b4435bc9cdf9dfd45db6bd 100644
--- a/html-test/ref/Bug201.html
+++ b/html-test/ref/Bug201.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug201</p
diff --git a/html-test/ref/Bug253.html b/html-test/ref/Bug253.html
index a482a21ab828f250a47e725841f63b72fb9e34f0..60d5ef66166970ff7c1029db301bb0035669db19 100644
--- a/html-test/ref/Bug253.html
+++ b/html-test/ref/Bug253.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug253</p
diff --git a/html-test/ref/Bug26.html b/html-test/ref/Bug26.html
index 5c6fb34e0a2feeac42d80313c127d037c4f25381..73b33e89a3bdf7e4a0a4332df0de111db55889dc 100644
--- a/html-test/ref/Bug26.html
+++ b/html-test/ref/Bug26.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug26</p
diff --git a/html-test/ref/Bug280.html b/html-test/ref/Bug280.html
index 57e265f4c2fb58100fb26b72da06282f599591cb..e821b091b066a4e71b63d0f6a8bfa00f2b830429 100644
--- a/html-test/ref/Bug280.html
+++ b/html-test/ref/Bug280.html
@@ -46,6 +46,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug280</p
diff --git a/html-test/ref/Bug294.html b/html-test/ref/Bug294.html
index 6ceb34223d2e247290ceb0188834810848a3d9e6..c62fc6069e6df2a2ea3b4c6bc8007cb306dfe80f 100644
--- a/html-test/ref/Bug294.html
+++ b/html-test/ref/Bug294.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug294</p
diff --git a/html-test/ref/Bug298.html b/html-test/ref/Bug298.html
index fc57d08741035affa450c1ae4bfa577b7beed68d..8983195b739e26527070159a15eb513ec5f8f890 100644
--- a/html-test/ref/Bug298.html
+++ b/html-test/ref/Bug298.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug298</p
diff --git a/html-test/ref/Bug3.html b/html-test/ref/Bug3.html
index 0c9d85260be2c60b45e8d613b9b9864eff620dab..da390bc7966c5b1e97f27197d00f4cc6495c459e 100644
--- a/html-test/ref/Bug3.html
+++ b/html-test/ref/Bug3.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug3</p
diff --git a/html-test/ref/Bug308.html b/html-test/ref/Bug308.html
index acd019d3e4ffc15731f92155c9baa2928ab5e5f1..66fedba859a850af39319c24c313e05e67e95359 100644
--- a/html-test/ref/Bug308.html
+++ b/html-test/ref/Bug308.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug308</p
diff --git a/html-test/ref/Bug308CrossModule.html b/html-test/ref/Bug308CrossModule.html
index f754aa879a64e8df3f2fe8d8dc6fc81de05610e8..1b9a280988caefab92ca1d0da1da5b51445cc8be 100644
--- a/html-test/ref/Bug308CrossModule.html
+++ b/html-test/ref/Bug308CrossModule.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug308CrossModule</p
diff --git a/html-test/ref/Bug310.html b/html-test/ref/Bug310.html
index 59faf609e8676b5c5a5fb6e8a8587b1ea444b1ae..85bfbbc3bae1fb8939e36fe17f5ec63eafe90749 100644
--- a/html-test/ref/Bug310.html
+++ b/html-test/ref/Bug310.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug310</p
diff --git a/html-test/ref/Bug313.html b/html-test/ref/Bug313.html
index 83ee7a342f5d9408ad312c32ac334e13b1a842cc..9bb1e176584cf98bff6498b0b2187437413c2cb5 100644
--- a/html-test/ref/Bug313.html
+++ b/html-test/ref/Bug313.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug313</p
diff --git a/html-test/ref/Bug335.html b/html-test/ref/Bug335.html
index 00e31ca02e2781cf4e00d1335136bb8ff8caeed7..a5049088d46eee78df908ef86d84a7c2523014a1 100644
--- a/html-test/ref/Bug335.html
+++ b/html-test/ref/Bug335.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug335</p
diff --git a/html-test/ref/Bug4.html b/html-test/ref/Bug4.html
index 8a19bc6bad9ec6f3210a4938e9d91ba73386fda1..a8861c4ef93969685f6f88d68acb8aa3d312718f 100644
--- a/html-test/ref/Bug4.html
+++ b/html-test/ref/Bug4.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug4</p
diff --git a/html-test/ref/Bug458.html b/html-test/ref/Bug458.html
index d5b5a768845d09f1a79fafb7460e60063ce7ba3c..ad07b3faa4a73086c1b0287c40ed18fc7ed86250 100644
--- a/html-test/ref/Bug458.html
+++ b/html-test/ref/Bug458.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug458</p
diff --git a/html-test/ref/Bug466.html b/html-test/ref/Bug466.html
index 4f6f6f1658d5ebd97f2fd2fe9fa5a2c80346eccc..4fab918a0e8a014fe907e3699327622d1280c2d3 100644
--- a/html-test/ref/Bug466.html
+++ b/html-test/ref/Bug466.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug466</p
diff --git a/html-test/ref/Bug546.html b/html-test/ref/Bug546.html
index bb400a5071acb60d07cd9988f2756042f33a8373..3b478723821b64b5984457343f7967e40fb44846 100644
--- a/html-test/ref/Bug546.html
+++ b/html-test/ref/Bug546.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug546</p
diff --git a/html-test/ref/Bug548.html b/html-test/ref/Bug548.html
index 32cfa2fd05faae042aa94310aa046ca48ca0f156..984a04cdc8e21d4779c74230951af224e2c0aa1a 100644
--- a/html-test/ref/Bug548.html
+++ b/html-test/ref/Bug548.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug548</p
diff --git a/html-test/ref/Bug574.html b/html-test/ref/Bug574.html
index e2024f477b963f5a25d807cac01dfff6787a4c9b..89f71a011218e70f7054fcb9c1a00f8f0b3369ff 100644
--- a/html-test/ref/Bug574.html
+++ b/html-test/ref/Bug574.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug574</p
diff --git a/html-test/ref/Bug6.html b/html-test/ref/Bug6.html
index 5bd4c030d9e8c7e89918f7fd90e9c38a969bc6ce..129542e2351b45124abd50a5f0844ec7e2fa8aea 100644
--- a/html-test/ref/Bug6.html
+++ b/html-test/ref/Bug6.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug6</p
diff --git a/html-test/ref/Bug613.html b/html-test/ref/Bug613.html
index 4df6037de1e3bde216921cd1172717e12f66d632..425fc670b6790082ee65d70b3ec9994b0795e4b6 100644
--- a/html-test/ref/Bug613.html
+++ b/html-test/ref/Bug613.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug613</p
diff --git a/html-test/ref/Bug647.html b/html-test/ref/Bug647.html
index 0648cf51f28bb20ba5a5baa99c6fae9fa15ae09d..07b3b11bd1dbb155644de1d4b6ee4f6a9500c9e2 100644
--- a/html-test/ref/Bug647.html
+++ b/html-test/ref/Bug647.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug647</p
diff --git a/html-test/ref/Bug679.html b/html-test/ref/Bug679.html
index 8814129d9cfa982455153ee48533e05476f7da30..50dbed5a8b2d5ffd81999b91a41da29ad16acae9 100644
--- a/html-test/ref/Bug679.html
+++ b/html-test/ref/Bug679.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug679</p
diff --git a/html-test/ref/Bug7.html b/html-test/ref/Bug7.html
index 5338bda2250934817892d8c2ce2a4f85714788af..df5cebe342e20d8444bb68ad02fe0a4d784b2848 100644
--- a/html-test/ref/Bug7.html
+++ b/html-test/ref/Bug7.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug7</p
diff --git a/html-test/ref/Bug8.html b/html-test/ref/Bug8.html
index 4d6fe69bb1db6a1baedd9ff6bbe0a93e5645dc9e..e62caae38a4933e7da434c95f3139064c004f8c6 100644
--- a/html-test/ref/Bug8.html
+++ b/html-test/ref/Bug8.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug8</p
diff --git a/html-test/ref/Bug85.html b/html-test/ref/Bug85.html
index bbef4d32b6cf1150804ce952ed998b78123dd9fa..c22438c77f30d1d4cf84a60f053f98bcf341c50e 100644
--- a/html-test/ref/Bug85.html
+++ b/html-test/ref/Bug85.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug85</p
diff --git a/html-test/ref/Bug865.html b/html-test/ref/Bug865.html
index 96f64dafd7733ca304614b844aeaabc9128561e2..7cc142b33fff0382e971ec3d9e1fd9ccd17dbc3c 100644
--- a/html-test/ref/Bug865.html
+++ b/html-test/ref/Bug865.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug865</p
diff --git a/html-test/ref/Bug923.html b/html-test/ref/Bug923.html
index d657e08e4a4563229ebdebd23181039467000a46..7c2872542f48789100a8528623901716d26aa282 100644
--- a/html-test/ref/Bug923.html
+++ b/html-test/ref/Bug923.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug923</p
diff --git a/html-test/ref/Bug952.html b/html-test/ref/Bug952.html
index bd301bcd4e61b35b3e6fd137885a698db663121c..0105b82fe73b91dec2436c041b838d3509d12b98 100644
--- a/html-test/ref/Bug952.html
+++ b/html-test/ref/Bug952.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug952</p
diff --git a/html-test/ref/Bug953.html b/html-test/ref/Bug953.html
index aea7ec5c6fe457fe664f3cb0ecb168205e9338c8..b19179d093cdacb7227b22ec56cefdc1a19c83aa 100644
--- a/html-test/ref/Bug953.html
+++ b/html-test/ref/Bug953.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug953</p
diff --git a/html-test/ref/Bug973.html b/html-test/ref/Bug973.html
index 20e2788694582ba097f82731074394ac78b9e778..8297b4f4e83c3c78d6ea024d2ff94d142f9ad155 100644
--- a/html-test/ref/Bug973.html
+++ b/html-test/ref/Bug973.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bug973</p
diff --git a/html-test/ref/BugDeprecated.html b/html-test/ref/BugDeprecated.html
index 92a963f370daa5bd9b113a77335464ec8b3dfd78..e4017f17f7d0016841fa513ead21dd784f46fe07 100644
--- a/html-test/ref/BugDeprecated.html
+++ b/html-test/ref/BugDeprecated.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>BugDeprecated</p
diff --git a/html-test/ref/BugExportHeadings.html b/html-test/ref/BugExportHeadings.html
index ddcb7aa317b5cbb142cc1c6466c648ceba639dc6..2ba3a8585ffed13334ddced7ad9d156aeb130836 100644
--- a/html-test/ref/BugExportHeadings.html
+++ b/html-test/ref/BugExportHeadings.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>BugExportHeadings</p
diff --git a/html-test/ref/Bugs.html b/html-test/ref/Bugs.html
index c6c42446670c0c78bd68726f62edeb6bcc4cde63..59c79d24053b818e001b58d6f8cf94c84d2862fb 100644
--- a/html-test/ref/Bugs.html
+++ b/html-test/ref/Bugs.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Bugs</p
diff --git a/html-test/ref/BundledPatterns.html b/html-test/ref/BundledPatterns.html
index f3a1010daaa1aaa68ae7adf0c4e49d57bf449835..94a197c2cdd196c5095e144410b74a36bb656888 100644
--- a/html-test/ref/BundledPatterns.html
+++ b/html-test/ref/BundledPatterns.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>BundledPatterns</p
diff --git a/html-test/ref/BundledPatterns2.html b/html-test/ref/BundledPatterns2.html
index 9ef3a85da5bd91043c737184336ea3ed20cf3894..3b19205474f755a35e01657c60dfd94c517f5592 100644
--- a/html-test/ref/BundledPatterns2.html
+++ b/html-test/ref/BundledPatterns2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>BundledPatterns2</p
diff --git a/html-test/ref/ConstructorArgs.html b/html-test/ref/ConstructorArgs.html
index 16ef6780b336db8073735849f345d98451f3d599..9441fd03a419c539ec34ccee8730ead2cadc63fc 100644
--- a/html-test/ref/ConstructorArgs.html
+++ b/html-test/ref/ConstructorArgs.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>ConstructorArgs</p
diff --git a/html-test/ref/ConstructorPatternExport.html b/html-test/ref/ConstructorPatternExport.html
index 0822733d195c6cd601efa7c7f52888a0c1ad03cb..aa0c1a8f3d3c5d9dae90681d0072c4397314a475 100644
--- a/html-test/ref/ConstructorPatternExport.html
+++ b/html-test/ref/ConstructorPatternExport.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>ConstructorPatternExport</p
diff --git a/html-test/ref/DefaultAssociatedTypes.html b/html-test/ref/DefaultAssociatedTypes.html
index 4b39483a0cdf58b7a0ec07c60a80dccd17f3ebf6..bc4d8a001e3746e48201aaa19c66338a06174c18 100644
--- a/html-test/ref/DefaultAssociatedTypes.html
+++ b/html-test/ref/DefaultAssociatedTypes.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DefaultAssociatedTypes</p
diff --git a/html-test/ref/DefaultSignatures.html b/html-test/ref/DefaultSignatures.html
index 60d0428f33efcb66862782015c693e531a41d752..f44cc85970978bb4def9d1996da50449f37e5b28 100644
--- a/html-test/ref/DefaultSignatures.html
+++ b/html-test/ref/DefaultSignatures.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DefaultSignatures</p
diff --git a/html-test/ref/DeprecatedClass.html b/html-test/ref/DeprecatedClass.html
index a0de4858de34b99d1c83de765a5a042f90d5dbdc..ff3be26d90f7217f62023ab03af0da3b22e79875 100644
--- a/html-test/ref/DeprecatedClass.html
+++ b/html-test/ref/DeprecatedClass.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedClass</p
diff --git a/html-test/ref/DeprecatedData.html b/html-test/ref/DeprecatedData.html
index 001970df6bc2476224200f12dd8cc88ee9195a28..3ca9982078525378236142bbad73291029e30b7a 100644
--- a/html-test/ref/DeprecatedData.html
+++ b/html-test/ref/DeprecatedData.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedData</p
diff --git a/html-test/ref/DeprecatedFunction.html b/html-test/ref/DeprecatedFunction.html
index 2b3c4a66053378295e0d61e6e3530cce7f3df100..104a67f1b574ad5ac043fd1f75e853f97c0b216f 100644
--- a/html-test/ref/DeprecatedFunction.html
+++ b/html-test/ref/DeprecatedFunction.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedFunction</p
diff --git a/html-test/ref/DeprecatedFunction2.html b/html-test/ref/DeprecatedFunction2.html
index a2cd84a2219c4a89302061ee13f466c5ddafd407..023e470114f33d6906ecbd7258de049d3fd85390 100644
--- a/html-test/ref/DeprecatedFunction2.html
+++ b/html-test/ref/DeprecatedFunction2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedFunction2</p
diff --git a/html-test/ref/DeprecatedFunction3.html b/html-test/ref/DeprecatedFunction3.html
index 90bde84dcc7a8c0f6c2d40c7aa20fe0d3b41cc8f..3666bcbc5af2a592e473794d3b4a32f1784da081 100644
--- a/html-test/ref/DeprecatedFunction3.html
+++ b/html-test/ref/DeprecatedFunction3.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedFunction3</p
diff --git a/html-test/ref/DeprecatedModule.html b/html-test/ref/DeprecatedModule.html
index c4d1c241dea76cf4b17dab7856ea7b1d12290b77..9a0a058b22636e6d53d1ddf703ae7d9431048472 100644
--- a/html-test/ref/DeprecatedModule.html
+++ b/html-test/ref/DeprecatedModule.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedModule</p
diff --git a/html-test/ref/DeprecatedModule2.html b/html-test/ref/DeprecatedModule2.html
index b1d6c12a8aa559ca1369c34187069cea0f7e78e6..c179dfc1cd33cbc943e54526ce688c0e47cf47df 100644
--- a/html-test/ref/DeprecatedModule2.html
+++ b/html-test/ref/DeprecatedModule2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedModule2</p
diff --git a/html-test/ref/DeprecatedNewtype.html b/html-test/ref/DeprecatedNewtype.html
index 4fad244af6f486c4de23c0197762839bf56952b6..7e423fc9b56c57a3d1cee597958efbfddcb56640 100644
--- a/html-test/ref/DeprecatedNewtype.html
+++ b/html-test/ref/DeprecatedNewtype.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedNewtype</p
diff --git a/html-test/ref/DeprecatedReExport.html b/html-test/ref/DeprecatedReExport.html
index d8dd554fdb93ac434979520074d3977ea6ab39d9..672f28aeeda987f6d1d055e7dc01e6cc0584864e 100644
--- a/html-test/ref/DeprecatedReExport.html
+++ b/html-test/ref/DeprecatedReExport.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedReExport</p
diff --git a/html-test/ref/DeprecatedRecord.html b/html-test/ref/DeprecatedRecord.html
index 7760386d512b01a98aa73e3e403d15692e1b4a5c..37dceddd13fd15aac6cc12c6d0c9c208cd9aa01b 100644
--- a/html-test/ref/DeprecatedRecord.html
+++ b/html-test/ref/DeprecatedRecord.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedRecord</p
diff --git a/html-test/ref/DeprecatedTypeFamily.html b/html-test/ref/DeprecatedTypeFamily.html
index 76a9a039f24e551123fb729848c0acbd2cb790f1..4fbaeaa5e997704f29c705050742c0c649461aa9 100644
--- a/html-test/ref/DeprecatedTypeFamily.html
+++ b/html-test/ref/DeprecatedTypeFamily.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedTypeFamily</p
diff --git a/html-test/ref/DeprecatedTypeSynonym.html b/html-test/ref/DeprecatedTypeSynonym.html
index 32c9721b2e5a6aa473ff9e8a8ae36fbc0c806276..81c7d78eb0fd1501e4eb5ed64264900c1f36e69c 100644
--- a/html-test/ref/DeprecatedTypeSynonym.html
+++ b/html-test/ref/DeprecatedTypeSynonym.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DeprecatedTypeSynonym</p
diff --git a/html-test/ref/DuplicateRecordFields.html b/html-test/ref/DuplicateRecordFields.html
index fab57a042680761f66411ed795be7d9df1b323aa..7017df6a3583b9d512f2e298e506333d4aa64068 100644
--- a/html-test/ref/DuplicateRecordFields.html
+++ b/html-test/ref/DuplicateRecordFields.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>DuplicateRecordFields</p
diff --git a/html-test/ref/Examples.html b/html-test/ref/Examples.html
index f5a7ba8c8de2632d516086fba93a788b3d8d8408..b397e0796fbf1335debe1b26dcacbfb73e7c4766 100644
--- a/html-test/ref/Examples.html
+++ b/html-test/ref/Examples.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Examples</p
diff --git a/html-test/ref/FunArgs.html b/html-test/ref/FunArgs.html
index 03a97522c12a4556b6262c37acf393b4a87fbd09..2fac6d4e31e92364fe26e73bf47552cb61dc6b92 100644
--- a/html-test/ref/FunArgs.html
+++ b/html-test/ref/FunArgs.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>FunArgs</p
diff --git a/html-test/ref/GADTRecords.html b/html-test/ref/GADTRecords.html
index 9dac0c13257ca36b5fd8bda36d70771fa52824fe..834d8f6723d94247658660305a9a6cbde30b1254 100644
--- a/html-test/ref/GADTRecords.html
+++ b/html-test/ref/GADTRecords.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>GADTRecords</p
diff --git a/html-test/ref/GadtConstructorArgs.html b/html-test/ref/GadtConstructorArgs.html
index c1a4dedf6827cee401c9c87d099bf6f7115ee90f..aefe15f5cb2246fd095376e33beab16d0ef18c53 100644
--- a/html-test/ref/GadtConstructorArgs.html
+++ b/html-test/ref/GadtConstructorArgs.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>GadtConstructorArgs</p
diff --git a/html-test/ref/Hash.html b/html-test/ref/Hash.html
index 8c062e1bd0fc39dab49702b209cf5b6342e2b5aa..a924e0e845710d00a90a3f7ad1a99ab47b47e5f4 100644
--- a/html-test/ref/Hash.html
+++ b/html-test/ref/Hash.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Hash</p
diff --git a/html-test/ref/HiddenInstances.html b/html-test/ref/HiddenInstances.html
index 1964f4f8afcfda26f7fb74a9a57a0db9b96ebbb6..71a80862850831531df4c8b903323338fafe7d80 100644
--- a/html-test/ref/HiddenInstances.html
+++ b/html-test/ref/HiddenInstances.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>HiddenInstances</p
diff --git a/html-test/ref/HiddenInstancesB.html b/html-test/ref/HiddenInstancesB.html
index 579f57544e34f5e7d47243a0c0dc70c772f312d7..89667e7325de4b62b206e45767b33482a032cbf2 100644
--- a/html-test/ref/HiddenInstancesB.html
+++ b/html-test/ref/HiddenInstancesB.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>HiddenInstancesB</p
diff --git a/html-test/ref/Hyperlinks.html b/html-test/ref/Hyperlinks.html
index 947d5342f9bc8ad0d02156fce4f143ba32a86107..28a38baca4c9366824338c907b1a696992a1335e 100644
--- a/html-test/ref/Hyperlinks.html
+++ b/html-test/ref/Hyperlinks.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Hyperlinks</p
diff --git a/html-test/ref/Identifiers.html b/html-test/ref/Identifiers.html
index c89e74342b278724e3a63e7136cbe00df77b0177..76487140a9c0cfa35cd43dff2a7cf17b2e343ce2 100644
--- a/html-test/ref/Identifiers.html
+++ b/html-test/ref/Identifiers.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Identifiers</p
diff --git a/html-test/ref/IgnoreExports.html b/html-test/ref/IgnoreExports.html
index ccaffdad0a7c3a19aef9c2b94865c4862804bd72..7450a3abc0349f9189b56c37ba9633528e0f48cb 100644
--- a/html-test/ref/IgnoreExports.html
+++ b/html-test/ref/IgnoreExports.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>IgnoreExports</p
diff --git a/html-test/ref/ImplicitParams.html b/html-test/ref/ImplicitParams.html
index 1c0126a9d20bf3a6629976262366471e3a471ae8..b027baad7b4d1041403fa984f5fe4c549ddc1006 100644
--- a/html-test/ref/ImplicitParams.html
+++ b/html-test/ref/ImplicitParams.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>ImplicitParams</p
diff --git a/html-test/ref/Instances.html b/html-test/ref/Instances.html
index 764f538de5f4065ddf8d29ebd953c210ae1bca70..9e9f2300b772b7efbf5413d98708d021d745d947 100644
--- a/html-test/ref/Instances.html
+++ b/html-test/ref/Instances.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Instances</p
diff --git a/html-test/ref/LinearTypes.html b/html-test/ref/LinearTypes.html
index 48ad04e2dce78fe365e680b57f00b9c555e9d493..fbece396bd03bbab45ad4b10497cff9117877b8f 100644
--- a/html-test/ref/LinearTypes.html
+++ b/html-test/ref/LinearTypes.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>LinearTypes</p
diff --git a/html-test/ref/Math.html b/html-test/ref/Math.html
index 627f4840dc024cc2acf091900b68df3c3f38718c..6ae9e392ff92128737261c90084ebe7ea02bcdbb 100644
--- a/html-test/ref/Math.html
+++ b/html-test/ref/Math.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Math</p
diff --git a/html-test/ref/Minimal.html b/html-test/ref/Minimal.html
index cacbb86dfb6ddf9db83000943275763588c77ec0..f8fa63ffa9f7af0369d151c2c7a9c1c75aeefff1 100644
--- a/html-test/ref/Minimal.html
+++ b/html-test/ref/Minimal.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Minimal</p
diff --git a/html-test/ref/ModuleWithWarning.html b/html-test/ref/ModuleWithWarning.html
index cb8b8f27c46fc1011e7beb7a0df6b85e124636bd..a54331cd9203b8feefcc0857c9af4a698e5f0594 100644
--- a/html-test/ref/ModuleWithWarning.html
+++ b/html-test/ref/ModuleWithWarning.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>ModuleWithWarning</p
diff --git a/html-test/ref/NamedDoc.html b/html-test/ref/NamedDoc.html
index 1fd0c25b9a3114c4fbe1289b1d086fc0172fe6e7..2e0f63211383396b1b0a539016a4fc48e1f9586c 100644
--- a/html-test/ref/NamedDoc.html
+++ b/html-test/ref/NamedDoc.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>NamedDoc</p
diff --git a/html-test/ref/NamespacedIdentifiers.html b/html-test/ref/NamespacedIdentifiers.html
index 8424e46d7f269e10de82c43a6b7fde71d25dba2c..2507c934a7a1c000feeae30ee65f18ba67585b39 100644
--- a/html-test/ref/NamespacedIdentifiers.html
+++ b/html-test/ref/NamespacedIdentifiers.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>NamespacedIdentifiers</p
diff --git a/html-test/ref/Nesting.html b/html-test/ref/Nesting.html
index 14905718859de6e3be1396f0d1e0cd5ff4325bfe..5911133851e6dc3b3f2e3914257d86bce24a1b90 100644
--- a/html-test/ref/Nesting.html
+++ b/html-test/ref/Nesting.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Nesting</p
diff --git a/html-test/ref/NoLayout.html b/html-test/ref/NoLayout.html
index a6afc3fcbeb92686b092f4042f83d8661d1d9348..44ed6688cf78adfe5f42ff3afd4cc0df58efa56b 100644
--- a/html-test/ref/NoLayout.html
+++ b/html-test/ref/NoLayout.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>NoLayout</p
diff --git a/html-test/ref/NonGreedy.html b/html-test/ref/NonGreedy.html
index 76861de65f551bf00267f691da62f0a7718f6d61..7f5146bad355d78123b4791d122e69c64a0fb78c 100644
--- a/html-test/ref/NonGreedy.html
+++ b/html-test/ref/NonGreedy.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>NonGreedy</p
diff --git a/html-test/ref/Operators.html b/html-test/ref/Operators.html
index 005d3a0c2c0c1b6ea28e4329c2f5a0124f815820..9ebbe42d064fe0c5486c7db571ff28ba2a20dc9b 100644
--- a/html-test/ref/Operators.html
+++ b/html-test/ref/Operators.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Operators</p
diff --git a/html-test/ref/OrphanInstances.html b/html-test/ref/OrphanInstances.html
index cc5b5c7cdf820468610b4cfa67b5cc84fa84674e..cad2a2d7a6603cd38ba4c45462a234c91a8f8549 100644
--- a/html-test/ref/OrphanInstances.html
+++ b/html-test/ref/OrphanInstances.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>OrphanInstances</p
diff --git a/html-test/ref/OrphanInstancesClass.html b/html-test/ref/OrphanInstancesClass.html
index b90e36e22743e57baa88fa86ec1b07cdf414b996..5445ddd7320a3865e251f93019da990b7ee1e4a6 100644
--- a/html-test/ref/OrphanInstancesClass.html
+++ b/html-test/ref/OrphanInstancesClass.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>OrphanInstancesClass</p
diff --git a/html-test/ref/OrphanInstancesType.html b/html-test/ref/OrphanInstancesType.html
index 16ea1d5373a2c36049a66bc217bb88c4aa01c565..2b01525c97c8960d04004de6078307424d63ec4c 100644
--- a/html-test/ref/OrphanInstancesType.html
+++ b/html-test/ref/OrphanInstancesType.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>OrphanInstancesType</p
diff --git a/html-test/ref/PR643.html b/html-test/ref/PR643.html
index e19e3343a66b901c85fe6f514c3e43f2b8f89050..bd0bef4c67ee7717f1dff95ac69483333b00f998 100644
--- a/html-test/ref/PR643.html
+++ b/html-test/ref/PR643.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>PR643</p
diff --git a/html-test/ref/PR643_1.html b/html-test/ref/PR643_1.html
index 0582deae100a11c70de92bcab689751388eb8a6b..91fd0eddcfe64449a5f44f8c350ac77a4c9f5ecf 100644
--- a/html-test/ref/PR643_1.html
+++ b/html-test/ref/PR643_1.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>PR643_1</p
diff --git a/html-test/ref/PatternSyns.html b/html-test/ref/PatternSyns.html
index 7e5cdc1f0136fe2d047281eed21b3a5c42da42cf..54c2ce005ca0e5601375e2e655274405418ef11a 100644
--- a/html-test/ref/PatternSyns.html
+++ b/html-test/ref/PatternSyns.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>PatternSyns</p
diff --git a/html-test/ref/PromotedTypes.html b/html-test/ref/PromotedTypes.html
index b4e4dd7c03f1df8f8184125144774fb177b4d61e..d13a6bd80ff84145e79269b820601f317686744b 100644
--- a/html-test/ref/PromotedTypes.html
+++ b/html-test/ref/PromotedTypes.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>PromotedTypes</p
diff --git a/html-test/ref/Properties.html b/html-test/ref/Properties.html
index 2adab2b094512ca6ddadec0cc61fcc3e90d860ac..aa9bc4adc4063c752c30be9788eacb752708f216 100644
--- a/html-test/ref/Properties.html
+++ b/html-test/ref/Properties.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Properties</p
diff --git a/html-test/ref/PruneWithWarning.html b/html-test/ref/PruneWithWarning.html
index 9747a87fa16267711733c96619946e96c8db2ec1..ba03144ea76ada484736bb3cf8d2e61b2c8a9fbb 100644
--- a/html-test/ref/PruneWithWarning.html
+++ b/html-test/ref/PruneWithWarning.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>PruneWithWarning</p
diff --git a/html-test/ref/QuantifiedConstraints.html b/html-test/ref/QuantifiedConstraints.html
index 0833f1a82f3d38b5c88ef21cf5fbbc636463879a..8838facb1a50ad29bc7b4ae26cc3da4bc33ebdf7 100644
--- a/html-test/ref/QuantifiedConstraints.html
+++ b/html-test/ref/QuantifiedConstraints.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>QuantifiedConstraints</p
diff --git a/html-test/ref/QuasiExpr.html b/html-test/ref/QuasiExpr.html
index e3c7b6e7deaae6d074a1786e2a997d971178a136..b7660f202e56db9e737240ae3e3aa24c6e4ee787 100644
--- a/html-test/ref/QuasiExpr.html
+++ b/html-test/ref/QuasiExpr.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>QuasiExpr</p
diff --git a/html-test/ref/QuasiQuote.html b/html-test/ref/QuasiQuote.html
index 1ea5109967499d823fca89e45a75f1758091f994..210c52481b960428a10be74ca582711ed4e26092 100644
--- a/html-test/ref/QuasiQuote.html
+++ b/html-test/ref/QuasiQuote.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>QuasiQuote</p
diff --git a/html-test/ref/SectionLabels.html b/html-test/ref/SectionLabels.html
index 8b571b4229e722d22621755495150474bc02d2cd..5137afa45fba8bea6f817f573be678d8a44b8c17 100644
--- a/html-test/ref/SectionLabels.html
+++ b/html-test/ref/SectionLabels.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>SectionLabels</p
diff --git a/html-test/ref/SpuriousSuperclassConstraints.html b/html-test/ref/SpuriousSuperclassConstraints.html
index b5cf64c793025dc222db1d59ec4f35cdc7c1a848..cbdc89561a03a9b72f37321c46781ddda50d31b9 100644
--- a/html-test/ref/SpuriousSuperclassConstraints.html
+++ b/html-test/ref/SpuriousSuperclassConstraints.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>SpuriousSuperclassConstraints</p
diff --git a/html-test/ref/TH.html b/html-test/ref/TH.html
index d44d57416ee5d6eb61270b523bbffb9a85406d6e..6019257147befccbdd9e714c0ea9c1015a41a0e8 100644
--- a/html-test/ref/TH.html
+++ b/html-test/ref/TH.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TH</p
diff --git a/html-test/ref/TH2.html b/html-test/ref/TH2.html
index 1b47e6409a7035188f521ba3cdfed12e6187ec5c..98f2315fdc65b0709c6237ee3d11c715c2889b7b 100644
--- a/html-test/ref/TH2.html
+++ b/html-test/ref/TH2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TH2</p
diff --git a/html-test/ref/Table.html b/html-test/ref/Table.html
index 26b0254d2e95f95f5acc46b25f0e9244a10d35e3..01f741198b8cc9c11ea6810e7b6b975f857e7278 100644
--- a/html-test/ref/Table.html
+++ b/html-test/ref/Table.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Table</p
diff --git a/html-test/ref/Test.html b/html-test/ref/Test.html
index ce2acb609b13c21752bd278edc5c4a2ad16d3fd6..10540c93104cc8d4cc280633053c53cf38dfa032 100644
--- a/html-test/ref/Test.html
+++ b/html-test/ref/Test.html
@@ -68,6 +68,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Test</p
diff --git a/html-test/ref/Threaded.html b/html-test/ref/Threaded.html
index 8391431ed7e577e903c9a47538365bf2869d7aec..4a980f9434099cf1500a403935d5fe74e8fd8750 100644
--- a/html-test/ref/Threaded.html
+++ b/html-test/ref/Threaded.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Threaded</p
diff --git a/html-test/ref/Threaded_TH.html b/html-test/ref/Threaded_TH.html
index 8850eafb719f867e9bf9500580d2eb7920640d52..52e65bb3194cbd1eeee2bb889d0b3528edda1c04 100644
--- a/html-test/ref/Threaded_TH.html
+++ b/html-test/ref/Threaded_TH.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Threaded_TH</p
diff --git a/html-test/ref/Ticket112.html b/html-test/ref/Ticket112.html
index bd596be0bfaab061a6fc24d3c9186101c4b10b23..42c9f7fb11967e078bf35879826517e736f6f826 100644
--- a/html-test/ref/Ticket112.html
+++ b/html-test/ref/Ticket112.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Ticket112</p
diff --git a/html-test/ref/Ticket61.html b/html-test/ref/Ticket61.html
index 5e384b8637a98b2943fe807b4e97e936356441f7..3b219168581fe8e0c43eeaa5ba3a79d88bc9929c 100644
--- a/html-test/ref/Ticket61.html
+++ b/html-test/ref/Ticket61.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Ticket61</p
diff --git a/html-test/ref/Ticket75.html b/html-test/ref/Ticket75.html
index 4940b6fb0619597929aa8c22cf9b50ff65a9ea8d..f9349d945507ac7be4f863e11b5e097fcc7fcb7c 100644
--- a/html-test/ref/Ticket75.html
+++ b/html-test/ref/Ticket75.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Ticket75</p
diff --git a/html-test/ref/TitledPicture.html b/html-test/ref/TitledPicture.html
index 5b936a16e943783c392ef822b2c1d2b02df7d85c..dd10e1be74208d4498abf7779788ed34df746e34 100644
--- a/html-test/ref/TitledPicture.html
+++ b/html-test/ref/TitledPicture.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TitledPicture</p
diff --git a/html-test/ref/TypeFamilies.html b/html-test/ref/TypeFamilies.html
index eeab135ec35f152ed38c1c664c73ae40de7af635..c3a5e3b515c320f183c5ffad3f37e89c99136ccc 100644
--- a/html-test/ref/TypeFamilies.html
+++ b/html-test/ref/TypeFamilies.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TypeFamilies</p
diff --git a/html-test/ref/TypeFamilies2.html b/html-test/ref/TypeFamilies2.html
index 68c272318f5ef51d5b1a51a983812d4df4fce1dd..1be5da836c16e4fa6dcb678ba06313f70531f04c 100644
--- a/html-test/ref/TypeFamilies2.html
+++ b/html-test/ref/TypeFamilies2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TypeFamilies2</p
diff --git a/html-test/ref/TypeFamilies3.html b/html-test/ref/TypeFamilies3.html
index c1573f88117a2055df6019158b7e6b359257d32c..5e2d1ea72ab47917830cdfbc03b2108f276ce73f 100644
--- a/html-test/ref/TypeFamilies3.html
+++ b/html-test/ref/TypeFamilies3.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TypeFamilies3</p
diff --git a/html-test/ref/TypeOperators.html b/html-test/ref/TypeOperators.html
index 5588e82a75b0ffc137589e39f59653f29bae54b7..ff79e6beb6234777deaa7680cb975be4d9585fb6 100644
--- a/html-test/ref/TypeOperators.html
+++ b/html-test/ref/TypeOperators.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>TypeOperators</p
diff --git a/html-test/ref/UnboxedStuff.html b/html-test/ref/UnboxedStuff.html
index 0f7ae9832c500497676605e328624c2892174d31..8bb5ad209c80bf1b8895beb4191eac84773de8f4 100644
--- a/html-test/ref/UnboxedStuff.html
+++ b/html-test/ref/UnboxedStuff.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>UnboxedStuff</p
diff --git a/html-test/ref/Unicode.html b/html-test/ref/Unicode.html
index 8f30145830d54474a05549998a9ef5511a3ac654..29ad66afdd803c734530272b269ba68de8d6045e 100644
--- a/html-test/ref/Unicode.html
+++ b/html-test/ref/Unicode.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Unicode</p
diff --git a/html-test/ref/Unicode2.html b/html-test/ref/Unicode2.html
index b789c2d7754dd7bf34b15e8076f919f5f93cacd5..d1e94dbd1bcb8b6b2a4a35d3bedf92a4b8e4df4a 100644
--- a/html-test/ref/Unicode2.html
+++ b/html-test/ref/Unicode2.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Unicode2</p
diff --git a/html-test/ref/Visible.html b/html-test/ref/Visible.html
index 0a932038ed719270eea655c1b10a96edc6cea281..c8f6b26d5b3fe81ebd549e96a22926170e88e566 100644
--- a/html-test/ref/Visible.html
+++ b/html-test/ref/Visible.html
@@ -38,6 +38,12 @@
 	    ><td
 	    >Safe-Inferred</td
 	    ></tr
+	  ><tr
+	  ><th
+	    >Language</th
+	    ><td
+	    >Haskell2010</td
+	    ></tr
 	  ></table
 	><p class="caption"
 	>Visible</p
diff --git a/html-test/src/A.hs b/html-test/src/A.hs
index 606b0865acd0605495a7f180f636c21bfddb9d4f..e23190417f7e411f5eb75e769b814fda5ad4ed4b 100644
--- a/html-test/src/A.hs
+++ b/html-test/src/A.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module A where
 
 data A = A
diff --git a/html-test/src/B.hs b/html-test/src/B.hs
index 5fd69acdbfa6cd42737cb932f142013af1cfca7f..ce7a945c6e7516ad809686aea005afc339dd2201 100644
--- a/html-test/src/B.hs
+++ b/html-test/src/B.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module B ( module A, test, reExport, X(..) ) where
 import A ( A(..), test2, reExport, X(..) )
 
diff --git a/html-test/src/Bold.hs b/html-test/src/Bold.hs
index 7ff28ef98712b22a878ea86cbf62023ba30f9ab1..91bc671504df9c652a1889b1cfaab65ff73913c5 100644
--- a/html-test/src/Bold.hs
+++ b/html-test/src/Bold.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bold where
 -- | Some __bold text__.
 --
diff --git a/html-test/src/Bug1.hs b/html-test/src/Bug1.hs
index af1ed4d3b563b260a7af93c0124a5ea03477b735..6df1b9e2d9155d022503a85228a628033f3f15f4 100644
--- a/html-test/src/Bug1.hs
+++ b/html-test/src/Bug1.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug1 where
 
 -- | We should have different anchors for constructors and types\/classes.  This
diff --git a/html-test/src/Bug1004.hs b/html-test/src/Bug1004.hs
index d789e77f747fa64984c0e72461d6a0204b91f605..f2ee5f61b18c51f1758a781ac7bdfc0a7f4e7faf 100644
--- a/html-test/src/Bug1004.hs
+++ b/html-test/src/Bug1004.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug1004 (Product(..)) where
 
 import Data.Functor.Product
diff --git a/html-test/src/Bug1033.hs b/html-test/src/Bug1033.hs
index fdf5a57e577d4258315626c93d54c27528c3ae46..4c80e672bf43b6494182d5447912555df18b5e4b 100644
--- a/html-test/src/Bug1033.hs
+++ b/html-test/src/Bug1033.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DeriveGeneric #-}
 {-# LANGUAGE StandaloneDeriving #-}
 
diff --git a/html-test/src/Bug1035.hs b/html-test/src/Bug1035.hs
index 3516c08f274f0f4000c47d4469412771f1ff475a..46a6dd1f4380a9e75a6771cc701153045bbf4832 100644
--- a/html-test/src/Bug1035.hs
+++ b/html-test/src/Bug1035.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug1035 where
 
 data Foo = Bar
diff --git a/html-test/src/Bug1050.hs b/html-test/src/Bug1050.hs
index ea293e6e118f80b21f7a361a6f9bdff75a5eca34..1fe49ab7beb5de32ea6bd83b309bd8f7bd716214 100644
--- a/html-test/src/Bug1050.hs
+++ b/html-test/src/Bug1050.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE PolyKinds #-}
 {-# LANGUAGE RankNTypes #-}
diff --git a/html-test/src/Bug1054.hs b/html-test/src/Bug1054.hs
index c699f1fb29addfb410de4b56abe14cff0a293f80..b05d79c0bac4e5914e8353b197c68998ac290fee 100644
--- a/html-test/src/Bug1054.hs
+++ b/html-test/src/Bug1054.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug1054 where
 
 -- * Header with 'foo' link
diff --git a/html-test/src/Bug1063.hs b/html-test/src/Bug1063.hs
index c6d13a1feb73691f27902f8c7203e73ad7ef0a0d..d5b1c69f0686d1f0b15b55586fc2d3777eac7d68 100644
--- a/html-test/src/Bug1063.hs
+++ b/html-test/src/Bug1063.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ConstraintKinds #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
diff --git a/html-test/src/Bug1067A.hs b/html-test/src/Bug1067A.hs
index 57ab60b07456823b49599a6a396f7beeccc37bdc..4523d838eeb7a4ac8b870342a22655aabb74a6cd 100644
--- a/html-test/src/Bug1067A.hs
+++ b/html-test/src/Bug1067A.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# language PatternSynonyms #-}
 module Bug1067A ( Foo(P) ) where
 
diff --git a/html-test/src/Bug1067B.hs b/html-test/src/Bug1067B.hs
index f1a814df0c791b735b994c7064adf5e650134384..b5ce67f6ec56e9d4fa23c6434d5cd363ae06aeb8 100644
--- a/html-test/src/Bug1067B.hs
+++ b/html-test/src/Bug1067B.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# language PatternSynonyms #-}
 module Bug1067B ( pattern P ) where
 
diff --git a/html-test/src/Bug1103.hs b/html-test/src/Bug1103.hs
index 1f387e62ef78093c33858ce0b16e72584bb37d48..c790e8c1550ed0e2592541a4026579069729f181 100644
--- a/html-test/src/Bug1103.hs
+++ b/html-test/src/Bug1103.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE PolyKinds #-}
diff --git a/html-test/src/Bug1206.hs b/html-test/src/Bug1206.hs
index 600af0e8257ee36c32e4a890601559bb5a126bbf..4901d30abdd6d4af719cdcdbadaf13c386c9053e 100644
--- a/html-test/src/Bug1206.hs
+++ b/html-test/src/Bug1206.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {- | Bug 1206
 -}
 
diff --git a/html-test/src/Bug195.hs b/html-test/src/Bug195.hs
index 14440e8d6994d51e7dd5c8a48475e910fa3c1821..304e0c2ebd98120ff97c004959b81ea1be0e8415 100644
--- a/html-test/src/Bug195.hs
+++ b/html-test/src/Bug195.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug195 where
 
 data T = A { someField :: () -- ^ Doc for someField of A
diff --git a/html-test/src/Bug2.hs b/html-test/src/Bug2.hs
index 9121922ee2e9104ddbd7c5df89105ba9fc1761fe..6dc79f46128c6af29b1cdbc5e51d7c8d075df9b0 100644
--- a/html-test/src/Bug2.hs
+++ b/html-test/src/Bug2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug2 ( x ) where
 import B
 x :: A
diff --git a/html-test/src/Bug201.hs b/html-test/src/Bug201.hs
index bf6cb9a9934e343bd8cce05b3f5cc671cbe929e7..caa92d958309df5b868f580d7018491aa4473046 100644
--- a/html-test/src/Bug201.hs
+++ b/html-test/src/Bug201.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- We test that leading whitespace gets properly dropped (or not!)
 -- from codeblocks
 module Bug201 where
diff --git a/html-test/src/Bug253.hs b/html-test/src/Bug253.hs
index 499f6cd41d4b9d66736026090df79da498824f40..29a3adc6288fe047823ef5570f66f7263a0b9314 100644
--- a/html-test/src/Bug253.hs
+++ b/html-test/src/Bug253.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | This module tests that if we're trying to link to a /qualified/
 -- identifier that's not in scope, we get an anchor as if it was a
 -- variable. Previous behaviour was to treat it as a type constructor
diff --git a/html-test/src/Bug26.hs b/html-test/src/Bug26.hs
index b0483f03ff364c9b1c3b24df029ae07936e228f2..8b9c4162c11739a514b74cf1c3164348f0ae35ae 100644
--- a/html-test/src/Bug26.hs
+++ b/html-test/src/Bug26.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | This module tests the ‘@since …’ annotation.
 --
 -- @since 1.2.3
diff --git a/html-test/src/Bug280.hs b/html-test/src/Bug280.hs
index ac27e2e5d26f293fff9d027a9d11aa91cd57ee25..d53def96b910cde9805de3b13e32163a1dc07ea1 100644
--- a/html-test/src/Bug280.hs
+++ b/html-test/src/Bug280.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-|
 Copyright: Foo,
            Bar,
diff --git a/html-test/src/Bug294.hs b/html-test/src/Bug294.hs
index 4f874705fa534a2f1a02863742739402c30c0fe3..922b8ee7dfc0b25968108e6a67e18b68c6197614 100644
--- a/html-test/src/Bug294.hs
+++ b/html-test/src/Bug294.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies, FlexibleInstances, GADTs #-}
 -- This tests that we are able to extract record selectors for
 -- associated types when the type itself is not exported. Making this
diff --git a/html-test/src/Bug298.hs b/html-test/src/Bug298.hs
index 07d6fa0ca2f6a932fe204314d48e1023cd7c8db8..7ab9d21b56cfb27d5af2995ba8967aba1295a18d 100644
--- a/html-test/src/Bug298.hs
+++ b/html-test/src/Bug298.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- We introduced a regression in 2.14.x where we don't consider
 -- identifiers with ^ as valid. We test that the regression goes away
 -- here. It's a silly typo in the parser, really. Same with ★ which is a valid
diff --git a/html-test/src/Bug3.hs b/html-test/src/Bug3.hs
index 67e57892dc6d798ee88df89537dc9b7fb74c7742..1b7e5277efb717ffefa97bf85ee9ba334fc32039 100644
--- a/html-test/src/Bug3.hs
+++ b/html-test/src/Bug3.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug3 where
 
 -- | /multi-line
diff --git a/html-test/src/Bug308.hs b/html-test/src/Bug308.hs
index 3adb37468a9950d0c8f78cd560733a10c840728d..93ecffac3b978d54dac753a61ba512cad48e325d 100644
--- a/html-test/src/Bug308.hs
+++ b/html-test/src/Bug308.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- From 2.14.x onwards we were forgetting to swallow ‘#’ as a special
 -- character resulting in broken anchors if they accured
 -- mid-paragraph. Here we check that anchors get generated as
diff --git a/html-test/src/Bug308CrossModule.hs b/html-test/src/Bug308CrossModule.hs
index 589aa69ed67bb50ad750702be9e5887ab45750c7..45c89040da69beb728d94e2e9f01cf48b081e98b 100644
--- a/html-test/src/Bug308CrossModule.hs
+++ b/html-test/src/Bug308CrossModule.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- Just like Bug308 module but here we test that referring to anchors
 -- from other modules works.
 module Bug308CrossModule where
diff --git a/html-test/src/Bug310.hs b/html-test/src/Bug310.hs
index d2492dc0ab2c9dd2ca542be7f31363d99f424d68..c54eab817be9fff5062dcc2d3481168430c996b0 100644
--- a/html-test/src/Bug310.hs
+++ b/html-test/src/Bug310.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ExplicitNamespaces #-}
 module Bug310 ( type (+) ) where
 
diff --git a/html-test/src/Bug313.hs b/html-test/src/Bug313.hs
index 90d4d3b64809ab6369e9a7e665062800d0f80b9c..c076c5b88e5dcf636a2d10c8bcf77caf32219db5 100644
--- a/html-test/src/Bug313.hs
+++ b/html-test/src/Bug313.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | The first list is incorrectly numbered as 1. 2. 1.; the second example
 -- renders fine (1. 2. 3.).
 --
diff --git a/html-test/src/Bug335.hs b/html-test/src/Bug335.hs
index c1821dd0d87cb83d54a3153fcb869f063990c959..4566830791166f9afe8585dc171e35b21634e1bf 100644
--- a/html-test/src/Bug335.hs
+++ b/html-test/src/Bug335.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- Tests for collapsable headers
 module Bug335 where
 
diff --git a/html-test/src/Bug4.hs b/html-test/src/Bug4.hs
index 425a77aa01dfc3849c9fecf95b257d1a690fba5b..3343e1b9364321240d9b309ff907d71d23a1c33d 100644
--- a/html-test/src/Bug4.hs
+++ b/html-test/src/Bug4.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug4 where
 -- | don't use apostrophe's in the wrong place's
 foo :: Int
diff --git a/html-test/src/Bug458.hs b/html-test/src/Bug458.hs
index 6a3ac9a46151c46128737a695c58502975470ce0..b0fefecf099afa12d47202ca1e01047e29dac381 100644
--- a/html-test/src/Bug458.hs
+++ b/html-test/src/Bug458.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug458 where
 
 -- | See the defn of @'⊆'@.
diff --git a/html-test/src/Bug466.hs b/html-test/src/Bug466.hs
index ec7cde2c507843c3cba01209111dff76ad521184..697f0f75260998853d680ae8ca4e58993f0fdc19 100644
--- a/html-test/src/Bug466.hs
+++ b/html-test/src/Bug466.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DataKinds, TypeFamilies, StarIsType #-}
 module Bug466 where
 
diff --git a/html-test/src/Bug546.hs b/html-test/src/Bug546.hs
index 4493b1d9c453d4c8eef204f582e9e10f94d5872c..e1df6aca7fadbbc5e60ad76d7ccb8639cf3db828 100644
--- a/html-test/src/Bug546.hs
+++ b/html-test/src/Bug546.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug546 where
 
 -- |Test:
diff --git a/html-test/src/Bug548.hs b/html-test/src/Bug548.hs
index 652d3d323c4eae2d7f102d68d5845e104596c3c1..c890a20769fdc753b06e2fe23bc476b509905aec 100644
--- a/html-test/src/Bug548.hs
+++ b/html-test/src/Bug548.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug548 (WrappedArrow(..)) where
 
 import Control.Applicative
diff --git a/html-test/src/Bug6.hs b/html-test/src/Bug6.hs
index 17411f3106a485f1d1ea9e3ae56a9dcd2546a6e0..de2874aac722021afa523b5d965d741e384920eb 100644
--- a/html-test/src/Bug6.hs
+++ b/html-test/src/Bug6.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | Exporting records.
 module Bug6( A(A), B(B), b, C(C,c1,c2), D(D,d1), E(E) ) where
 
diff --git a/html-test/src/Bug613.hs b/html-test/src/Bug613.hs
index effef6950c3b212f9120e0e83353cf43a9010adb..3bdd0ac2889f3a628fd3668ab04788967c06e5b2 100644
--- a/html-test/src/Bug613.hs
+++ b/html-test/src/Bug613.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug613  where
 
 import Prelude (Either(Left, Right))
diff --git a/html-test/src/Bug647.hs b/html-test/src/Bug647.hs
index 4143092a9cee1537b052f1845cc5d78fb79d6ddd..7f1b9544ed3558995331e347c18efb1c29b02eed 100644
--- a/html-test/src/Bug647.hs
+++ b/html-test/src/Bug647.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug647 where
 
 class Bug647 a where
diff --git a/html-test/src/Bug679.hs b/html-test/src/Bug679.hs
index 0a321ec547ad94c85fe261dc7099f7dbf01596d9..3cc2278fa0fe80e43d472bf421886adacb8e814b 100644
--- a/html-test/src/Bug679.hs
+++ b/html-test/src/Bug679.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 module Bug679 where
diff --git a/html-test/src/Bug7.hs b/html-test/src/Bug7.hs
index a07934c4f87cbc5035f4ed908bd8f932fad9c8dd..aeb7d96e022432f27bfca9d3b23d6e8e1e938eda 100644
--- a/html-test/src/Bug7.hs
+++ b/html-test/src/Bug7.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 -- | This module caused a duplicate instance in the documentation for the Foo
 -- type.
diff --git a/html-test/src/Bug745.hs b/html-test/src/Bug745.hs
index f26562c13a6bb7c7d5d64a2c3f9bf5310944dd3c..295ac59dbbdffc570b164a794fd33fc58c207fc3 100644
--- a/html-test/src/Bug745.hs
+++ b/html-test/src/Bug745.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
 
 module Bug574 where
diff --git a/html-test/src/Bug8.hs b/html-test/src/Bug8.hs
index 30afae1f68dafd45910d750b880c26d81415f8ce..1b50ce9c39e02431de17ed79909c100220336dc0 100644
--- a/html-test/src/Bug8.hs
+++ b/html-test/src/Bug8.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug8 where
 
 infix -->
diff --git a/html-test/src/Bug85.hs b/html-test/src/Bug85.hs
index e29b2662eacbc0c2d853a6f48364136f5e46fb8b..53979aee5f3a0436ea431e9182e55bdcb89e9c85 100644
--- a/html-test/src/Bug85.hs
+++ b/html-test/src/Bug85.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs, KindSignatures #-}
 module Bug85 where
 
diff --git a/html-test/src/Bug865.hs b/html-test/src/Bug865.hs
index 71a6add173088ff839ba5393d01d7e1ceb5f0a9b..86627f8efce4af877093ba5bd9a7e2611b671e32 100644
--- a/html-test/src/Bug865.hs
+++ b/html-test/src/Bug865.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug865 where
 
 -- | An emphasized link [yes /this/ is emphasized while this is
diff --git a/html-test/src/Bug923.hs b/html-test/src/Bug923.hs
index bb5bca0a92702c32bac69f94610b83dc263e6551..1d24a9f61efc74b0c8355f2da66bfbd5966307dc 100644
--- a/html-test/src/Bug923.hs
+++ b/html-test/src/Bug923.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE KindSignatures, FlexibleInstances, GADTs, DataKinds #-}
 module Bug923 where
 
diff --git a/html-test/src/Bug952.hs b/html-test/src/Bug952.hs
index 09b365e4e41d007755d2382a7bc5ef6e6d75c759..0840e46c295b8507a28697b2c9fb86b21ffd5290 100644
--- a/html-test/src/Bug952.hs
+++ b/html-test/src/Bug952.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug952 where
 
 -- | See 'case', 'of', '--' compared to 'Q.case', 'Q.of', 'Q.--'
diff --git a/html-test/src/Bug953.hs b/html-test/src/Bug953.hs
index 63f2c45a109698f3856bfc01ca09b23a9358d8e0..4ff3e8ae33a9cf41de9bb25f6bd53e33a0373c64 100644
--- a/html-test/src/Bug953.hs
+++ b/html-test/src/Bug953.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bug953 where
 
 {- | A foo
diff --git a/html-test/src/Bug975.hs b/html-test/src/Bug975.hs
index 97ebabda9adb978762313ecda9e1c47d016ac1d7..e55385c542a56a5734c999f4c0b80faae313a523 100644
--- a/html-test/src/Bug975.hs
+++ b/html-test/src/Bug975.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ExplicitForAll #-}
 module Bug973 where
 
diff --git a/html-test/src/BugDeprecated.hs b/html-test/src/BugDeprecated.hs
index 7741786fad09c5be2725bb13ab36cf6f0fc34080..9dfef1768344253f68b8470df8cc2fa8b7cc8336 100644
--- a/html-test/src/BugDeprecated.hs
+++ b/html-test/src/BugDeprecated.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module BugDeprecated where
 
 foo :: Int
diff --git a/html-test/src/BugExportHeadings.hs b/html-test/src/BugExportHeadings.hs
index a5493a08494fc94479d394c00178f144feee8e74..b664a4482980a65b0583b72f77a569c29f63ae12 100644
--- a/html-test/src/BugExportHeadings.hs
+++ b/html-test/src/BugExportHeadings.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- test for #192
 module BugExportHeadings (
 -- * Foo
diff --git a/html-test/src/Bugs.hs b/html-test/src/Bugs.hs
index e60bbe8fee38906c56f0a8c66d287a501b7d45b7..aed716a427b9444a2775caafb80f0d0e151a7939 100644
--- a/html-test/src/Bugs.hs
+++ b/html-test/src/Bugs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Bugs where
 
 data A a = A a (a -> Int)
diff --git a/html-test/src/BundledPatterns.hs b/html-test/src/BundledPatterns.hs
index 443e64fa8f8ee1141817b87b8009ef7d0be93008..420068ac0c9cbedb3204b35b2da836a697e33c92 100644
--- a/html-test/src/BundledPatterns.hs
+++ b/html-test/src/BundledPatterns.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DataKinds, GADTs, KindSignatures, PatternSynonyms, TypeOperators,
              ViewPatterns #-}
 module BundledPatterns (Vec(Nil,(:>)), RTree (LR,BR)) where
diff --git a/html-test/src/BundledPatterns2.hs b/html-test/src/BundledPatterns2.hs
index 5e9a83a7626ea355798e9f8f0779f40dab573ed7..c4123535581361506fbb4fefba8f00dbae64edea 100644
--- a/html-test/src/BundledPatterns2.hs
+++ b/html-test/src/BundledPatterns2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DataKinds, GADTs, KindSignatures, PatternSynonyms, TypeOperators,
              ViewPatterns #-}
 module BundledPatterns2 (Vec((:>), Empty), RTree(..)) where
diff --git a/html-test/src/ConstructorArgs.hs b/html-test/src/ConstructorArgs.hs
index 6b0da7119809a1b5ff4547eef9e33465366de6f9..c3b848c39b5bf7fcf652c2f20fec5a9b4e7bf1bd 100644
--- a/html-test/src/ConstructorArgs.hs
+++ b/html-test/src/ConstructorArgs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs, PatternSynonyms #-}
 
 module ConstructorArgs (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where
diff --git a/html-test/src/ConstructorPatternExport.hs b/html-test/src/ConstructorPatternExport.hs
index 7897b4bcfd2bfbf4b76ed6b1a7d490c359f59dc8..aa2971d6f83e7bd8c30f87da2adca80d743c42f6 100644
--- a/html-test/src/ConstructorPatternExport.hs
+++ b/html-test/src/ConstructorPatternExport.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE PatternSynonyms #-}
 {-# LANGUAGE ExistentialQuantification #-}
 {-# LANGUAGE GADTs #-}
diff --git a/html-test/src/DefaultAssociatedTypes.hs b/html-test/src/DefaultAssociatedTypes.hs
index 6ad197d3990759339f0f17d930488fff2b2ce8b9..340742d363ad354ae54c4d4a2a06b4d01a9e908c 100644
--- a/html-test/src/DefaultAssociatedTypes.hs
+++ b/html-test/src/DefaultAssociatedTypes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DefaultSignatures, TypeFamilies #-}
 
 module DefaultAssociatedTypes where
diff --git a/html-test/src/DefaultSignatures.hs b/html-test/src/DefaultSignatures.hs
index 52d68a96091fc4cce2ec4ba7be13f8c30480c4da..1b1b8257011606b8e08b20be84d9f931bf7c7108 100644
--- a/html-test/src/DefaultSignatures.hs
+++ b/html-test/src/DefaultSignatures.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DefaultSignatures #-}
 
 module DefaultSignatures where
diff --git a/html-test/src/DeprecatedClass.hs b/html-test/src/DeprecatedClass.hs
index 018904abbd4faf81c98509cf60d361849a11c475..357f64e495a6494c6c8b7b2129b17e480b9a297f 100644
--- a/html-test/src/DeprecatedClass.hs
+++ b/html-test/src/DeprecatedClass.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedClass where
 
 -- | some class
diff --git a/html-test/src/DeprecatedData.hs b/html-test/src/DeprecatedData.hs
index c40ba122c14558e89d167d9b22b236bd174193bb..f23241623ade1682fe607177a6cc917bb6132b55 100644
--- a/html-test/src/DeprecatedData.hs
+++ b/html-test/src/DeprecatedData.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 module DeprecatedData where
 
diff --git a/html-test/src/DeprecatedFunction.hs b/html-test/src/DeprecatedFunction.hs
index 8d626435aaa8e2035b38a1ff80715fe3381317fc..2c6418d396baeb2b591e9247e4fdaa9cb267f4c5 100644
--- a/html-test/src/DeprecatedFunction.hs
+++ b/html-test/src/DeprecatedFunction.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedFunction where
 
 -- | some documentation for foo
diff --git a/html-test/src/DeprecatedFunction2.hs b/html-test/src/DeprecatedFunction2.hs
index bdbbf95c4240f7c3e4ddb528e98c31262fd3ea66..fb4193f2bc7b2804a10bf9814ec5da0e666ffc97 100644
--- a/html-test/src/DeprecatedFunction2.hs
+++ b/html-test/src/DeprecatedFunction2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedFunction2 where
 
 
diff --git a/html-test/src/DeprecatedFunction3.hs b/html-test/src/DeprecatedFunction3.hs
index ca719bda2f9e606f4ebbe70a1d92dab79202bf15..4a286e0ad83e0df4dc3513e98a9dc3eb003ac34e 100644
--- a/html-test/src/DeprecatedFunction3.hs
+++ b/html-test/src/DeprecatedFunction3.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedFunction3 where
 
 
diff --git a/html-test/src/DeprecatedModule.hs b/html-test/src/DeprecatedModule.hs
index 369dba4fff7d3869a4b614b4b6c91e6257d70c15..179b589945be63e9fcc24cce387ff00ef8381079 100644
--- a/html-test/src/DeprecatedModule.hs
+++ b/html-test/src/DeprecatedModule.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | Documentation for "DeprecatedModule".
 module DeprecatedModule {-# DEPRECATED "Use \"Foo\" instead" #-} where
 
diff --git a/html-test/src/DeprecatedModule2.hs b/html-test/src/DeprecatedModule2.hs
index 9418529755247b7e4b975e909c1cb8a12d958935..ccec1be7c626db5f03c495f1df5e4e479a5becb8 100644
--- a/html-test/src/DeprecatedModule2.hs
+++ b/html-test/src/DeprecatedModule2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedModule2 {-# DEPRECATED "Use Foo instead" #-} where
 
 foo :: Int
diff --git a/html-test/src/DeprecatedNewtype.hs b/html-test/src/DeprecatedNewtype.hs
index 254f1f550d09e868a3aab95927e416e5c9e410b4..6aeead44172496dddad9090245195bb079f24f57 100644
--- a/html-test/src/DeprecatedNewtype.hs
+++ b/html-test/src/DeprecatedNewtype.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedNewtype where
 
 -- | some documentation
diff --git a/html-test/src/DeprecatedReExport.hs b/html-test/src/DeprecatedReExport.hs
index f851e2ff73207fe3fb5cdd86b888fbba221c9c5c..061c9c2736835a49887892baa8a91530a9a427f1 100644
--- a/html-test/src/DeprecatedReExport.hs
+++ b/html-test/src/DeprecatedReExport.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- |
 -- What is tested here:
 --
diff --git a/html-test/src/DeprecatedRecord.hs b/html-test/src/DeprecatedRecord.hs
index d44499e7b97972ee1af8a97ae329a93ae4a1f123..9fe0240d57ce63e3a93e941860d5f877d8af38de 100644
--- a/html-test/src/DeprecatedRecord.hs
+++ b/html-test/src/DeprecatedRecord.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module DeprecatedRecord where
 
 -- | type Foo
diff --git a/html-test/src/DeprecatedTypeFamily.hs b/html-test/src/DeprecatedTypeFamily.hs
index 70473bb80330404db96d4f39066eb0ecef68c27c..3d94cace9d9db2ed64354529bbc481219294cc3d 100644
--- a/html-test/src/DeprecatedTypeFamily.hs
+++ b/html-test/src/DeprecatedTypeFamily.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 module DeprecatedTypeFamily where
 
diff --git a/html-test/src/DeprecatedTypeSynonym.hs b/html-test/src/DeprecatedTypeSynonym.hs
index 34df47da2994b58272a03a057812e60aa6b7f90d..05fb9bdc713209b32af9355554c87c3f5a860506 100644
--- a/html-test/src/DeprecatedTypeSynonym.hs
+++ b/html-test/src/DeprecatedTypeSynonym.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 
 module DeprecatedTypeSynonym where
 
diff --git a/html-test/src/DuplicateRecordFields.hs b/html-test/src/DuplicateRecordFields.hs
index 2cf9ff43ebc4e9c8bbaa84579330a626681e3f16..594417508093fe0b4749dd99673d2ef34203ccfb 100644
--- a/html-test/src/DuplicateRecordFields.hs
+++ b/html-test/src/DuplicateRecordFields.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DuplicateRecordFields #-}
 module DuplicateRecordFields (RawReplay(..)) where
 
diff --git a/html-test/src/Examples.hs b/html-test/src/Examples.hs
index c8c450f1a3f7c62ac2f56fe104d95974170e0f23..b518ea7011a5245ebc6cbb44cc5e7e0415178f8e 100644
--- a/html-test/src/Examples.hs
+++ b/html-test/src/Examples.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Examples where
 
 -- | Fibonacci number of given 'Integer'.
diff --git a/html-test/src/Extensions.hs b/html-test/src/Extensions.hs
index 61eac2199fa74479665c12d5c71e531f5c27b3c4..bbaa6395906f90bbcd297dd6ff3789afde8272fb 100644
--- a/html-test/src/Extensions.hs
+++ b/html-test/src/Extensions.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE Haskell2010, ExplicitForAll, MonomorphismRestriction #-}
 {-# OPTIONS_HADDOCK show-extensions #-}
 module Extensions where
diff --git a/html-test/src/FunArgs.hs b/html-test/src/FunArgs.hs
index e20bcda72a597a244f47a2eeacffff6855edaeb9..9d7c19dc454c78825d38e7b3f5c3ace2865014b0 100644
--- a/html-test/src/FunArgs.hs
+++ b/html-test/src/FunArgs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE RankNTypes, DataKinds, TypeFamilies #-}
 module FunArgs where
 
diff --git a/html-test/src/GADTRecords.hs b/html-test/src/GADTRecords.hs
index dcbbb870988fdaab8039a9d9e6841cd564e63ac8..015027d2bb7ccf87046db070486324046ae75d8a 100644
--- a/html-test/src/GADTRecords.hs
+++ b/html-test/src/GADTRecords.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs #-}
 module GADTRecords (H1(..)) where
 
diff --git a/html-test/src/GadtConstructorArgs.hs b/html-test/src/GadtConstructorArgs.hs
index 79ffb4d3972f2dbabdcaf017853217c11ff20ad3..6d742bd7e2504ae2c4d1984e331c67f5becb6a4f 100644
--- a/html-test/src/GadtConstructorArgs.hs
+++ b/html-test/src/GadtConstructorArgs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs, PatternSynonyms #-}
 
 module GadtConstructorArgs (Boo(..)) where
diff --git a/html-test/src/Hash.hs b/html-test/src/Hash.hs
index 1eb8af5b847e1367f6e4e464d0eeed26f47bc2ca..ce40fdd3fb44cf34547b25671ab27a86437a09c9 100644
--- a/html-test/src/Hash.hs
+++ b/html-test/src/Hash.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {- |
   Implementation of fixed-size hash tables, with a type
   class for constructing hash values for structured types.
diff --git a/html-test/src/Hidden.hs b/html-test/src/Hidden.hs
index 896da64866a05dcbfece8c362f00760976f99fde..2b694e863ab496a3442fb0b1ed0cd759d7a108f7 100644
--- a/html-test/src/Hidden.hs
+++ b/html-test/src/Hidden.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# OPTIONS_HADDOCK hide #-}
 
 module Hidden where
diff --git a/html-test/src/HiddenInstances.hs b/html-test/src/HiddenInstances.hs
index 99a6c2fd41ebc91774b004d402b4cb374e09765f..a912409813be9d28f7cb61a2145ecccef93f5751 100644
--- a/html-test/src/HiddenInstances.hs
+++ b/html-test/src/HiddenInstances.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- http://trac.haskell.org/haddock/ticket/37
 module HiddenInstances (VisibleClass, VisibleData) where
 
diff --git a/html-test/src/HiddenInstancesA.hs b/html-test/src/HiddenInstancesA.hs
index f1775208669dd85d62f477a31783bc590003fee0..8879868c1801d7b8dfd5581f5045cbdf659f6380 100644
--- a/html-test/src/HiddenInstancesA.hs
+++ b/html-test/src/HiddenInstancesA.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# OPTIONS_HADDOCK hide #-}
 module HiddenInstancesA where
 
diff --git a/html-test/src/HiddenInstancesB.hs b/html-test/src/HiddenInstancesB.hs
index eabf063774bbda92cfc97919eb12e1ae595af8d3..0def0ecce1b64cd1bd09b794c84676e223dc7e0b 100644
--- a/html-test/src/HiddenInstancesB.hs
+++ b/html-test/src/HiddenInstancesB.hs
@@ -1,2 +1,3 @@
+{-# LANGUAGE Haskell2010 #-}
 module HiddenInstancesB (Foo, Bar) where
 import HiddenInstancesA
diff --git a/html-test/src/Hyperlinks.hs b/html-test/src/Hyperlinks.hs
index 34e64448e80e9229d0ae6b6c07a1de1e4bebf986..f64a5bb1efda09ed2fee409f81eeff4669f7a884 100644
--- a/html-test/src/Hyperlinks.hs
+++ b/html-test/src/Hyperlinks.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Hyperlinks where
 
 -- |
diff --git a/html-test/src/Identifiers.hs b/html-test/src/Identifiers.hs
index 75f1210941150a65e600724b9bf99f874c63acb7..13ee3b82b4ab6e05c44266830da222caf602c419 100644
--- a/html-test/src/Identifiers.hs
+++ b/html-test/src/Identifiers.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeOperators #-}
 module Identifiers where
 
diff --git a/html-test/src/IgnoreExports.hs b/html-test/src/IgnoreExports.hs
index edb7c4c1c0c559d61c6babc40e24ac21739681b4..2016d3d5b59aa91bcc7a982072dfe0d66f94afff 100644
--- a/html-test/src/IgnoreExports.hs
+++ b/html-test/src/IgnoreExports.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# OPTIONS_HADDOCK ignore-exports #-}
 module IgnoreExports (Foo, foo) where
 
diff --git a/html-test/src/ImplicitParams.hs b/html-test/src/ImplicitParams.hs
index 3ca9157b0a12619789164995fdc61b9dbe77b975..8635b2a4e892f470418194ad6262df5c71e1649d 100644
--- a/html-test/src/ImplicitParams.hs
+++ b/html-test/src/ImplicitParams.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ImplicitParams, RankNTypes #-}
 module ImplicitParams where
 
diff --git a/html-test/src/Instances.hs b/html-test/src/Instances.hs
index 545c8534bd20479e9de0012e3e21c70177a04dfa..e9537a920050bb0e3f39467a511667600108ab3f 100644
--- a/html-test/src/Instances.hs
+++ b/html-test/src/Instances.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE FlexibleContexts #-}
diff --git a/html-test/src/LinearTypes.hs b/html-test/src/LinearTypes.hs
index cb4eb138bd40744369b58c6eb73e7d8fdf0ff098..c4f9c84fd6347e48de3eff12588ce2886166d5cb 100644
--- a/html-test/src/LinearTypes.hs
+++ b/html-test/src/LinearTypes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE LinearTypes #-}
 module LinearTypes where
 
diff --git a/html-test/src/Math.hs b/html-test/src/Math.hs
index 75bc513eecf1f5f404df3d461720567bc681f674..375dbc2da09ebe5a9bc7ab42c65e57bc4bff069c 100644
--- a/html-test/src/Math.hs
+++ b/html-test/src/Math.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | Math (display) for 'normalDensity'
 --
 -- \[
diff --git a/html-test/src/Minimal.hs b/html-test/src/Minimal.hs
index 9df03cca255b1631ca51e8684d9de2b004ac25a7..ec275aeca1cc6611ceb3f2b90575271df226305d 100644
--- a/html-test/src/Minimal.hs
+++ b/html-test/src/Minimal.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | This tests the new MINIMAL pragma present in GHC 7.8
 module Minimal
   ( Foo(..)
diff --git a/html-test/src/ModuleWithWarning.hs b/html-test/src/ModuleWithWarning.hs
index e64d9d7e5e924c9a029b596f9b4e90135d7cdf37..710589bfcabcb2b1821a3520948cc062aa3636e2 100644
--- a/html-test/src/ModuleWithWarning.hs
+++ b/html-test/src/ModuleWithWarning.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | Documentation for "ModuleWithWarning".
 module ModuleWithWarning {-# WARNING "This is an unstable interface.  Prefer functions from \"Prelude\" instead!" #-} where
 
diff --git a/html-test/src/NamedDoc.hs b/html-test/src/NamedDoc.hs
index 7c04ba72d92f9c03037d64b8411775604f6b22ed..8ac40921dca3c6715863a9b7264ce4f30e3f6034 100644
--- a/html-test/src/NamedDoc.hs
+++ b/html-test/src/NamedDoc.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module NamedDoc where
 
 -- $foo bar
diff --git a/html-test/src/NamespacedIdentifiers.hs b/html-test/src/NamespacedIdentifiers.hs
index 6f59d24740629531f0b48aa1c63250662490f498..38fb710138044bbfb03788a91e844d5a90715f1c 100644
--- a/html-test/src/NamespacedIdentifiers.hs
+++ b/html-test/src/NamespacedIdentifiers.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module NamespacedIdentifiers where
 
 -- | A link to:
diff --git a/html-test/src/Nesting.hs b/html-test/src/Nesting.hs
index f88be87df9a1e0d6b334b7c55cf19e99642d0c54..fa45e11b5f8cdcf2103b478b842d38283f8ff224 100644
--- a/html-test/src/Nesting.hs
+++ b/html-test/src/Nesting.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Nesting where
 
 {-|
diff --git a/html-test/src/NoLayout.hs b/html-test/src/NoLayout.hs
index 19b38b1da657c475e94edd3758761ac86cca1136..e07470a3228f16afd8808efb6606fa5d300836a9 100644
--- a/html-test/src/NoLayout.hs
+++ b/html-test/src/NoLayout.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 
 -- Haddock comments are parsed as separate declarations so we
 -- need to insert a ';' when using them with explicit layout.
diff --git a/html-test/src/NonGreedy.hs b/html-test/src/NonGreedy.hs
index f51b55f56f102fef43455a60a7ff68873002ac45..b89b0723d6de916ea53bc34744ce3905d5d1fe9d 100644
--- a/html-test/src/NonGreedy.hs
+++ b/html-test/src/NonGreedy.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module NonGreedy where
 
 -- | <url1> <url2>
diff --git a/html-test/src/Operators.hs b/html-test/src/Operators.hs
index 0b633c3fab0370477e7b3efa997ff82fec2449f8..c303c8bd06bf296948a621bdf21672a7fcbf6535 100644
--- a/html-test/src/Operators.hs
+++ b/html-test/src/Operators.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE PatternSynonyms, TypeOperators, TypeFamilies, MultiParamTypeClasses, GADTs #-}
 {-# LANGUAGE FunctionalDependencies #-}
 
diff --git a/html-test/src/OrphanInstances.hs b/html-test/src/OrphanInstances.hs
index e50327eebd9a07f4dff15d0d4a63dbb904dcae97..e7a24c45a9b6bb11fca57ceab3ffdc98248c88df 100644
--- a/html-test/src/OrphanInstances.hs
+++ b/html-test/src/OrphanInstances.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module OrphanInstances where
 
 import OrphanInstancesType
diff --git a/html-test/src/OrphanInstancesClass.hs b/html-test/src/OrphanInstancesClass.hs
index 4b51acfcbd62c278b90b8263c3d57d6042f97f87..d5cbf708e4d4a2222c63d933ecfd39225b8aa0f9 100644
--- a/html-test/src/OrphanInstancesClass.hs
+++ b/html-test/src/OrphanInstancesClass.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module OrphanInstancesClass (AClass(..)) where
 
 class AClass a where
diff --git a/html-test/src/OrphanInstancesType.hs b/html-test/src/OrphanInstancesType.hs
index b3c3145e3df8ec389b9bc9d1576916167e5698b9..8a48b93ea945c00c9adca79baaf0ac8595499aec 100644
--- a/html-test/src/OrphanInstancesType.hs
+++ b/html-test/src/OrphanInstancesType.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module OrphanInstancesType (AType(..)) where
 
 data AType = AType Int
diff --git a/html-test/src/PR643.hs b/html-test/src/PR643.hs
index 565e5b57b5590afa0cf6f86a94fe31a5d1bf9e8b..a6ad81eed8b0dc56710e4e4391d7e4a8bf13e20c 100644
--- a/html-test/src/PR643.hs
+++ b/html-test/src/PR643.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module PR643 (test) where
 
 import PR643_1
diff --git a/html-test/src/PR643_1.hs b/html-test/src/PR643_1.hs
index ecd0db94494bead9a5cb4f116c9282a695492058..67dabee3c4a8aa948e5af95e97a39a661dce65d2 100644
--- a/html-test/src/PR643_1.hs
+++ b/html-test/src/PR643_1.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module PR643_1 where
 
 infixr 5 `test`
diff --git a/html-test/src/PatternSyns.hs b/html-test/src/PatternSyns.hs
index bf0f78488f7a53fea2f79252921fa219ce66a88c..e0da6d6b37188f1fa08b3c9de52054d478191009 100644
--- a/html-test/src/PatternSyns.hs
+++ b/html-test/src/PatternSyns.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE ExistentialQuantification, PatternSynonyms, PolyKinds, TypeOperators #-}
 
 -- | Testing some pattern synonyms
diff --git a/html-test/src/PromotedTypes.hs b/html-test/src/PromotedTypes.hs
index ae3ad37536eeca3dba6391ec5aae9c73b4b3258d..624f9d5ad8dd471d41851f4e3a5dbf2f5e62d642 100644
--- a/html-test/src/PromotedTypes.hs
+++ b/html-test/src/PromotedTypes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DataKinds #-}
 {-# LANGUAGE GADTs #-}
 {-# LANGUAGE KindSignatures #-}
diff --git a/html-test/src/Properties.hs b/html-test/src/Properties.hs
index 05930ece4c964b6087c1a39a08b641cbcdb88f4a..8b1409f3a7e309203d782f0b31612f561a55a0b9 100644
--- a/html-test/src/Properties.hs
+++ b/html-test/src/Properties.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Properties where
 
 -- | Fibonacci number of given 'Integer'.
diff --git a/html-test/src/PruneWithWarning.hs b/html-test/src/PruneWithWarning.hs
index bfa55ea2e71d796e1ca5cb2a725f9257df230117..c2f746f00acdc243145b07dbe426a08d7978f63a 100644
--- a/html-test/src/PruneWithWarning.hs
+++ b/html-test/src/PruneWithWarning.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# OPTIONS_HADDOCK prune #-}
 -- |
 -- What is tested here:
diff --git a/html-test/src/QuantifiedConstraints.hs b/html-test/src/QuantifiedConstraints.hs
index 82dd81e5678621e8671eee9a079a0a383713c79d..4f96b322a6ee8751529f97a5a8223cb70d2c6e90 100644
--- a/html-test/src/QuantifiedConstraints.hs
+++ b/html-test/src/QuantifiedConstraints.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE QuantifiedConstraints #-}
 module QuantifiedConstraints where
 
diff --git a/html-test/src/QuasiExpr.hs b/html-test/src/QuasiExpr.hs
index 970759ba713708d8840e37568b899b10349c4549..d81fcf8b05585076b2cfc6bf266f976bf522b579 100644
--- a/html-test/src/QuasiExpr.hs
+++ b/html-test/src/QuasiExpr.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 -- Used by QuasiQuote. Example taken from the GHC documentation.
diff --git a/html-test/src/QuasiQuote.hs b/html-test/src/QuasiQuote.hs
index 06762cf9c1346d605841c0fe07491d20d41d012e..fe900eb8256da4f10258ef5c10f6624ff1b0df8e 100644
--- a/html-test/src/QuasiQuote.hs
+++ b/html-test/src/QuasiQuote.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
 
 -- example taken from the GHC documentation
diff --git a/html-test/src/SectionLabels.hs b/html-test/src/SectionLabels.hs
index 560bafa4a6daa3c83db605d1cf6cec5b5649bd93..0017bd72353ef367b98e06b0cf840fc80a11caa6 100644
--- a/html-test/src/SectionLabels.hs
+++ b/html-test/src/SectionLabels.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module SectionLabels
   (
     -- * Section heading#custom#
diff --git a/html-test/src/SpuriousSuperclassConstraints.hs b/html-test/src/SpuriousSuperclassConstraints.hs
index 3e2309452102e62351340f524193a5b1aa1a8e68..cb2049415a672cd97aca84458bf07b62a7b6d674 100644
--- a/html-test/src/SpuriousSuperclassConstraints.hs
+++ b/html-test/src/SpuriousSuperclassConstraints.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE EmptyDataDecls, KindSignatures #-}
 -- |
 -- What is tested here:
diff --git a/html-test/src/TH.hs b/html-test/src/TH.hs
index f8178bcb392f0302d964b4c409c577e33e4b56a1..2692ae427606fa5338c27792fc972958057a2816 100644
--- a/html-test/src/TH.hs
+++ b/html-test/src/TH.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 module TH where
diff --git a/html-test/src/TH2.hs b/html-test/src/TH2.hs
index ea85e5478206e5a26c447cbff1f0452c7892c6b1..f878b1e0162f29f7b03e961835a7c607fbbc508c 100644
--- a/html-test/src/TH2.hs
+++ b/html-test/src/TH2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 module TH2 where
diff --git a/html-test/src/Table.hs b/html-test/src/Table.hs
index 2cf0c6625261fbb401a5d548ffaff2283e496e9a..4ffbc9b350d5feef38f8da4b6437e0cc039a10b7 100644
--- a/html-test/src/Table.hs
+++ b/html-test/src/Table.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | This tests the table markup
 module Table
   ( tableWithHeader
diff --git a/html-test/src/Test.hs b/html-test/src/Test.hs
index e94cc4146c8af83c7f673e895ede807a11df6adf..a809f337af3f4e9f293b0859f2ac8c2f0119d657 100644
--- a/html-test/src/Test.hs
+++ b/html-test/src/Test.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Test
diff --git a/html-test/src/Threaded.hs b/html-test/src/Threaded.hs
index 7f3073adfa23f9123eac8c4bb96fc338c31f6ce0..afe38c27431bb20a35552813d8d1a47c04a96c06 100644
--- a/html-test/src/Threaded.hs
+++ b/html-test/src/Threaded.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 -- | Ensures haddock built with @-threaded@.
diff --git a/html-test/src/Threaded_TH.hs b/html-test/src/Threaded_TH.hs
index 53e5a39925b2e34ab9beec14d1b54e093e6d5223..8179f09050bb1f992f67eafd8c99baafb1941261 100644
--- a/html-test/src/Threaded_TH.hs
+++ b/html-test/src/Threaded_TH.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- | Imported by 'Threaded', since a TH splice can't be used in the
 -- module where it is defined.
 module Threaded_TH where
diff --git a/html-test/src/Ticket112.hs b/html-test/src/Ticket112.hs
index c9cd5117004287ff197facdfcebf0942216d37f8..db7f3ed06e3c42a56488d49603d3ec24c91dbca2 100644
--- a/html-test/src/Ticket112.hs
+++ b/html-test/src/Ticket112.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE MagicHash #-}
 
 module Ticket112 where
diff --git a/html-test/src/Ticket61.hs b/html-test/src/Ticket61.hs
index 26ca287f14dd94445e323a2f3e8bf425d10260c7..c80e1c75597350f362ae3b027d71d130d4f18b6a 100644
--- a/html-test/src/Ticket61.hs
+++ b/html-test/src/Ticket61.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Ticket61 (module Ticket61_Hidden) where
 
 import Ticket61_Hidden
diff --git a/html-test/src/Ticket61_Hidden.hs b/html-test/src/Ticket61_Hidden.hs
index 583c10cd732a99b0d8fef909fae86b7b069090b7..f3654cfcffeb4127b7ec17ef0b0825b28cb8cb93 100644
--- a/html-test/src/Ticket61_Hidden.hs
+++ b/html-test/src/Ticket61_Hidden.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# OPTIONS_HADDOCK hide #-}
 
 module Ticket61_Hidden where
diff --git a/html-test/src/Ticket75.hs b/html-test/src/Ticket75.hs
index 5fc704d615d947c74c3ee90818b59b1d4e5cd3a8..743ffd607f4a15217601bb675630ee23cea19c52 100644
--- a/html-test/src/Ticket75.hs
+++ b/html-test/src/Ticket75.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeOperators #-}
 module Ticket75 where
 
diff --git a/html-test/src/TitledPicture.hs b/html-test/src/TitledPicture.hs
index 7029d98ad87164512595b3983f6dc10b3218e7ee..69d44397c9338e529d592ff387adb1754298adea 100644
--- a/html-test/src/TitledPicture.hs
+++ b/html-test/src/TitledPicture.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module TitledPicture where
 
 -- | Picture for 'foo' without a title <<bar>>
diff --git a/html-test/src/TypeFamilies.hs b/html-test/src/TypeFamilies.hs
index a79d503e7e943a4ea19904d7362e1e03f72f62a6..d759af4fb2816e0b85cdfcfdf9d3555c52d05e76 100644
--- a/html-test/src/TypeFamilies.hs
+++ b/html-test/src/TypeFamilies.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies, UndecidableInstances, PolyKinds, TypeOperators, DataKinds, MultiParamTypeClasses, GADTs #-}
 
 -- | Doc for: module TypeFamilies
diff --git a/html-test/src/TypeFamilies2.hs b/html-test/src/TypeFamilies2.hs
index b66acbfa096c1fabbd5bf00af967126f615aec96..c12113194915d948561046640023c57cc2ee3854 100644
--- a/html-test/src/TypeFamilies2.hs
+++ b/html-test/src/TypeFamilies2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 -- This tests what happens if we have unexported types
 -- in type instances. The expected behaviour is
diff --git a/html-test/src/TypeFamilies3.hs b/html-test/src/TypeFamilies3.hs
index bde05fb8cf7d1ff7cac7500d458485bd5b0933e8..80279e365876fc649e66aac34954e80a142fd17c 100644
--- a/html-test/src/TypeFamilies3.hs
+++ b/html-test/src/TypeFamilies3.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 
 module TypeFamilies3 where
diff --git a/html-test/src/TypeOperators.hs b/html-test/src/TypeOperators.hs
index e69e89cb55a8d756724dd174614073f91284c9c9..e82d065d9a82d6184409c16550661c12dd5764f3 100644
--- a/html-test/src/TypeOperators.hs
+++ b/html-test/src/TypeOperators.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeOperators, GADTs, MultiParamTypeClasses, FlexibleContexts #-}
 module TypeOperators where
 
diff --git a/html-test/src/UnboxedStuff.hs b/html-test/src/UnboxedStuff.hs
index bd1b1302dacd76359a783ab16747ecbc8ea62036..dfeb7429b6ff00b92dd5e37bfaab92bc11119e19 100644
--- a/html-test/src/UnboxedStuff.hs
+++ b/html-test/src/UnboxedStuff.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE UnboxedSums, UnboxedTuples #-}
 module UnboxedStuff where
 
diff --git a/html-test/src/Unicode.hs b/html-test/src/Unicode.hs
index d5bbf445db219c42688b665d2bbeef8f2d50e56e..ecd195cfa060b83c72e36cadfae8e16f5a771b37 100644
--- a/html-test/src/Unicode.hs
+++ b/html-test/src/Unicode.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Unicode where
 
 -- | γλώσσα
diff --git a/html-test/src/Unicode2.hs b/html-test/src/Unicode2.hs
index ca6b18bacffb21f3bef854d4433f416c4e642822..19925a4f2f93c16b4ec0ab6201c66b3f52e4a934 100644
--- a/html-test/src/Unicode2.hs
+++ b/html-test/src/Unicode2.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Unicode2 where
 
 -- | All of the following work with a unicode character ü:
diff --git a/html-test/src/Visible.hs b/html-test/src/Visible.hs
index cad719315f1f061c051338ce0a3cca03609719b6..9440aeef09b7559eee4ef422cb377e03fd35ec68 100644
--- a/html-test/src/Visible.hs
+++ b/html-test/src/Visible.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Visible where
 visible :: Int -> Int
 visible a = a
diff --git a/hypsrc-test/ref/src/Bug1091.html b/hypsrc-test/ref/src/Bug1091.html
index a9c7d163380e27f70b3285e555d8ae870b840a54..3aad9cc83d0ca358f4f83a79487b01fcb8455ed3 100644
--- a/hypsrc-test/ref/src/Bug1091.html
+++ b/hypsrc-test/ref/src/Bug1091.html
@@ -7,12 +7,19 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE CPP #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE CPP #-}</span
+      ><span
+      >
+</span
+      ><span id="line-3"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
diff --git a/hypsrc-test/ref/src/CPP.html b/hypsrc-test/ref/src/CPP.html
index 719be7f8df3a381a20d2abfcb54aa6085517cba6..41cb8f8c5cdd286d72520acf57494f2c894059ff 100644
--- a/hypsrc-test/ref/src/CPP.html
+++ b/hypsrc-test/ref/src/CPP.html
@@ -7,12 +7,19 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE CPP #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE CPP #-}</span
+      ><span
+      >
+</span
+      ><span id="line-3"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -31,7 +38,7 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span class="annot"
       ><a href="CPP.html#foo"
@@ -52,7 +59,7 @@
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span id="foo"
       ><span class="annot"
@@ -92,7 +99,7 @@
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span class="annot"
       ><a href="CPP.html#bar"
@@ -113,7 +120,7 @@
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id="bar"
       ><span class="annot"
@@ -147,26 +154,26 @@
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span class="hs-comment"
       >-- &quot; single quotes are fine in line comments</span
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span class="hs-comment"
       >-- {- unclosed block comments are fine in line comments</span
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span class="hs-comment"
       >-- Multiline CPP is also fine</span
@@ -178,7 +185,7 @@
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span class="annot"
       ><a href="CPP.html#baz"
@@ -199,7 +206,7 @@
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span id="baz"
       ><span class="annot"
@@ -228,7 +235,7 @@
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Classes.html b/hypsrc-test/ref/src/Classes.html
index 3477d89d2b8543acb301ebde447b473b1a9fef22..f4652c91159998b5f876ffca23d547ee037d568a 100644
--- a/hypsrc-test/ref/src/Classes.html
+++ b/hypsrc-test/ref/src/Classes.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,17 +26,17 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="hs-keyword"
       >class</span
@@ -60,7 +67,7 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >    </span
@@ -97,7 +104,7 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >    </span
@@ -148,12 +155,12 @@
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span class="hs-keyword"
       >instance</span
@@ -178,7 +185,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >    </span
@@ -210,7 +217,7 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >    </span
@@ -273,12 +280,12 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span id=""
       ><span class="hs-keyword"
@@ -310,7 +317,7 @@ forall a. a -&gt; a
 	><span
 	>
 </span
-	><span id="line-13"
+	><span id="line-14"
 	></span
 	><span
 	>    </span
@@ -342,7 +349,7 @@ forall (t :: * -&gt; *) a. Foldable t =&gt; t a -&gt; Int
 	><span
 	>
 </span
-	><span id="line-14"
+	><span id="line-15"
 	></span
 	><span
 	>    </span
@@ -392,17 +399,17 @@ forall (t :: * -&gt; *) a. Foldable t =&gt; t a -&gt; Int
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span class="hs-keyword"
       >class</span
@@ -453,7 +460,7 @@ forall (t :: * -&gt; *) a. Foldable t =&gt; t a -&gt; Int
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span
       >    </span
@@ -506,7 +513,7 @@ forall (t :: * -&gt; *) a. Foldable t =&gt; t a -&gt; Int
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >    </span
@@ -597,12 +604,12 @@ forall a. Foo' a =&gt; [a] -&gt; a
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span
       >    </span
@@ -645,7 +652,7 @@ forall a. Foo' a =&gt; [a] -&gt; a
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span
       >    </span
@@ -750,12 +757,12 @@ forall a. Foo a =&gt; a -&gt; Int
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span class="hs-keyword"
       >instance</span
@@ -782,7 +789,7 @@ forall a. Foo a =&gt; a -&gt; Int
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span
       >    </span
@@ -814,12 +821,12 @@ forall (t :: * -&gt; *) a. (Foldable t, Num a) =&gt; t a -&gt; a
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span id=""
       ><span class="hs-keyword"
@@ -853,7 +860,7 @@ forall (t :: * -&gt; *) a. (Foldable t, Num a) =&gt; t a -&gt; a
 	><span
 	>
 </span
-	><span id="line-28"
+	><span id="line-29"
 	></span
 	><span
 	>    </span
@@ -896,17 +903,17 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span class="hs-keyword"
       >class</span
@@ -937,7 +944,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span
       >    </span
@@ -1072,12 +1079,12 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span class="hs-keyword"
       >instance</span
@@ -1102,7 +1109,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ><span
       >    </span
@@ -1198,7 +1205,7 @@ forall a b. a -&gt; b -&gt; a
       ><span
       >
 </span
-      ><span id="line-36"
+      ><span id="line-37"
       ></span
       ><span
       >    </span
@@ -1289,7 +1296,7 @@ forall a b. a -&gt; b -&gt; a
       ><span
       >
 </span
-      ><span id="line-37"
+      ><span id="line-38"
       ></span
       ><span
       >    </span
@@ -1380,7 +1387,7 @@ forall a b. a -&gt; b -&gt; a
       ><span
       >
 </span
-      ><span id="line-38"
+      ><span id="line-39"
       ></span
       ><span
       >    </span
@@ -1471,7 +1478,7 @@ forall a b. a -&gt; b -&gt; a
       ><span
       >
 </span
-      ><span id="line-39"
+      ><span id="line-40"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Constructors.html b/hypsrc-test/ref/src/Constructors.html
index 2cc234ac5e63b3f9c8301bc28d8a46e7b75e674b..d5c3dd33d2c690d5eec23972699ac08e5ecd8287 100644
--- a/hypsrc-test/ref/src/Constructors.html
+++ b/hypsrc-test/ref/src/Constructors.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,17 +26,17 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -46,7 +53,7 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >    </span
@@ -65,7 +72,7 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >    </span
@@ -84,7 +91,7 @@
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >    </span
@@ -117,12 +124,12 @@
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span class="hs-keyword"
       >newtype</span
@@ -189,17 +196,17 @@
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#bar"
@@ -242,7 +249,7 @@
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span id="bar"
       ><span class="annot"
@@ -273,7 +280,7 @@
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id="baz"
       ><span class="annot"
@@ -304,7 +311,7 @@
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span id="quux"
       ><span class="annot"
@@ -355,17 +362,17 @@
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unfoo"
@@ -398,7 +405,7 @@
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span id="unfoo"
       ><span class="annot"
@@ -438,7 +445,7 @@
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unfoo"
@@ -473,7 +480,7 @@
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unfoo"
@@ -588,17 +595,17 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unnorf"
@@ -637,7 +644,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span id="unnorf"
       ><span class="annot"
@@ -723,7 +730,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unnorf"
@@ -814,7 +821,7 @@ forall a. [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unnorf"
@@ -848,17 +855,17 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span class="annot"
       ><a href="Constructors.html#unnorf%27"
@@ -891,7 +898,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span id="unnorf%27"
       ><span class="annot"
@@ -1047,7 +1054,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span
       >    </span
@@ -1148,7 +1155,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span
       >  </span
@@ -1157,7 +1164,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span
       >    </span
@@ -1278,7 +1285,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ><span
       >    </span
@@ -1383,7 +1390,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-36"
+      ><span id="line-37"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Identifiers.html b/hypsrc-test/ref/src/Identifiers.html
index e0f88772e45283a77abd9b19245955b83c9c7b4c..a983182d727bd8c18a45d91e514be43b2db937d6 100644
--- a/hypsrc-test/ref/src/Identifiers.html
+++ b/hypsrc-test/ref/src/Identifiers.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,17 +26,17 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="annot"
       ><a href="Identifiers.html#foo"
@@ -90,7 +97,7 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span id="foo"
       ><span class="annot"
@@ -253,7 +260,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span id="bar"
       ><span class="annot"
@@ -416,7 +423,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span id="baz"
       ><span class="annot"
@@ -557,12 +564,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span class="annot"
       ><a href="Identifiers.html#quux"
@@ -593,7 +600,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span id="quux"
       ><span class="annot"
@@ -711,12 +718,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span class="annot"
       ><a href="Identifiers.html#norf"
@@ -767,7 +774,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span id="norf"
       ><span class="annot"
@@ -822,7 +829,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span
       >    </span
@@ -887,7 +894,7 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span
       >    </span
@@ -952,7 +959,7 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >    </span
@@ -1017,7 +1024,7 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span
       >    </span
@@ -1101,17 +1108,17 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span class="annot"
       ><a href="Identifiers.html#main"
@@ -1138,7 +1145,7 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span id="main"
       ><span class="annot"
@@ -1162,7 +1169,7 @@ forall a. Ord a =&gt; a -&gt; a -&gt; Bool
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span
       >    </span
@@ -1239,7 +1246,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span
       >    </span
@@ -1305,7 +1312,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span
       >    </span
@@ -1393,7 +1400,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span
       >  </span
@@ -1402,7 +1409,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span
       >    </span
@@ -1433,7 +1440,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span
       >    </span
@@ -1464,7 +1471,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span
       >    </span
@@ -1495,7 +1502,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/LinkingIdentifiers.html b/hypsrc-test/ref/src/LinkingIdentifiers.html
index c923b6daebc7d736290a5f1c859f82901820e6fc..3a6cca568fde43e878928a685a6a521a19adc319 100644
--- a/hypsrc-test/ref/src/LinkingIdentifiers.html
+++ b/hypsrc-test/ref/src/LinkingIdentifiers.html
@@ -6,41 +6,48 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-comment"
-      >-- Tests that the identifers/operators are properly linked even when:</span
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
       ><span class="hs-comment"
-      >--</span
+      >-- Tests that the identifers/operators are properly linked even when:</span
       ><span
       >
 </span
       ><span id="line-3"
       ></span
       ><span class="hs-comment"
-      >--   * backquoted, parenthesized, vanilla</span
+      >--</span
       ><span
       >
 </span
       ><span id="line-4"
       ></span
       ><span class="hs-comment"
-      >--   * qualified, not-qualified</span
+      >--   * backquoted, parenthesized, vanilla</span
       ><span
       >
 </span
       ><span id="line-5"
       ></span
       ><span class="hs-comment"
-      >--</span
+      >--   * qualified, not-qualified</span
       ><span
       >
 </span
       ><span id="line-6"
       ></span
+      ><span class="hs-comment"
+      >--</span
+      ><span
+      >
+</span
+      ><span id="line-7"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -54,12 +61,12 @@
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span class="annot"
       ><a href="LinkingIdentifiers.html#ident"
@@ -100,7 +107,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span id=""
       ><span class="annot"
@@ -222,7 +229,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span class="annot"
       ><a href="LinkingIdentifiers.html#ident"
@@ -331,12 +338,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span class="annot"
       ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
@@ -377,7 +384,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span id=""
       ><span class="annot"
@@ -499,7 +506,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span class="annot"
       ><a href="LinkingIdentifiers.html#%2B%2B%3A%2B%2B"
@@ -608,7 +615,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Literals.html b/hypsrc-test/ref/src/Literals.html
index db6d37b39f9e6b332cef5bc51fe8934220fa5f18..94deb3045e4c1c694a639234bf860b65d5e30303 100644
--- a/hypsrc-test/ref/src/Literals.html
+++ b/hypsrc-test/ref/src/Literals.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,17 +26,17 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="annot"
       ><a href="Literals.html#str"
@@ -50,7 +57,7 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span id="str"
       ><span class="annot"
@@ -79,12 +86,12 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span id=""
       ><span class="annot"
@@ -127,7 +134,7 @@
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id="num"
       ><span class="annot"
@@ -232,12 +239,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span id=""
       ><span class="annot"
@@ -280,7 +287,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span id="frac"
       ><span class="annot"
@@ -309,12 +316,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span id=""
       ><span class="annot"
@@ -355,7 +362,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id="list"
       ><span class="annot"
@@ -413,12 +420,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span class="annot"
       ><a href="Literals.html#pair"
@@ -479,7 +486,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span id="pair"
       ><span class="annot"
@@ -545,7 +552,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Operators.html b/hypsrc-test/ref/src/Operators.html
index 2ce87a6e3f50ce92219efc8ac5ea7318d7cb2bb2..04006a0db576bcfe52caf6b320bcec4457ac2e9c 100644
--- a/hypsrc-test/ref/src/Operators.html
+++ b/hypsrc-test/ref/src/Operators.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,17 +26,17 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span id=""
       ><span class="annot"
@@ -90,7 +97,7 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span id=""
       ><span class="annot"
@@ -189,12 +196,12 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span id=""
       ><span class="annot"
@@ -255,7 +262,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id=""
       ><span class="annot"
@@ -335,12 +342,12 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span id=""
       ><span class="annot"
@@ -401,7 +408,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span id="%2A%2A%2A"
       ><span class="annot"
@@ -451,7 +458,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span class="annot"
       ><a href="Operators.html#%2A%2A%2A"
@@ -568,12 +575,12 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id=""
       ><span class="annot"
@@ -638,7 +645,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span id=""
       ><span class="annot"
@@ -732,12 +739,12 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span id=""
       ><span class="annot"
@@ -810,7 +817,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span id=""
       ><span class="annot"
@@ -954,17 +961,17 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span id=""
       ><span id=""
@@ -1047,7 +1054,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span id=""
       ><span class="annot"
@@ -1141,7 +1148,7 @@ forall a b. (a -&gt; b) -&gt; a -&gt; b
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Polymorphism.html b/hypsrc-test/ref/src/Polymorphism.html
index 1b166aff98e4f2222e31673bae1d3f04d1c63547..e1c13828bc03b11c8c0ea58d67e98b5ed84bd552 100644
--- a/hypsrc-test/ref/src/Polymorphism.html
+++ b/hypsrc-test/ref/src/Polymorphism.html
@@ -7,19 +7,21 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE RankNTypes #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
       ><span class="hs-pragma"
-      >{-# LANGUAGE ScopedTypeVariables #-}</span
+      >{-# LANGUAGE RankNTypes #-}</span
       ><span
       >
 </span
       ><span id="line-3"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE ScopedTypeVariables #-}</span
       ><span
       >
 </span
@@ -30,6 +32,11 @@
 </span
       ><span id="line-5"
       ></span
+      ><span
+      >
+</span
+      ><span id="line-6"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -43,17 +50,17 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id=""
       ><span class="annot"
@@ -102,7 +109,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span id="foo"
       ><span class="annot"
@@ -132,12 +139,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#foo%27"
@@ -200,7 +207,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span id="foo%27"
       ><span class="annot"
@@ -230,12 +237,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id=""
       ><span id=""
@@ -300,7 +307,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span id="bar"
       ><span class="annot"
@@ -330,12 +337,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#bar%27"
@@ -422,7 +429,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span id="bar%27"
       ><span class="annot"
@@ -452,12 +459,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span id=""
       ><span id=""
@@ -552,7 +559,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span id="baz"
       ><span class="annot"
@@ -582,12 +589,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#baz%27"
@@ -704,7 +711,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span id="baz%27"
       ><span class="annot"
@@ -734,12 +741,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span id=""
       ><span class="annot"
@@ -820,7 +827,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span id="quux"
       ><span class="annot"
@@ -889,12 +896,12 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#quux%27"
@@ -989,7 +996,7 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span id="quux%27"
       ><span class="annot"
@@ -1058,17 +1065,17 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span id=""
       ><span class="annot"
@@ -1135,7 +1142,7 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span id="num"
       ><span class="annot"
@@ -1165,12 +1172,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ><span
       >
 </span
-      ><span id="line-36"
+      ><span id="line-37"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#num%27"
@@ -1251,7 +1258,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-37"
+      ><span id="line-38"
       ></span
       ><span id="num%27"
       ><span class="annot"
@@ -1281,12 +1288,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-38"
+      ><span id="line-39"
       ></span
       ><span
       >
 </span
-      ><span id="line-39"
+      ><span id="line-40"
       ></span
       ><span id=""
       ><span id=""
@@ -1397,7 +1404,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-40"
+      ><span id="line-41"
       ></span
       ><span id="eq"
       ><span class="annot"
@@ -1427,12 +1434,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-41"
+      ><span id="line-42"
       ></span
       ><span
       >
 </span
-      ><span id="line-42"
+      ><span id="line-43"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#eq%27"
@@ -1565,7 +1572,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-43"
+      ><span id="line-44"
       ></span
       ><span id="eq%27"
       ><span class="annot"
@@ -1595,12 +1602,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-44"
+      ><span id="line-45"
       ></span
       ><span
       >
 </span
-      ><span id="line-45"
+      ><span id="line-46"
       ></span
       ><span id=""
       ><span id=""
@@ -1689,7 +1696,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-46"
+      ><span id="line-47"
       ></span
       ><span id="mon"
       ><span class="annot"
@@ -1719,12 +1726,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-47"
+      ><span id="line-48"
       ></span
       ><span
       >
 </span
-      ><span id="line-48"
+      ><span id="line-49"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#mon%27"
@@ -1835,7 +1842,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-49"
+      ><span id="line-50"
       ></span
       ><span id="mon%27"
       ><span class="annot"
@@ -1865,17 +1872,17 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-50"
+      ><span id="line-51"
       ></span
       ><span
       >
 </span
-      ><span id="line-51"
+      ><span id="line-52"
       ></span
       ><span
       >
 </span
-      ><span id="line-52"
+      ><span id="line-53"
       ></span
       ><span id=""
       ><span class="annot"
@@ -1974,7 +1981,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-53"
+      ><span id="line-54"
       ></span
       ><span id="norf"
       ><span class="annot"
@@ -2031,12 +2038,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-54"
+      ><span id="line-55"
       ></span
       ><span
       >
 </span
-      ><span id="line-55"
+      ><span id="line-56"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#norf%27"
@@ -2149,7 +2156,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-56"
+      ><span id="line-57"
       ></span
       ><span id="norf%27"
       ><span class="annot"
@@ -2206,17 +2213,17 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-57"
+      ><span id="line-58"
       ></span
       ><span
       >
 </span
-      ><span id="line-58"
+      ><span id="line-59"
       ></span
       ><span
       >
 </span
-      ><span id="line-59"
+      ><span id="line-60"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#plugh"
@@ -2267,7 +2274,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-60"
+      ><span id="line-61"
       ></span
       ><span id="plugh"
       ><span class="annot"
@@ -2323,12 +2330,12 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-61"
+      ><span id="line-62"
       ></span
       ><span
       >
 </span
-      ><span id="line-62"
+      ><span id="line-63"
       ></span
       ><span class="annot"
       ><a href="Polymorphism.html#thud"
@@ -2431,7 +2438,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-63"
+      ><span id="line-64"
       ></span
       ><span id="thud"
       ><span class="annot"
@@ -2477,7 +2484,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-64"
+      ><span id="line-65"
       ></span
       ><span
       >    </span
@@ -2548,7 +2555,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-65"
+      ><span id="line-66"
       ></span
       ><span
       >  </span
@@ -2557,7 +2564,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-66"
+      ><span id="line-67"
       ></span
       ><span
       >    </span
@@ -2641,7 +2648,7 @@ forall a. HasCallStack =&gt; a
       ><span
       >
 </span
-      ><span id="line-67"
+      ><span id="line-68"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/PositionPragmas.html b/hypsrc-test/ref/src/PositionPragmas.html
index 8ee123faf0186f6cae40aca67e5b3d55f668f284..3fef6c73f5e1952340f4ed62df5766cfbff5bdb1 100644
--- a/hypsrc-test/ref/src/PositionPragmas.html
+++ b/hypsrc-test/ref/src/PositionPragmas.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -19,12 +26,12 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span class="hs-pragma"
       >{-# LINE 8 &quot;hypsrc-test/src/PositionPragmas.hs&quot; #-}</span
diff --git a/hypsrc-test/ref/src/Quasiquoter.html b/hypsrc-test/ref/src/Quasiquoter.html
index ea111cadf0492bc772576846f4a4494131cd2353..ea3d27d3232e37ec6ccd8c040fe01060e8821c9d 100644
--- a/hypsrc-test/ref/src/Quasiquoter.html
+++ b/hypsrc-test/ref/src/Quasiquoter.html
@@ -6,7 +6,14 @@
     ></head
   ><body
   ><pre
-    ><span class="hs-keyword"
+    ><span class="hs-pragma"
+      >{-# LANGUAGE Haskell2010 #-}</span
+      ><span
+      >
+</span
+      ><span id="line-2"
+      ></span
+      ><span class="hs-keyword"
       >module</span
       ><span
       > </span
@@ -35,12 +42,12 @@
       ><span
       >
 </span
-      ><span id="line-2"
+      ><span id="line-3"
       ></span
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span class="hs-keyword"
       >import</span
@@ -53,7 +60,7 @@
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="hs-keyword"
       >import</span
@@ -66,19 +73,19 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span class="hs-comment"
       >-- | Quoter for constructing multiline string literals</span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span class="annot"
       ><a href="Quasiquoter.html#string"
@@ -99,7 +106,7 @@
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id="string"
       ><span class="annot"
@@ -132,7 +139,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >  </span
@@ -202,7 +209,7 @@ forall b c a. (b -&gt; c) -&gt; (a -&gt; b) -&gt; a -&gt; c
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >  </span
@@ -236,7 +243,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >  </span
@@ -270,7 +277,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span
       >  </span
@@ -304,7 +311,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span
       >  </span
@@ -313,7 +320,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span
       >  </span
@@ -322,7 +329,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span
       >    </span
@@ -365,7 +372,7 @@ forall a. String -&gt; Q a
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >    </span
@@ -415,7 +422,7 @@ forall (m :: * -&gt; *) a. MonadFail m =&gt; String -&gt; m a
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Records.html b/hypsrc-test/ref/src/Records.html
index 604ac6ca0429345c11d2d665e5b3312098b1e002..a42d940f2745c399aab96dd1384f798adbc402a4 100644
--- a/hypsrc-test/ref/src/Records.html
+++ b/hypsrc-test/ref/src/Records.html
@@ -7,19 +7,21 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE NamedFieldPuns #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
       ><span class="hs-pragma"
-      >{-# LANGUAGE RecordWildCards #-}</span
+      >{-# LANGUAGE NamedFieldPuns #-}</span
       ><span
       >
 </span
       ><span id="line-3"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE RecordWildCards #-}</span
       ><span
       >
 </span
@@ -30,6 +32,11 @@
 </span
       ><span id="line-5"
       ></span
+      ><span
+      >
+</span
+      ><span id="line-6"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -43,17 +50,17 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -84,7 +91,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >    </span
@@ -118,7 +125,7 @@
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >    </span
@@ -152,7 +159,7 @@
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >    </span
@@ -161,17 +168,17 @@
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span class="annot"
       ><a href="Records.html#point"
@@ -214,7 +221,7 @@
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span id="point"
       ><span class="annot"
@@ -333,17 +340,17 @@
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span class="annot"
       ><a href="Records.html#lengthSqr"
@@ -376,7 +383,7 @@
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span id="lengthSqr"
       ><span class="annot"
@@ -548,12 +555,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span class="annot"
       ><a href="Records.html#lengthSqr%27"
@@ -586,7 +593,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span id="lengthSqr%27"
       ><span class="annot"
@@ -732,17 +739,17 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span class="annot"
       ><a href="Records.html#translateX"
@@ -797,7 +804,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span id="translateX"
       ><span class="annot"
@@ -920,7 +927,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span id="translateY"
       ><span class="annot"
@@ -1043,12 +1050,12 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span class="annot"
       ><a href="Records.html#translate"
@@ -1103,7 +1110,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span id="translate"
       ><span class="annot"
@@ -1162,7 +1169,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span
       >    </span
@@ -1189,7 +1196,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span
       >  </span
@@ -1198,7 +1205,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span
       >    </span
@@ -1267,7 +1274,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span
       >    </span
@@ -1433,7 +1440,7 @@ forall a. Num a =&gt; a -&gt; a -&gt; a
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html b/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
index 38dfb97e9e6b84876c61c3dac0b3004b8d6c8346..9c06e8e087548b46e9ba26c91eea0f6921bf1d1c 100644
--- a/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
+++ b/hypsrc-test/ref/src/TemplateHaskellQuasiquotes.html
@@ -7,17 +7,24 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE TemplateHaskell #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE TemplateHaskell #-}</span
       ><span
       >
 </span
       ><span id="line-3"
       ></span
+      ><span
+      >
+</span
+      ><span id="line-4"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -31,12 +38,12 @@
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span class="hs-keyword"
       >import</span
@@ -49,12 +56,12 @@
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span class="annot"
       ><a href="TemplateHaskellQuasiquotes.html#aDecl"
@@ -75,7 +82,7 @@
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id="aDecl"
       ><span class="annot"
@@ -99,7 +106,7 @@
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span
       >    </span
@@ -144,7 +151,7 @@
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >    </span
@@ -169,7 +176,7 @@
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span
       >  </span
@@ -178,12 +185,12 @@
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span class="annot"
       ><a href="TemplateHaskellQuasiquotes.html#aPattern"
@@ -204,7 +211,7 @@
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span id="aPattern"
       ><span class="annot"
@@ -228,7 +235,7 @@
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span
       >    </span
@@ -241,7 +248,7 @@
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >    </span
@@ -254,7 +261,7 @@
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span
       >    </span
@@ -277,7 +284,7 @@
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span
       >    </span
@@ -304,7 +311,7 @@
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >    </span
@@ -313,7 +320,7 @@
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >  </span
@@ -322,12 +329,12 @@
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span class="annot"
       ><a href="TemplateHaskellQuasiquotes.html#aNumberPattern"
@@ -348,7 +355,7 @@
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span id="aNumberPattern"
       ><span class="annot"
@@ -372,7 +379,7 @@
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span
       >    </span
@@ -389,7 +396,7 @@
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span
       >  </span
@@ -398,12 +405,12 @@
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span class="annot"
       ><a href="TemplateHaskellQuasiquotes.html#anExpression"
@@ -434,7 +441,7 @@
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span id="anExpression"
       ><span class="annot"
@@ -458,7 +465,7 @@
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span
       >    </span
@@ -495,7 +502,7 @@
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span
       >  </span
@@ -504,7 +511,7 @@
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span id="anExpression2"
       ><span class="annot"
@@ -552,12 +559,12 @@
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span class="annot"
       ><a href="TemplateHaskellQuasiquotes.html#aType"
@@ -578,7 +585,7 @@
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span id="aType"
       ><span class="annot"
@@ -602,7 +609,7 @@
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ><span
       >    </span
@@ -629,7 +636,7 @@
       ><span
       >
 </span
-      ><span id="line-36"
+      ><span id="line-37"
       ></span
       ><span
       >  </span
@@ -638,22 +645,22 @@
       ><span
       >
 </span
-      ><span id="line-37"
+      ><span id="line-38"
       ></span
       ><span
       >
 </span
-      ><span id="line-38"
+      ><span id="line-39"
       ></span
       ><span
       >
 </span
-      ><span id="line-39"
+      ><span id="line-40"
       ></span
       ><span
       >
 </span
-      ><span id="line-40"
+      ><span id="line-41"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/TemplateHaskellSplices.html b/hypsrc-test/ref/src/TemplateHaskellSplices.html
index 63b0025d08a566240329c84d82682930363212d2..db43c8183fe5f5b536d3068170e544e9740d8e3d 100644
--- a/hypsrc-test/ref/src/TemplateHaskellSplices.html
+++ b/hypsrc-test/ref/src/TemplateHaskellSplices.html
@@ -7,12 +7,19 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE TemplateHaskell #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE TemplateHaskell #-}</span
+      ><span
+      >
+</span
+      ><span id="line-3"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -26,12 +33,12 @@
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="hs-keyword"
       >import</span
@@ -46,12 +53,12 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span class="hs-special"
       >$</span
@@ -66,12 +73,12 @@
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span id="foo"
       ><span class="annot"
@@ -111,7 +118,7 @@ forall a. a -&gt; a
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/Types.html b/hypsrc-test/ref/src/Types.html
index 835fafb07837de7e8288af04ba76b82b19240482..641ba5127b829f93748e71b2480d02fe15c2c949 100644
--- a/hypsrc-test/ref/src/Types.html
+++ b/hypsrc-test/ref/src/Types.html
@@ -7,12 +7,14 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE TypeFamilies #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE TypeFamilies #-}</span
       ><span
       >
 </span
@@ -23,6 +25,11 @@
 </span
       ><span id="line-4"
       ></span
+      ><span
+      >
+</span
+      ><span id="line-5"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -36,17 +43,17 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span
       >
 </span
-      ><span id="line-7"
+      ><span id="line-8"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -91,12 +98,12 @@
       ><span
       >
 </span
-      ><span id="line-8"
+      ><span id="line-9"
       ></span
       ><span
       >
 </span
-      ><span id="line-9"
+      ><span id="line-10"
       ></span
       ><span class="hs-keyword"
       >newtype</span
@@ -133,12 +140,12 @@
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ><span
       >
 </span
-      ><span id="line-11"
+      ><span id="line-12"
       ></span
       ><span class="hs-keyword"
       >type</span
@@ -181,7 +188,7 @@
       ><span
       >
 </span
-      ><span id="line-12"
+      ><span id="line-13"
       ></span
       ><span class="hs-keyword"
       >type</span
@@ -224,17 +231,17 @@
       ><span
       >
 </span
-      ><span id="line-13"
+      ><span id="line-14"
       ></span
       ><span
       >
 </span
-      ><span id="line-14"
+      ><span id="line-15"
       ></span
       ><span
       >
 </span
-      ><span id="line-15"
+      ><span id="line-16"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -275,12 +282,12 @@
       ><span
       >
 </span
-      ><span id="line-16"
+      ><span id="line-17"
       ></span
       ><span
       >
 </span
-      ><span id="line-17"
+      ><span id="line-18"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -347,7 +354,7 @@
       ><span
       >
 </span
-      ><span id="line-18"
+      ><span id="line-19"
       ></span
       ><span class="hs-keyword"
       >data</span
@@ -414,17 +421,17 @@
       ><span
       >
 </span
-      ><span id="line-19"
+      ><span id="line-20"
       ></span
       ><span
       >
 </span
-      ><span id="line-20"
+      ><span id="line-21"
       ></span
       ><span
       >
 </span
-      ><span id="line-21"
+      ><span id="line-22"
       ></span
       ><span class="hs-keyword"
       >type</span
@@ -465,12 +472,12 @@
       ><span
       >
 </span
-      ><span id="line-22"
+      ><span id="line-23"
       ></span
       ><span
       >
 </span
-      ><span id="line-23"
+      ><span id="line-24"
       ></span
       ><span class="hs-keyword"
       >type</span
@@ -533,7 +540,7 @@
       ><span
       >
 </span
-      ><span id="line-24"
+      ><span id="line-25"
       ></span
       ><span class="hs-keyword"
       >type</span
@@ -596,17 +603,17 @@
       ><span
       >
 </span
-      ><span id="line-25"
+      ><span id="line-26"
       ></span
       ><span
       >
 </span
-      ><span id="line-26"
+      ><span id="line-27"
       ></span
       ><span
       >
 </span
-      ><span id="line-27"
+      ><span id="line-28"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf1"
@@ -655,7 +662,7 @@
       ><span
       >
 </span
-      ><span id="line-28"
+      ><span id="line-29"
       ></span
       ><span id="norf1"
       ><span class="annot"
@@ -725,7 +732,7 @@
       ><span
       >
 </span
-      ><span id="line-29"
+      ><span id="line-30"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf1"
@@ -790,12 +797,12 @@
       ><span
       >
 </span
-      ><span id="line-30"
+      ><span id="line-31"
       ></span
       ><span
       >
 </span
-      ><span id="line-31"
+      ><span id="line-32"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf2"
@@ -844,7 +851,7 @@
       ><span
       >
 </span
-      ><span id="line-32"
+      ><span id="line-33"
       ></span
       ><span id="norf2"
       ><span class="annot"
@@ -914,7 +921,7 @@
       ><span
       >
 </span
-      ><span id="line-33"
+      ><span id="line-34"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf2"
@@ -979,17 +986,17 @@
       ><span
       >
 </span
-      ><span id="line-34"
+      ><span id="line-35"
       ></span
       ><span
       >
 </span
-      ><span id="line-35"
+      ><span id="line-36"
       ></span
       ><span
       >
 </span
-      ><span id="line-36"
+      ><span id="line-37"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf1%27"
@@ -1038,7 +1045,7 @@
       ><span
       >
 </span
-      ><span id="line-37"
+      ><span id="line-38"
       ></span
       ><span id="norf1%27"
       ><span class="annot"
@@ -1098,7 +1105,7 @@
       ><span
       >
 </span
-      ><span id="line-38"
+      ><span id="line-39"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf1%27"
@@ -1153,12 +1160,12 @@
       ><span
       >
 </span
-      ><span id="line-39"
+      ><span id="line-40"
       ></span
       ><span
       >
 </span
-      ><span id="line-40"
+      ><span id="line-41"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf2%27"
@@ -1207,7 +1214,7 @@
       ><span
       >
 </span
-      ><span id="line-41"
+      ><span id="line-42"
       ></span
       ><span id="norf2%27"
       ><span class="annot"
@@ -1267,7 +1274,7 @@
       ><span
       >
 </span
-      ><span id="line-42"
+      ><span id="line-43"
       ></span
       ><span class="annot"
       ><a href="Types.html#norf2%27"
@@ -1322,7 +1329,7 @@
       ><span
       >
 </span
-      ><span id="line-43"
+      ><span id="line-44"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/ref/src/UsingQuasiquotes.html b/hypsrc-test/ref/src/UsingQuasiquotes.html
index ca48775d7481a3c91d986413a977e99cb33bde72..1e7aef2c47c10ea7163b2c456970cbdc45ac1bd8 100644
--- a/hypsrc-test/ref/src/UsingQuasiquotes.html
+++ b/hypsrc-test/ref/src/UsingQuasiquotes.html
@@ -7,12 +7,19 @@
   ><body
   ><pre
     ><span class="hs-pragma"
-      >{-# LANGUAGE QuasiQuotes #-}</span
+      >{-# LANGUAGE Haskell2010 #-}</span
       ><span
       >
 </span
       ><span id="line-2"
       ></span
+      ><span class="hs-pragma"
+      >{-# LANGUAGE QuasiQuotes #-}</span
+      ><span
+      >
+</span
+      ><span id="line-3"
+      ></span
       ><span class="hs-keyword"
       >module</span
       ><span
@@ -26,12 +33,12 @@
       ><span
       >
 </span
-      ><span id="line-3"
+      ><span id="line-4"
       ></span
       ><span
       >
 </span
-      ><span id="line-4"
+      ><span id="line-5"
       ></span
       ><span class="hs-keyword"
       >import</span
@@ -46,12 +53,12 @@
       ><span
       >
 </span
-      ><span id="line-5"
+      ><span id="line-6"
       ></span
       ><span
       >
 </span
-      ><span id="line-6"
+      ><span id="line-7"
       ></span
       ><span id="baz"
       ><span class="annot"
@@ -96,7 +103,7 @@ forall a. [a] -&gt; [a] -&gt; [a]
       ><span
       >
 </span
-      ><span id="line-10"
+      ><span id="line-11"
       ></span
       ></pre
     ></body
diff --git a/hypsrc-test/src/Bug1091.hs b/hypsrc-test/src/Bug1091.hs
index f0cea03386e62168660c56201b10a6f5ec15af3f..013acbbc8b89df3a36c7968d8ed5525931294a85 100644
--- a/hypsrc-test/src/Bug1091.hs
+++ b/hypsrc-test/src/Bug1091.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE CPP #-}
 module Bug1091 where
 
diff --git a/hypsrc-test/src/CPP.hs b/hypsrc-test/src/CPP.hs
index f00ce031ea8206faac033409101d8ff7eae95660..59cb603470d35a800e4c3e80a847eaaa097997ab 100644
--- a/hypsrc-test/src/CPP.hs
+++ b/hypsrc-test/src/CPP.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE CPP #-}
 module CPP where
 
diff --git a/hypsrc-test/src/Classes.hs b/hypsrc-test/src/Classes.hs
index b3c3f785950a36302ed84583473311e0815cee6e..0f2416de1127ec0f86a0cd1086383fc334209aab 100644
--- a/hypsrc-test/src/Classes.hs
+++ b/hypsrc-test/src/Classes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Classes where
 
 
diff --git a/hypsrc-test/src/Constructors.hs b/hypsrc-test/src/Constructors.hs
index 8cb465359bc35f2128f31624cd5a3bd69c68eb36..66260ee8998fec134da2bf7adf5a2d974890b78a 100644
--- a/hypsrc-test/src/Constructors.hs
+++ b/hypsrc-test/src/Constructors.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Constructors where
 
 
diff --git a/hypsrc-test/src/Identifiers.hs b/hypsrc-test/src/Identifiers.hs
index 173c3ba7b322c4d25a4a024afd195c662229d6d3..72853a4a700c31e505a7ba9b66ddc24cddbd8395 100644
--- a/hypsrc-test/src/Identifiers.hs
+++ b/hypsrc-test/src/Identifiers.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Identifiers where
 
 
diff --git a/hypsrc-test/src/LinkingIdentifiers.hs b/hypsrc-test/src/LinkingIdentifiers.hs
index 4fff9776c9e729af8335e9a24adc8ad4dd99268e..b195c2c620ea52b29c73982f8113b5adb62933a4 100644
--- a/hypsrc-test/src/LinkingIdentifiers.hs
+++ b/hypsrc-test/src/LinkingIdentifiers.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 -- Tests that the identifers/operators are properly linked even when:
 --
 --   * backquoted, parenthesized, vanilla
diff --git a/hypsrc-test/src/Literals.hs b/hypsrc-test/src/Literals.hs
index 997b6615610d44dda226382b867e8da0eb3703a5..d862bf87b3f2fe5c037f69c29eae4fa16d142e7f 100644
--- a/hypsrc-test/src/Literals.hs
+++ b/hypsrc-test/src/Literals.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Literals where
 
 
diff --git a/hypsrc-test/src/Operators.hs b/hypsrc-test/src/Operators.hs
index 8e86ab0b710ec09d3c5be708f6425c7f315175b9..1dcb8856f8cbab0a085468aa6b6175b3f9b372b2 100644
--- a/hypsrc-test/src/Operators.hs
+++ b/hypsrc-test/src/Operators.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Operators where
 
 
diff --git a/hypsrc-test/src/Polymorphism.hs b/hypsrc-test/src/Polymorphism.hs
index 3f0103bf2aa1315219c8a11802e1bec105fa3bbc..dfcb37fa2649092d414143e1a31bf10f0fcd476b 100644
--- a/hypsrc-test/src/Polymorphism.hs
+++ b/hypsrc-test/src/Polymorphism.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 
diff --git a/hypsrc-test/src/PositionPragmas.hs b/hypsrc-test/src/PositionPragmas.hs
index 907316fd8aece3452a7409b4be482cb3befb6306..e01334eda5d3414df7f68cea45a4eaa01e8a76d1 100644
--- a/hypsrc-test/src/PositionPragmas.hs
+++ b/hypsrc-test/src/PositionPragmas.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module PositionPragmas where
 
 {-# LINE 8 "hypsrc-test/src/PositionPragmas.hs" #-}
diff --git a/hypsrc-test/src/Quasiquoter.hs b/hypsrc-test/src/Quasiquoter.hs
index d0a46c33f49a95bd14f18cfe8852527a769c59f7..48f1b155efad2d35c12d2b0246d3be590a117f90 100644
--- a/hypsrc-test/src/Quasiquoter.hs
+++ b/hypsrc-test/src/Quasiquoter.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Quasiquoter ( string ) where
 
 import Language.Haskell.TH.Quote
diff --git a/hypsrc-test/src/Records.hs b/hypsrc-test/src/Records.hs
index 40a01121f29d4d8baf54dd534c2923f78b277f3c..ae5a0c5560c9e3ae287eb2335736c7427bcdbb80 100644
--- a/hypsrc-test/src/Records.hs
+++ b/hypsrc-test/src/Records.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE NamedFieldPuns #-}
 {-# LANGUAGE RecordWildCards #-}
 
diff --git a/hypsrc-test/src/TemplateHaskellQuasiquotes.hs b/hypsrc-test/src/TemplateHaskellQuasiquotes.hs
index 6d4049211e5007a6d24b9a98e3cee8bdd7666159..7fafc7aaead03c45edbb9bd88ec51e231bb9fa12 100644
--- a/hypsrc-test/src/TemplateHaskellQuasiquotes.hs
+++ b/hypsrc-test/src/TemplateHaskellQuasiquotes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 
 module TemplateHaskellQuasiquotes where
diff --git a/hypsrc-test/src/TemplateHaskellSplices.hs b/hypsrc-test/src/TemplateHaskellSplices.hs
index bbd3948ea724149940cf38c128cbd85a111aba1c..f8a859a0bbad6629431d285b4776ce2e360c9fd1 100644
--- a/hypsrc-test/src/TemplateHaskellSplices.hs
+++ b/hypsrc-test/src/TemplateHaskellSplices.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TemplateHaskell #-}
 module TemplateHaskellSplices where
 
diff --git a/hypsrc-test/src/Types.hs b/hypsrc-test/src/Types.hs
index b63a825b95f932ebd11a346897c615e2ff4ad5e1..a0481e82e7121104722ee5ba664d5895ef9d5942 100644
--- a/hypsrc-test/src/Types.hs
+++ b/hypsrc-test/src/Types.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 
 
diff --git a/hypsrc-test/src/UsingQuasiquotes.hs b/hypsrc-test/src/UsingQuasiquotes.hs
index 34872d4d10688cdad0b1decdd635f74106e11415..44da0c4bd854cd1a700a39dee7501057a1943520 100644
--- a/hypsrc-test/src/UsingQuasiquotes.hs
+++ b/hypsrc-test/src/UsingQuasiquotes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE QuasiQuotes #-}
 module UsingQuasiquotes where
 
diff --git a/latex-test/src/ConstructorArgs/ConstructorArgs.hs b/latex-test/src/ConstructorArgs/ConstructorArgs.hs
index 6b0da7119809a1b5ff4547eef9e33465366de6f9..c3b848c39b5bf7fcf652c2f20fec5a9b4e7bf1bd 100644
--- a/latex-test/src/ConstructorArgs/ConstructorArgs.hs
+++ b/latex-test/src/ConstructorArgs/ConstructorArgs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs, PatternSynonyms #-}
 
 module ConstructorArgs (Foo(..), Boo(Foo, Foa, Fo, Fo'), pattern Bo, pattern Bo') where
diff --git a/latex-test/src/DefaultSignatures/DefaultSignatures.hs b/latex-test/src/DefaultSignatures/DefaultSignatures.hs
index 52d68a96091fc4cce2ec4ba7be13f8c30480c4da..1b1b8257011606b8e08b20be84d9f931bf7c7108 100644
--- a/latex-test/src/DefaultSignatures/DefaultSignatures.hs
+++ b/latex-test/src/DefaultSignatures/DefaultSignatures.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE DefaultSignatures #-}
 
 module DefaultSignatures where
diff --git a/latex-test/src/Deprecated/Deprecated.hs b/latex-test/src/Deprecated/Deprecated.hs
index aecec94e9be9ab0005076ec7c1584db8d448ac60..bf7755c671d26499eb8f4bbdf49994df109d3b26 100644
--- a/latex-test/src/Deprecated/Deprecated.hs
+++ b/latex-test/src/Deprecated/Deprecated.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Deprecated where
 
 -- | Docs for something deprecated
diff --git a/latex-test/src/Example/Example.hs b/latex-test/src/Example/Example.hs
index 42ff1646efcad2da29fde35200ed9c8c04569b22..932fddfac81016540430c553104bb6b9f48065ae 100644
--- a/latex-test/src/Example/Example.hs
+++ b/latex-test/src/Example/Example.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Example where
 
 -- | Example use.
diff --git a/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs b/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs
index 79ffb4d3972f2dbabdcaf017853217c11ff20ad3..6d742bd7e2504ae2c4d1984e331c67f5becb6a4f 100644
--- a/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs
+++ b/latex-test/src/GadtConstructorArgs/GadtConstructorArgs.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE GADTs, PatternSynonyms #-}
 
 module GadtConstructorArgs (Boo(..)) where
diff --git a/latex-test/src/LinearTypes/LinearTypes.hs b/latex-test/src/LinearTypes/LinearTypes.hs
index cb4eb138bd40744369b58c6eb73e7d8fdf0ff098..c4f9c84fd6347e48de3eff12588ce2886166d5cb 100644
--- a/latex-test/src/LinearTypes/LinearTypes.hs
+++ b/latex-test/src/LinearTypes/LinearTypes.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE LinearTypes #-}
 module LinearTypes where
 
diff --git a/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs b/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs
index 6f59d24740629531f0b48aa1c63250662490f498..38fb710138044bbfb03788a91e844d5a90715f1c 100644
--- a/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs
+++ b/latex-test/src/NamespacedIdentifier/NamespacedIdentifier.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module NamespacedIdentifiers where
 
 -- | A link to:
diff --git a/latex-test/src/Simple/Simple.hs b/latex-test/src/Simple/Simple.hs
index 7c6b9744ff75ff5ebb9f12df2a21af3e440310cc..d1c7cf6d363df022d16d3acd81d14674e1997011 100644
--- a/latex-test/src/Simple/Simple.hs
+++ b/latex-test/src/Simple/Simple.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 module Simple (foo) where
 
 -- | This is foo.
diff --git a/latex-test/src/TypeFamilies3/TypeFamilies3.hs b/latex-test/src/TypeFamilies3/TypeFamilies3.hs
index bde05fb8cf7d1ff7cac7500d458485bd5b0933e8..80279e365876fc649e66aac34954e80a142fd17c 100644
--- a/latex-test/src/TypeFamilies3/TypeFamilies3.hs
+++ b/latex-test/src/TypeFamilies3/TypeFamilies3.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE TypeFamilies #-}
 
 module TypeFamilies3 where
diff --git a/latex-test/src/UnboxedStuff/UnboxedStuff.hs b/latex-test/src/UnboxedStuff/UnboxedStuff.hs
index bd1b1302dacd76359a783ab16747ecbc8ea62036..dfeb7429b6ff00b92dd5e37bfaab92bc11119e19 100644
--- a/latex-test/src/UnboxedStuff/UnboxedStuff.hs
+++ b/latex-test/src/UnboxedStuff/UnboxedStuff.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE Haskell2010 #-}
 {-# LANGUAGE UnboxedSums, UnboxedTuples #-}
 module UnboxedStuff where