Skip to content
This repository has been archived by the owner on Oct 7, 2020. It is now read-only.

Commit

Permalink
Drop CPP directives guarding GHC 8.2.2 statements
Browse files Browse the repository at this point in the history
  • Loading branch information
fendor committed Oct 30, 2019
1 parent 339dce3 commit a5b44db
Show file tree
Hide file tree
Showing 12 changed files with 12 additions and 74 deletions.
4 changes: 0 additions & 4 deletions hie-plugin-api/Haskell/Ide/Engine/ArtifactMap.hs
Original file line number Diff line number Diff line change
Expand Up @@ -92,11 +92,7 @@ genImportMap tm = moduleMap
where
(_, lImports, mlies, _) = fromJust $ GHC.tm_renamed_source tm

#if __GLASGOW_HASKELL__ > 802
lies = map fst $ fromMaybe [] mlies
#else
lies = fromMaybe [] mlies
#endif

moduleMap :: ModuleMap
moduleMap = foldl goImp IM.empty lImports `IM.union` foldl goExp IM.empty lies
Expand Down
39 changes: 12 additions & 27 deletions hie-plugin-api/Haskell/Ide/Engine/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,79 +37,68 @@ isExtensionOf ext = isSuffixOf ('.':ext) . takeExtensions
#endif


#if MIN_VERSION_ghc(8, 4, 0)
type GhcTc = GHC.GhcTc
#else
type GhcTc = GHC.Id
#endif

pattern HsOverLitType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsOverLitType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsOverLit _ (GHC.overLitType -> t)
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsOverLit (GHC.overLitType -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsOverLit (GHC.overLitType -> t)
#endif

pattern HsLitType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsLitType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsLit _ (TcHsSyn.hsLitType -> t)
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLit (TcHsSyn.hsLitType -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLit (TcHsSyn.hsLitType -> t)
#endif

pattern HsLamType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsLamType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsLam _ ((\(GHC.MG { GHC.mg_ext = groupTy }) -> matchGroupType groupTy) -> t)
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLam (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLam (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#endif

pattern HsLamCaseType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsLamCaseType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsLamCase _ ((\(GHC.MG { GHC.mg_ext = groupTy }) -> matchGroupType groupTy) -> t)
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLamCase (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsLamCase (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#endif

pattern HsCaseType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsCaseType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsCase _ _ ((\(GHC.MG { GHC.mg_ext = groupTy }) -> matchGroupType groupTy) -> t)
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsCase _ (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsCase _ (\GHC.MG { GHC.mg_res_ty = res, GHC.mg_arg_tys = args } -> Type.mkFunTys args res -> t)
#endif

pattern ExplicitListType :: Type.Type -> GHC.HsExpr GhcTc
pattern ExplicitListType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.ExplicitList (TysWiredIn.mkListTy -> t) _ _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.ExplicitList (TysWiredIn.mkListTy -> t) _ _
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.ExplicitList (TysWiredIn.mkListTy -> t) _ _
#endif

pattern ExplicitSumType :: Type.Type -> GHC.HsExpr GhcTc
pattern ExplicitSumType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.ExplicitSum (TysWiredIn.mkSumTy -> t) _ _ _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.ExplicitSum _ _ _ (TysWiredIn.mkSumTy -> t)
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.ExplicitSum _ _ _ (TysWiredIn.mkSumTy -> t)
#endif

Expand All @@ -118,40 +107,36 @@ pattern HsMultiIfType :: Type.Type -> GHC.HsExpr GhcTc
pattern HsMultiIfType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.HsMultiIf t _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsMultiIf t _
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.HsMultiIf t _
#endif

pattern FunBindType :: Type.Type -> GHC.HsBindLR GhcTc GhcTc
pattern FunBindType t <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.FunBind _ (GHC.L _ (Var.varType -> t)) _ _ _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.FunBind (GHC.L _ (Var.varType -> t)) _ _ _ _
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.FunBind (GHC.L _ (Var.varType -> t)) _ _ _ _
#endif

pattern FunBindGen :: Type.Type -> GHC.MatchGroup GhcTc (GHC.LHsExpr GhcTc) -> GHC.HsBindLR GhcTc GhcTc
pattern FunBindGen t fmatches <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.FunBind _ (GHC.L _ (Var.varType -> t)) fmatches _ _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.FunBind (GHC.L _ (Var.varType -> t)) fmatches _ _ _
#else
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.FunBind (GHC.L _ (Var.varType -> t)) fmatches _ _ _
#endif

pattern AbsBinds :: GHC.LHsBinds GhcTc -> GHC.HsBindLR GhcTc GhcTc
pattern AbsBinds bs <-
#if MIN_VERSION_ghc(8, 6, 0)
GHC.AbsBinds _ _ _ _ _ bs _
#elif MIN_VERSION_ghc(8, 4, 0)
GHC.AbsBinds _ _ _ _ bs _
#else
GHC.AbsBinds _ _ _ _ bs
-- elif MIN_VERSION_ghc(8, 4, 0)
GHC.AbsBinds _ _ _ _ bs _
#endif

#if MIN_VERSION_ghc(8, 6, 0)
Expand Down
3 changes: 0 additions & 3 deletions src/Haskell/Ide/Engine/Options.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,6 @@
{-# LANGUAGE CPP #-}
module Haskell.Ide.Engine.Options where

#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup hiding (option)
#endif
import Options.Applicative.Simple

data GlobalOpts = GlobalOpts
Expand Down
5 changes: 0 additions & 5 deletions src/Haskell/Ide/Engine/Plugin/ApplyRefact.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
Expand Down Expand Up @@ -27,11 +26,7 @@ import Haskell.Ide.Engine.PluginUtils
import Language.Haskell.Exts.SrcLoc
import Language.Haskell.Exts.Parser
import Language.Haskell.Exts.Extension
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
import Language.Haskell.HLint4 as Hlint
#else
import Language.Haskell.HLint3 as Hlint
#endif
import qualified Language.Haskell.LSP.Types as LSP
import qualified Language.Haskell.LSP.Types.Lens as LSP
import Refact.Apply
Expand Down
3 changes: 0 additions & 3 deletions src/Haskell/Ide/Engine/Plugin/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,9 +11,6 @@ import Data.Aeson
import Data.Foldable
import qualified Data.Map as Map
import Data.Maybe
#if __GLASGOW_HASKELL__ < 804
import Data.Semigroup
#endif
import qualified Data.Text as T
import qualified Data.Versions as V
import Development.GitRev (gitCommitCount)
Expand Down
6 changes: 0 additions & 6 deletions src/Haskell/Ide/Engine/Plugin/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,13 +13,7 @@ module Haskell.Ide.Engine.Plugin.Build where
#endif

import qualified Data.Aeson as J
#if __GLASGOW_HASKELL__ < 802
import qualified Data.Aeson.Types as J
#endif
import Data.Maybe (fromMaybe)
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans.Reader
Expand Down
4 changes: 0 additions & 4 deletions src/Haskell/Ide/Engine/Plugin/Example2.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
Expand All @@ -9,9 +8,6 @@ import Control.Lens
import Control.Monad.IO.Class
import Data.Aeson
import qualified Data.HashMap.Strict as H
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import qualified Data.Map as Map
import qualified Data.Set as S
import qualified Data.Text as T
Expand Down
4 changes: 0 additions & 4 deletions src/Haskell/Ide/Engine/Plugin/HaRe.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
Expand All @@ -14,9 +13,6 @@ import qualified Data.Aeson.Types as J
import Data.Algorithm.Diff
import Data.Algorithm.DiffOutput
import Data.Foldable
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import qualified Data.Text as T
import qualified Data.Text.IO as T
import Exception
Expand Down
6 changes: 0 additions & 6 deletions src/Haskell/Ide/Engine/Plugin/Haddock.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -9,9 +8,6 @@ module Haskell.Ide.Engine.Plugin.Haddock where
import Control.Monad.State
import Data.Foldable
import qualified Data.Map as Map
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import qualified Data.Text as T
import Data.IORef
import Data.Function
Expand Down Expand Up @@ -195,9 +191,7 @@ renderMarkDown =
["```\n"])
, markupHeader = \h ->
T.replicate (headerLevel h) "#" <> " " <> headerTitle h <> "\n"
#if __GLASGOW_HASKELL__ >= 804
, markupTable = mempty
#endif
}
where surround c x = c <> T.replace c "" x <> c
removeInner x = T.replace "```" "" $ T.replace "```haskell" "" x
Expand Down
4 changes: 0 additions & 4 deletions src/Haskell/Ide/Engine/Plugin/Hoogle.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,5 @@
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module Haskell.Ide.Engine.Plugin.Hoogle where

Expand All @@ -11,9 +10,6 @@ import Control.Applicative (liftA2)
import Data.Aeson
import Data.Bifunctor
import Data.Maybe
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import qualified Data.Text as T
import Data.List
import Haskell.Ide.Engine.MonadTypes
Expand Down
4 changes: 0 additions & 4 deletions src/Haskell/Ide/Engine/Plugin/Liquid.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
Expand All @@ -10,9 +9,6 @@ import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Trans
import Control.Exception (bracket)
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import Data.Aeson
import qualified Data.ByteString.Lazy as BS
import qualified Data.Map as Map
Expand Down
4 changes: 0 additions & 4 deletions src/Haskell/Ide/Engine/Transport/JsonStdio.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
Expand All @@ -21,9 +20,6 @@ import Control.Monad.IO.Class
import qualified Data.Aeson as J
import qualified Data.ByteString.Builder as B
import qualified Data.ByteString.Lazy.Char8 as B
#if __GLASGOW_HASKELL__ < 804
import Data.Monoid
#endif
import qualified Data.Text as T
import GHC.Generics
import Haskell.Ide.Engine.PluginsIdeMonads
Expand Down

0 comments on commit a5b44db

Please sign in to comment.