Try to fix for ghc < 7.8

This commit is contained in:
Alejandro Serrano 2014-06-29 10:28:28 +02:00
parent c06ee75fbb
commit 11acd93bf6
2 changed files with 32 additions and 1 deletions

View File

@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}
-- | Reading cabal @dist/setup-config@ -- | Reading cabal @dist/setup-config@
module Language.Haskell.GhcMod.CabalConfig ( module Language.Haskell.GhcMod.CabalConfig (
CabalConfig CabalConfig
@ -15,7 +17,11 @@ import qualified Language.Haskell.GhcMod.Cabal18 as C18
import qualified Control.Exception as E import qualified Control.Exception as E
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Control.Monad (mplus) import Control.Monad (mplus)
#if MIN_VERSION_mtl(2,2,1)
import Control.Monad.Except ()
#else
import Control.Monad.Error () import Control.Monad.Error ()
#endif
import Data.Maybe () import Data.Maybe ()
import Data.Set () import Data.Set ()
import Data.List (find,tails,isPrefixOf,isInfixOf,nub,stripPrefix) import Data.List (find,tails,isPrefixOf,isInfixOf,nub,stripPrefix)

View File

@ -1,4 +1,4 @@
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies, FlexibleInstances, CPP #-}
module Language.Haskell.GhcMod.FillSig ( module Language.Haskell.GhcMod.FillSig (
fillSig fillSig
@ -21,7 +21,11 @@ import Outputable (PprStyle)
import qualified Type as Ty import qualified Type as Ty
import qualified HsBinds as Ty import qualified HsBinds as Ty
import qualified Class as Ty import qualified Class as Ty
#if __GLASGOW_HASKELL__ >= 706
import OccName (occName) import OccName (occName)
#else
import OccName (rdrNameOcc)
#endif
import qualified Language.Haskell.Exts.Annotated as HE import qualified Language.Haskell.Exts.Annotated as HE
---------------------------------------------------------------- ----------------------------------------------------------------
@ -89,12 +93,28 @@ getSignature modSum lineNo colNo = do
,tm_checked_module_info = minfo} <- G.typecheckModule p ,tm_checked_module_info = minfo} <- G.typecheckModule p
case listifyRenamedSpans tcs (lineNo, colNo) :: [G.LInstDecl G.Name] of case listifyRenamedSpans tcs (lineNo, colNo) :: [G.LInstDecl G.Name] of
-- Instance declarations of sort 'instance F (G a)' -- Instance declarations of sort 'instance F (G a)'
#if __GLASGOW_HASKELL__ >= 708
[L loc (G.ClsInstD (G.ClsInstDecl {G.cid_poly_ty = [L loc (G.ClsInstD (G.ClsInstDecl {G.cid_poly_ty =
(L _ (G.HsForAllTy _ _ _ (L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _))))}))] -> (L _ (G.HsForAllTy _ _ _ (L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _))))}))] ->
#elif __GLASGOW_HASKELL__ >= 706
[L loc (G.ClsInstD
(L _ (G.HsForAllTy _ _ _ (L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _)))) _ _ _)] ->
#else
[L loc (G.InstDecl
(L _ (G.HsForAllTy _ _ _ (L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _)))) _ _ _)] ->
#endif
obtainClassInfo minfo clsName loc obtainClassInfo minfo clsName loc
-- Instance declarations of sort 'instance F G' (no variables) -- Instance declarations of sort 'instance F G' (no variables)
#if __GLASGOW_HASKELL__ >= 708
[L loc (G.ClsInstD (G.ClsInstDecl {G.cid_poly_ty = [L loc (G.ClsInstD (G.ClsInstDecl {G.cid_poly_ty =
(L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _))}))] -> (L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _))}))] ->
#elif __GLASGOW_HASKELL__ >= 706
[L loc (G.ClsInstD
(L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _)) _ _ _)] ->
#else
[L loc (G.InstDecl
(L _ (G.HsAppTy (L _ (G.HsTyVar clsName)) _)) _ _ _)] ->
#endif
obtainClassInfo minfo clsName loc obtainClassInfo minfo clsName loc
_ -> return Nothing _ -> return Nothing
_ -> return Nothing _ -> return Nothing
@ -161,6 +181,11 @@ instance FnArgsInfo (G.HsType G.RdrName) (G.RdrName) where
_ -> False _ -> False
getFnArgs _ = [] getFnArgs _ = []
#if __GLASGOW_HASKELL__ < 706
occName :: G.RdrName -> OccName
occName = rdrNameOcc
#endif
instance FnArgsInfo (HE.Type HE.SrcSpanInfo) (HE.Name HE.SrcSpanInfo) where instance FnArgsInfo (HE.Type HE.SrcSpanInfo) (HE.Name HE.SrcSpanInfo) where
getFnName _ _ (HE.Ident _ s) = s getFnName _ _ (HE.Ident _ s) = s
getFnName _ _ (HE.Symbol _ s) = s getFnName _ _ (HE.Symbol _ s) = s