diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs index 698c86566db8760967bd8a23bc8f066b9ff031db..6f812def6b6585126a973ebe6f0640234e7027f2 100644 --- a/compiler/basicTypes/MkId.hs +++ b/compiler/basicTypes/MkId.hs @@ -12,7 +12,7 @@ have a standard form, namely: - primitive operations -} -{-# LANGUAGE CPP, DataKinds #-} +{-# LANGUAGE CPP #-} module MkId ( mkDictFunId, mkDictFunTy, mkDictSelId, mkDictSelRhs, diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs index b601dc656a56faba3c7ebc40274831e739c226c5..5189b3c5a85bc0701acc2b02a9e9d80f0dbe639e 100644 --- a/compiler/iface/TcIface.hs +++ b/compiler/iface/TcIface.hs @@ -6,7 +6,7 @@ Type checking of type signatures in interface files -} -{-# LANGUAGE CPP, DataKinds #-} +{-# LANGUAGE CPP #-} module TcIface ( tcLookupImported_maybe, diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs index 978e92e34c209a5e493d6f0ff0a49264a403c268..b598f2a21f88546d3684f954c2c1f9973f85cbfb 100644 --- a/compiler/typecheck/FamInst.hs +++ b/compiler/typecheck/FamInst.hs @@ -1,6 +1,6 @@ -- The @FamInst@ type: family instance heads -{-# LANGUAGE CPP, GADTs, DataKinds #-} +{-# LANGUAGE CPP, GADTs #-} module FamInst ( FamInstEnvs, tcGetFamInstEnvs, diff --git a/compiler/types/TypeRep.hs b/compiler/types/TypeRep.hs index b732247b3daaad5dfaaa4dcda37f542f7bca4dbf..9a4bccf31022ece83b94959c443bc96d07b91474 100644 --- a/compiler/types/TypeRep.hs +++ b/compiler/types/TypeRep.hs @@ -16,7 +16,7 @@ Note [The Type-related module hierarchy] -} {-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable, - DeriveTraversable, DataKinds #-} + DeriveTraversable #-} {-# OPTIONS_HADDOCK hide #-} -- We expose the relevant stuff from this module via the Type module