aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authoralexwl <alexey.a.kiryushin@gmail.com>2018-10-14 18:56:06 +0300
committeralexwl <alexey.a.kiryushin@gmail.com>2018-10-14 18:56:06 +0300
commit9c5cb27828bcc3cbe505fba8ef8e6db0e87d2a9c (patch)
treed558ebcf13b4f5d42d27efea30e5f5697a0f456f
parent1b8661d36ce9dcbcd5a833a79357445fe734426d (diff)
parent2b5cbccffa21d9f80f804bd9d95d4527ce3246b7 (diff)
Merge branch 'ghc-8.4.3'
-rw-r--r--app/Indexer.hs5
-rw-r--r--app/Server.hs6
-rw-r--r--src/HaskellCodeExplorer/AST/RenamedSource.hs144
-rw-r--r--src/HaskellCodeExplorer/AST/TypecheckedSource.hs163
-rw-r--r--src/HaskellCodeExplorer/GhcUtils.hs106
-rw-r--r--src/HaskellCodeExplorer/ModuleInfo.hs42
-rw-r--r--src/HaskellCodeExplorer/Types.hs20
-rw-r--r--stack-8.2.2.yaml10
-rw-r--r--stack-8.4.3.yaml9
-rw-r--r--stack.yaml12
-rw-r--r--test/Main.hs24
-rw-r--r--test/test-package/stack-8.2.2.yaml1
-rw-r--r--test/test-package/stack.yaml2
13 files changed, 471 insertions, 73 deletions
diff --git a/app/Indexer.hs b/app/Indexer.hs
index 083c94d..3a23df5 100644
--- a/app/Indexer.hs
+++ b/app/Indexer.hs
@@ -73,7 +73,10 @@ data Compression
| NoCompression
deriving (Show, Eq)
-#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ghcVersion :: Version
+ghcVersion = Version {versionBranch = [8, 4, 3, 0], versionTags = []}
+#elif MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
ghcVersion :: Version
ghcVersion = Version {versionBranch = [8, 2, 2, 0], versionTags = []}
#else
diff --git a/app/Server.hs b/app/Server.hs
index 39f550f..fd70454 100644
--- a/app/Server.hs
+++ b/app/Server.hs
@@ -343,9 +343,11 @@ loadPackageInfo config path =
HCE.source :: HCE.CompactModuleInfo -> V.Vector T.Text
in if not enableExpressionInfo
then modInfo
- { HCE.exprInfoMap = IVM.empty
+ { HCE.exprInfoMap = IVM.empty
+ , HCE.source = V.force $ source modInfo
+ -- 'force' fixes this error: Data.Vector.Mutable: uninitialised element CallStack (from HasCallStack): error, called at ./Data/Vector/Mutable.hs:188:17 in vector-0.12.0.1-GGZqQZyzchy8YFPCF67wxL:Data.Vector.Mutable
}
- else modInfo)
+ else modInfo {HCE.source = V.force $ source modInfo})
, path)
Left e -> return . Left $ (e, path)
diff --git a/src/HaskellCodeExplorer/AST/RenamedSource.hs b/src/HaskellCodeExplorer/AST/RenamedSource.hs
index c1bf463..46ecc8f 100644
--- a/src/HaskellCodeExplorer/AST/RenamedSource.hs
+++ b/src/HaskellCodeExplorer/AST/RenamedSource.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE CPP #-}
+{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
@@ -54,10 +55,19 @@ import GHC
, PatSynBind(..)
, Sig(..)
, TyClDecl(..)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ , FamEqn(..)
+ , HsDataDefn(..)
+#else
, TyFamEqn(..)
+#endif
, Type
+ , RoleAnnotDecl(..)
, unLoc
)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+import HsExtension (GhcRn)
+#endif
import HaskellCodeExplorer.GhcUtils (hsPatSynDetails, ieLocNames)
import Prelude hiding (span)
import TysWiredIn
@@ -86,9 +96,14 @@ namesFromRenamedSource =
hsTypeNames `extQ`
tyClDeclNames `extQ`
familyDeclNames `extQ`
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ familyEqNames `extQ`
+ dataEqNames `extQ`
+#else
tyFamilyEqNames `extQ`
tyFamilyDefEqNames `extQ`
dataFamInstDeclNames `extQ`
+#endif
conDeclNames `extQ`
importNames `extQ`
hsTyVarBndrNames `extQ`
@@ -97,9 +112,14 @@ namesFromRenamedSource =
hsRecFieldExprNames `extQ`
hsRecAmbFieldExprNames `extQ`
hsRecFieldPatNames `extQ`
- foreignDeclNames)
+ foreignDeclNames `extQ`
+ roleAnnotationNames)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+fieldOccName :: Bool -> FieldOcc GhcRn -> NameOccurrence
+#else
fieldOccName :: Bool -> FieldOcc Name -> NameOccurrence
+#endif
fieldOccName isBinder (FieldOcc (L span _) name) =
NameOccurrence
{ locatedName = L span (Just name)
@@ -107,16 +127,26 @@ fieldOccName isBinder (FieldOcc (L span _) name) =
, isBinder = isBinder
}
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+conDeclFieldNames :: ConDeclField GhcRn -> [NameOccurrence]
+#else
conDeclFieldNames :: ConDeclField Name -> [NameOccurrence]
+#endif
conDeclFieldNames ConDeclField {..} =
map (fieldOccName True . unLoc) cd_fld_names
-hsRecFieldExprNames ::
- HsRecField' (FieldOcc Name) (LHsExpr Name) -> [NameOccurrence]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsRecFieldExprNames :: HsRecField' (FieldOcc GhcRn) (LHsExpr GhcRn) -> [NameOccurrence]
+#else
+hsRecFieldExprNames :: HsRecField' (FieldOcc Name) (LHsExpr Name) -> [NameOccurrence]
+#endif
hsRecFieldExprNames HsRecField {..} = [fieldOccName False $ unLoc hsRecFieldLbl]
-hsRecAmbFieldExprNames ::
- HsRecField' (AmbiguousFieldOcc Name) (LHsExpr Name) -> [NameOccurrence]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsRecAmbFieldExprNames :: HsRecField' (AmbiguousFieldOcc GhcRn) (LHsExpr GhcRn) -> [NameOccurrence]
+#else
+hsRecAmbFieldExprNames :: HsRecField' (AmbiguousFieldOcc Name) (LHsExpr Name) -> [NameOccurrence]
+#endif
hsRecAmbFieldExprNames HsRecField {..} =
let (L span recField) = hsRecFieldLbl
mbName =
@@ -130,11 +160,18 @@ hsRecAmbFieldExprNames HsRecField {..} =
}
]
-hsRecFieldPatNames ::
- HsRecField' (FieldOcc Name) (LPat Name) -> [NameOccurrence]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsRecFieldPatNames :: HsRecField' (FieldOcc GhcRn) (LPat GhcRn) -> [NameOccurrence]
+#else
+hsRecFieldPatNames :: HsRecField' (FieldOcc Name) (LPat Name) -> [NameOccurrence]
+#endif
hsRecFieldPatNames HsRecField {..} = [fieldOccName False $ unLoc hsRecFieldLbl]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsExprNames :: LHsExpr GhcRn -> [NameOccurrence]
+#else
hsExprNames :: LHsExpr Name -> [NameOccurrence]
+#endif
hsExprNames (L _span (HsVar name)) =
[ NameOccurrence
{ locatedName = Just <$> name
@@ -174,9 +211,13 @@ hsExprNames (L _span (HsRecFld (Ambiguous (L span _) _name))) =
]
hsExprNames _ = []
-matchGroupNames :: MatchGroup Name (LHsExpr Name) -> [NameOccurrence]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+matchGroupNames :: MatchGroup GhcRn (LHsExpr GhcRn) -> [NameOccurrence]
+#else
+matchGroupNames :: MatchGroup Name (LHsExpr Name) -> [NameOccurrence]
+#endif
matchGroupNames =
-#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
+#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
mapMaybe (fmap toNameOcc . matchContextName . m_ctxt . unLoc) .
#else
mapMaybe (fmap toNameOcc . matchFixityName . m_fixity . unLoc) .
@@ -184,20 +225,24 @@ matchGroupNames =
unLoc . mg_alts
where
#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
- matchContextName :: HsMatchContext Name -> Maybe (Located Name)
+ --matchContextName :: HsMatchContext Name -> Maybe (Located Name)
matchContextName (FunRhs name _ _bool) = Just name
matchContextName _ = Nothing
#else
- matchFixityName :: MatchFixity Name -> Maybe (Located Name)
+ --matchFixityName :: MatchFixity Name -> Maybe (Located Name)
matchFixityName NonFunBindMatch = Nothing
matchFixityName (FunBindMatch name _bool) = Just name
#endif
- toNameOcc :: Located Name -> NameOccurrence
+ --toNameOcc :: Located Name -> NameOccurrence
toNameOcc n =
NameOccurrence
- {locatedName = Just <$> n, description = "Match", isBinder = True}
+ {locatedName = Just <$> n, description = "Match", isBinder = True}
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+bindNames :: LHsBindLR GhcRn GhcRn -> [NameOccurrence]
+#else
bindNames :: LHsBindLR Name Name -> [NameOccurrence]
+#endif
bindNames (L _span (PatSynBind PSB {..})) =
[ NameOccurrence
{ locatedName = Just <$> psb_id
@@ -218,7 +263,11 @@ hsPatSynDetailsNames =
}) .
hsPatSynDetails
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+importNames :: IE GhcRn -> [NameOccurrence]
+#else
importNames :: IE Name -> [NameOccurrence]
+#endif
importNames =
map
(\name ->
@@ -229,7 +278,12 @@ importNames =
}) .
ieLocNames
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+patNames :: LPat GhcRn -> [NameOccurrence]
+#else
patNames :: LPat Name -> [NameOccurrence]
+#endif
patNames (L _span (VarPat name)) =
[ NameOccurrence
{ locatedName = Just <$> name
@@ -260,7 +314,12 @@ patNames (L _span (NPlusKPat name _ _ _ _ _)) =
]
patNames _ = []
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+sigNames :: LSig GhcRn -> [NameOccurrence]
+#else
sigNames :: LSig Name -> [NameOccurrence]
+#endif
sigNames (L _span (TypeSig names _)) =
map
(\n ->
@@ -332,7 +391,11 @@ sigNames (L _span (MinimalSig _ (L _ boolFormula))) =
boolFormulaNames (Parens (L _ f)) = boolFormulaNames f
sigNames (L _ _) = []
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsTypeNames :: LHsType GhcRn -> [NameOccurrence]
+#else
hsTypeNames :: LHsType Name -> [NameOccurrence]
+#endif
#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
hsTypeNames (L _span (HsTyVar _promoted name)) =
#else
@@ -382,7 +445,12 @@ hsTypeNames (L span (HsTupleTy tupleSort types))
--hsTypeNames (L span (HsExplicitTupleTy _kind types)) = ...
hsTypeNames _ = []
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsTyVarBndrNames :: HsTyVarBndr GhcRn -> [NameOccurrence]
+#else
hsTyVarBndrNames :: HsTyVarBndr Name -> [NameOccurrence]
+#endif
hsTyVarBndrNames (UserTyVar n) =
[ NameOccurrence
{ locatedName = Just <$> n
@@ -398,7 +466,11 @@ hsTyVarBndrNames (KindedTyVar n _) =
}
]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+tyClDeclNames :: LTyClDecl GhcRn -> [NameOccurrence]
+#else
tyClDeclNames :: LTyClDecl Name -> [NameOccurrence]
+#endif
tyClDeclNames (L _span DataDecl {..}) =
[ NameOccurrence
{ locatedName = Just <$> tcdLName
@@ -432,7 +504,11 @@ tyClDeclNames (L _span ClassDecl {..}) =
}
tyClDeclNames _ = []
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+familyDeclNames :: FamilyDecl GhcRn -> [NameOccurrence]
+#else
familyDeclNames :: FamilyDecl Name -> [NameOccurrence]
+#endif
familyDeclNames FamilyDecl {..} =
[ NameOccurrence
{ locatedName = Just <$> fdLName
@@ -441,6 +517,26 @@ familyDeclNames FamilyDecl {..} =
}
]
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+familyEqNames :: FamEqn GhcRn (HsTyPats GhcRn) (LHsType GhcRn) -> [NameOccurrence]
+familyEqNames FamEqn {feqn_tycon = tyCon} =
+ [ NameOccurrence
+ { locatedName = Just <$> tyCon
+ , description = "FamEqn"
+ , isBinder = False
+ }
+ ]
+
+dataEqNames :: FamEqn GhcRn (HsTyPats GhcRn) (HsDataDefn GhcRn) -> [NameOccurrence]
+dataEqNames FamEqn {feqn_tycon = tyCon} =
+ [ NameOccurrence
+ { locatedName = Just <$> tyCon
+ , description = "FamEqn"
+ , isBinder = False
+ }
+ ]
+#else
tyFamilyEqNames :: TyFamEqn Name (HsTyPats Name) -> [NameOccurrence]
tyFamilyEqNames TyFamEqn {tfe_tycon = tyCon} =
[ NameOccurrence
@@ -467,8 +563,13 @@ dataFamInstDeclNames DataFamInstDecl {dfid_tycon = tyCon} =
, isBinder = False
}
]
+#endif
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+conDeclNames :: ConDecl GhcRn -> [NameOccurrence]
+#else
conDeclNames :: ConDecl Name -> [NameOccurrence]
+#endif
conDeclNames con =
case con of
ConDeclGADT {con_names = names} ->
@@ -488,7 +589,11 @@ conDeclNames con =
}
]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foreignDeclNames :: ForeignDecl GhcRn -> [NameOccurrence]
+#else
foreignDeclNames :: ForeignDecl Name -> [NameOccurrence]
+#endif
foreignDeclNames decl =
[ NameOccurrence
{ locatedName = Just <$> fd_name decl
@@ -496,3 +601,16 @@ foreignDeclNames decl =
, isBinder = True
}
]
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+roleAnnotationNames :: RoleAnnotDecl GhcRn -> [NameOccurrence]
+#else
+roleAnnotationNames :: RoleAnnotDecl Name -> [NameOccurrence]
+#endif
+roleAnnotationNames (RoleAnnotDecl n _) =
+ [ NameOccurrence
+ { locatedName = Just <$> n
+ , description = "RoleAnnotDecl"
+ , isBinder = False
+ }
+ ]
diff --git a/src/HaskellCodeExplorer/AST/TypecheckedSource.hs b/src/HaskellCodeExplorer/AST/TypecheckedSource.hs
index f97c33b..6f9a4cf 100644
--- a/src/HaskellCodeExplorer/AST/TypecheckedSource.hs
+++ b/src/HaskellCodeExplorer/AST/TypecheckedSource.hs
@@ -80,6 +80,9 @@ import HsSyn
, selectorAmbiguousFieldOcc
)
import HscTypes (TypeEnv, lookupTypeEnv)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+import HsExtension (GhcTc)
+#endif
import Id (idType)
import IdInfo (IdDetails(..))
import InstEnv
@@ -541,11 +544,19 @@ tidyType typ = do
let (tidyEnv', typ') = tidyOpenType tidyEnv typ
modify' (\s -> s {astStateTidyEnv = tidyEnv'})
return typ'
-
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldTypecheckedSource :: LHsBinds GhcTc -> State ASTState ()
+#else
foldTypecheckedSource :: LHsBinds Id -> State ASTState ()
+#endif
foldTypecheckedSource = foldLHsBindsLR
-foldLHsExpr :: LHsExpr Var -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsExpr :: LHsExpr GhcTc -> State ASTState (Maybe Type)
+#else
+foldLHsExpr :: LHsExpr Id -> State ASTState (Maybe Type)
+#endif
foldLHsExpr (L span (HsVar (L _ identifier))) =
restoreTidyEnv $ do
(identifier', mbTypes) <- tidyIdentifier identifier
@@ -801,8 +812,12 @@ foldLHsExpr (L span (HsWrap wrapper expr)) =
Composite -> return () -- Not sure if it is possible
typ <- foldLHsExpr (L span expr)
return $ applyWrapper wrapper <$> typ
-
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldHsRecFields :: HsRecFields GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
foldHsRecFields :: HsRecFields Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldHsRecFields HsRecFields {..} = do
let userWritten =
case rec_dotdot of
@@ -810,8 +825,12 @@ foldHsRecFields HsRecFields {..} = do
Nothing -> id
mapM_ foldLHsRecField $ userWritten rec_flds
return Nothing
-
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsRecField :: LHsRecField GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
foldLHsRecField :: LHsRecField Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldLHsRecField (L span (HsRecField (L idSpan (FieldOcc _ identifier)) arg pun)) =
restoreTidyEnv $ do
(identifier', mbTypes) <- tidyIdentifier identifier
@@ -820,7 +839,11 @@ foldLHsRecField (L span (HsRecField (L idSpan (FieldOcc _ identifier)) arg pun))
unless pun $ void (foldLHsExpr arg)
return . Just . varType $ identifier'
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsRecUpdField :: LHsRecUpdField GhcTc -> State ASTState (Maybe Type)
+#else
foldLHsRecUpdField :: LHsRecUpdField Id -> State ASTState (Maybe Type)
+#endif
foldLHsRecUpdField (L span (HsRecField (L idSpan recField) arg pun)) =
restoreTidyEnv $ do
let selectorId = selectorAmbiguousFieldOcc recField
@@ -844,7 +867,11 @@ data TupArg
| TupArgMissing
deriving (Show, Eq)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsTupArg :: LHsTupArg GhcTc -> State ASTState (Maybe Type, TupArg)
+#else
foldLHsTupArg :: LHsTupArg Id -> State ASTState (Maybe Type, TupArg)
+#endif
foldLHsTupArg (L _span (Present expr)) =
restoreTidyEnv $ do
typ <- foldLHsExpr expr
@@ -858,31 +885,51 @@ foldLHsTupArg (L _ (Missing typ)) =
typ' <- tidyType typ
return (Just typ', TupArgMissing)
-foldLMatch :: LMatch Id (LHsExpr Var) -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLMatch :: LMatch GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
+foldLMatch :: LMatch Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldLMatch (L _span Match {..}) = do
mapM_ foldLPat m_pats
_ <- foldGRHSs m_grhss
return Nothing
-
-foldLMatchCmd :: LMatch Id (LHsCmd Var) -> State ASTState (Maybe Type)
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLMatchCmd :: LMatch GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type)
+#else
+foldLMatchCmd :: LMatch Id (LHsCmd Id) -> State ASTState (Maybe Type)
+#endif
foldLMatchCmd (L _span Match {..}) = do
mapM_ foldLPat m_pats
_ <- foldGRHSsCmd m_grhss
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldGRHSsCmd :: GRHSs GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type)
+#else
foldGRHSsCmd :: GRHSs Id (LHsCmd Id) -> State ASTState (Maybe Type)
+#endif
foldGRHSsCmd GRHSs {..} = do
mapM_ foldLGRHSCmd grhssGRHSs
_ <- foldHsLocalBindsLR (unLoc grhssLocalBinds)
return Nothing
-foldGRHSs :: GRHSs Id (LHsExpr Var) -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldGRHSs :: GRHSs GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
+foldGRHSs :: GRHSs Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldGRHSs GRHSs {..} = do
mapM_ foldLGRHS grhssGRHSs
_ <- foldHsLocalBindsLR (unLoc grhssLocalBinds)
return Nothing
-foldLStmtLR :: LStmtLR Id Id (LHsExpr Var) -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLStmtLR :: LStmtLR GhcTc GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
+foldLStmtLR :: LStmtLR Id Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldLStmtLR (L span (LastStmt body _ _)) =
do typ <- foldLHsExpr body
addExprInfo span typ "LastStmt" Composite
@@ -916,10 +963,18 @@ foldLStmtLR (L span (ApplicativeStmt args _ typ)) =
addExprInfo span (Just typ') "ApplicativeStmt" Composite
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldApplicativeArg :: ApplicativeArg GhcTc GhcTc -> State ASTState (Maybe Type)
+#else
foldApplicativeArg :: ApplicativeArg Id Id -> State ASTState (Maybe Type)
+#endif
foldApplicativeArg appArg =
case appArg of
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ ApplicativeArgOne pat expr _bool -> do
+#else
ApplicativeArgOne pat expr -> do
+#endif
_ <- foldLPat pat
_ <- foldLHsExpr expr
return Nothing
@@ -927,9 +982,12 @@ foldApplicativeArg appArg =
_ <- mapM_ foldLStmtLR exprStmts
_ <- foldLPat pat
return Nothing
-
-foldLStmtLRCmd :: LStmtLR Id Id (LHsCmd Var)
- -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLStmtLRCmd ::
+ LStmtLR GhcTc GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type)
+#else
+foldLStmtLRCmd :: LStmtLR Id Id (LHsCmd Id) -> State ASTState (Maybe Type)
+#endif
foldLStmtLRCmd (L span (LastStmt body _syntaxExpr _)) = do
typ <- foldLHsCmd body
addExprInfo span typ "LastStmt Cmd" Composite
@@ -962,43 +1020,73 @@ foldLStmtLRCmd (L span (ApplicativeStmt args _ typ)) =
mapM_ (foldApplicativeArg . snd) args
addExprInfo span (Just typ') "ApplicativeStmt Cmd" Composite
return Nothing
-
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLGRHS :: LGRHS GhcTc (LHsExpr GhcTc) -> State ASTState (Maybe Type)
+#else
foldLGRHS :: LGRHS Id (LHsExpr Id) -> State ASTState (Maybe Type)
+#endif
foldLGRHS (L _span (GRHS guards body)) = do
typ <- foldLHsExpr body
mapM_ foldLStmtLR guards
return typ
-
-foldLGRHSCmd :: LGRHS Id (LHsCmd Var) -> State ASTState (Maybe Type)
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLGRHSCmd :: LGRHS GhcTc (LHsCmd GhcTc) -> State ASTState (Maybe Type)
+#else
+foldLGRHSCmd :: LGRHS Id (LHsCmd Id) -> State ASTState (Maybe Type)
+#endif
foldLGRHSCmd (L _span (GRHS guards body)) = do
typ <- foldLHsCmd body
mapM_ foldLStmtLR guards
return typ
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldParStmtBlock :: ParStmtBlock GhcTc GhcTc -> State ASTState (Maybe Type)
+#else
foldParStmtBlock :: ParStmtBlock Id Id -> State ASTState (Maybe Type)
+#endif
foldParStmtBlock (ParStmtBlock exprStmts _ids _syntaxExpr) = do
mapM_ foldLStmtLR exprStmts
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldHsLocalBindsLR :: HsLocalBindsLR GhcTc GhcTc -> State ASTState (Maybe Type)
+#else
foldHsLocalBindsLR :: HsLocalBindsLR Id Id -> State ASTState (Maybe Type)
+#endif
foldHsLocalBindsLR (HsValBinds binds) = do
_ <- foldHsValBindsLR binds
return Nothing
foldHsLocalBindsLR (HsIPBinds _binds) = return Nothing
foldHsLocalBindsLR EmptyLocalBinds = return Nothing
-foldHsValBindsLR :: HsValBindsLR Id Var -> State ASTState (Maybe Type)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldHsValBindsLR :: HsValBindsLR GhcTc GhcTc -> State ASTState (Maybe Type)
+#else
+foldHsValBindsLR :: HsValBindsLR Id Id -> State ASTState (Maybe Type)
+#endif
foldHsValBindsLR (ValBindsIn _ _) = return Nothing
foldHsValBindsLR (ValBindsOut binds _) = do
_ <- mapM_ (foldLHsBindsLR . snd) binds
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsBindsLR :: LHsBinds GhcTc -> State ASTState ()
+#else
foldLHsBindsLR :: LHsBinds Id -> State ASTState ()
+#endif
foldLHsBindsLR = mapM_ (`foldLHsBindLR` Nothing) . bagToList
-foldLHsBindLR :: LHsBindLR Id Var
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsBindLR :: LHsBindLR GhcTc GhcTc
-> Maybe Id -- ^ Polymorphic id
-> State ASTState (Maybe Type)
+#else
+foldLHsBindLR :: LHsBindLR Id Id
+ -> Maybe Id -- ^ Polymorphic id
+ -> State ASTState (Maybe Type)
+#endif
foldLHsBindLR (L _span FunBind {..}) mbPolyId
| mg_origin fun_matches == FromSource =
restoreTidyEnv $ do
@@ -1024,9 +1112,12 @@ foldLHsBindLR (L _ AbsBinds {..}) _ = do
mapM_ (\(bind, typ) -> foldLHsBindLR bind (Just typ)) $
zip (bagToList abs_binds) (map abe_poly abs_exports)
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+#else
foldLHsBindLR (L _ AbsBindsSig {..}) _ = do
_ <- foldLHsBindLR abs_sig_bind (Just abs_sig_export)
return Nothing
+#endif
foldLHsBindLR (L _ (PatSynBind PSB {..})) _ =
restoreTidyEnv $ do
_ <- foldLPat psb_def
@@ -1036,16 +1127,30 @@ foldLHsBindLR (L _ (PatSynBind PSB {..})) _ =
(i', _) <- tidyIdentifier i
addIdentifierToIdSrcSpanMap span i' Nothing
in case psb_args of
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ InfixCon id1 id2 -> addId id1 >> addId id2
+ PrefixCon ids -> mapM_ addId ids
+ RecCon recs ->
+ mapM_
+ (\(RecordPatSynField selId patVar) ->
+ addId selId >> addId patVar)
+ recs
+#else
InfixPatSyn id1 id2 -> addId id1 >> addId id2
PrefixPatSyn ids -> mapM_ addId ids
RecordPatSyn recs ->
mapM_
(\(RecordPatSynField selId patVar) ->
addId selId >> addId patVar)
- recs
+ recs
+#endif
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLPat :: LPat GhcTc -> State ASTState (Maybe Type)
+#else
foldLPat :: LPat Id -> State ASTState (Maybe Type)
+#endif
foldLPat (L span (VarPat (L _ identifier))) = do
(identifier', _) <- tidyIdentifier identifier
addIdentifierToIdSrcSpanMap span identifier' Nothing
@@ -1151,9 +1256,15 @@ foldLPat (L span p@(CoPat _ pat typ)) = do
_ <- foldLPat (L span pat)
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldHsConPatDetails
+ :: HsConPatDetails GhcTc
+ -> State ASTState (Maybe Type)
+#else
foldHsConPatDetails
:: HsConPatDetails Id
-> State ASTState (Maybe Type)
+#endif
foldHsConPatDetails (PrefixCon args) = do
_ <- mapM_ foldLPat args
return Nothing
@@ -1165,7 +1276,11 @@ foldHsConPatDetails (InfixCon arg1 arg2) = do
_ <- foldLPat arg2
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldHsRecFieldsPat :: HsRecFields GhcTc (LPat GhcTc) -> State ASTState (Maybe Type)
+#else
foldHsRecFieldsPat :: HsRecFields Id (LPat Id) -> State ASTState (Maybe Type)
+#endif
foldHsRecFieldsPat HsRecFields {..} = do
let onlyUserWritten =
case rec_dotdot of
@@ -1174,20 +1289,32 @@ foldHsRecFieldsPat HsRecFields {..} = do
_ <- mapM_ foldLHsRecFieldPat $ onlyUserWritten rec_flds
return Nothing
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsRecFieldPat :: LHsRecField GhcTc (LPat GhcTc) -> State ASTState (Maybe Type)
+#else
foldLHsRecFieldPat :: LHsRecField Id (LPat Id) -> State ASTState (Maybe Type)
+#endif
foldLHsRecFieldPat (L _ (HsRecField (L idSpan (FieldOcc _ identifier)) arg pun)) = do
(identifier', mbTypes) <- tidyIdentifier identifier
addIdentifierToIdSrcSpanMap idSpan identifier' mbTypes
unless pun $ void $ foldLPat arg
return . Just . varType $ identifier'
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsCmdTop :: LHsCmdTop GhcTc -> State ASTState (Maybe Type)
+#else
foldLHsCmdTop :: LHsCmdTop Id -> State ASTState (Maybe Type)
+#endif
foldLHsCmdTop (L span (HsCmdTop cmd _ _ _)) = do
mbTyp <- foldLHsCmd cmd
addExprInfo span mbTyp "HsCmdTop" Composite
return mbTyp
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+foldLHsCmd :: LHsCmd GhcTc -> State ASTState (Maybe Type)
+#else
foldLHsCmd :: LHsCmd Id -> State ASTState (Maybe Type)
+#endif
foldLHsCmd (L _ (HsCmdArrApp expr1 expr2 _ _ _)) = do
_ <- foldLHsExpr expr1
_ <- foldLHsExpr expr2
diff --git a/src/HaskellCodeExplorer/GhcUtils.hs b/src/HaskellCodeExplorer/GhcUtils.hs
index 714e429..b25678d 100644
--- a/src/HaskellCodeExplorer/GhcUtils.hs
+++ b/src/HaskellCodeExplorer/GhcUtils.hs
@@ -3,6 +3,8 @@
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}
module HaskellCodeExplorer.GhcUtils
@@ -71,7 +73,13 @@ import Data.Ord (comparing)
import qualified Data.Text as T
import DataCon (dataConWorkId, flSelector)
import Documentation.Haddock.Parser (overIdentifier, parseParas)
-import Documentation.Haddock.Types (DocH(..), Header(..), _doc)
+import Documentation.Haddock.Types (DocH(..),
+ Header(..),
+ _doc,
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ Table(..)
+#endif
+ )
import DynFlags ()
import FastString (mkFastString, unpackFS)
import GHC
@@ -121,6 +129,9 @@ import GHC
#else
, tyClGroupConcat
#endif
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ , FamEqn(..)
+#endif
, tyConKind
, nameSrcSpan
, srcSpanFile
@@ -138,11 +149,18 @@ import GHC
, tyFamInstDeclName
, idType
, hsib_body
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+#else
, tfe_pats
+#endif
, tfid_eqn
)
+
import qualified HaskellCodeExplorer.Types as HCE
import HscTypes (TypeEnv, lookupTypeEnv)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+import HsExtension (GhcRn,IdP)
+#endif
import IdInfo (IdDetails(..))
import InstEnv (ClsInst(..))
import Lexer (ParseResult(POk), mkPState, unP)
@@ -250,10 +268,28 @@ instanceToText :: DynFlags -> ClsInst -> T.Text
instanceToText flags ClsInst {..} =
T.append "instance " $ T.pack . showSDoc flags $ pprSigmaType (idType is_dfun)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+instanceDeclToText :: DynFlags -> InstDecl GhcRn -> T.Text
+#else
instanceDeclToText :: DynFlags -> InstDecl Name -> T.Text
+#endif
instanceDeclToText flags decl =
case decl of
ClsInstD ClsInstDecl {..} -> T.append "instance " (toText flags cid_poly_ty)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ DataFamInstD di ->
+ let args =
+ T.intercalate " " . map (toText flags) . feqn_pats .hsib_body . dfid_eqn $ di
+ in T.concat
+ ["data instance ", toText flags (unLoc $ feqn_tycon . hsib_body . dfid_eqn $ di), " ", args]
+ TyFamInstD ti ->
+ let args =
+ T.intercalate " " .
+ map (toText flags) . feqn_pats . hsib_body . tfid_eqn $
+ ti
+ in T.concat
+ ["type instance ", toText flags $ tyFamInstDeclName ti, " ", args]
+#else
DataFamInstD di ->
let args =
T.intercalate " " . map (toText flags) . hsib_body $ dfid_pats di
@@ -266,6 +302,7 @@ instanceDeclToText flags decl =
ti
in T.concat
["type instance ", toText flags $ tyFamInstDeclName ti, " ", args]
+#endif
nameToText :: Name -> T.Text
nameToText = T.pack . unpackFS . occNameFS . nameOccName
@@ -366,7 +403,11 @@ mbIdDetails _ = Nothing
-- Syntax transformation
--------------------------------------------------------------------------------
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+hsGroupVals :: HsGroup GhcRn -> [GenLocated SrcSpan (HsBindLR GhcRn GhcRn)]
+#else
hsGroupVals :: HsGroup Name -> [GenLocated SrcSpan (HsBindLR Name Name)]
+#endif
hsGroupVals hsGroup =
filter (isGoodSrcSpan . getLoc) $
case hs_valds hsGroup of
@@ -375,6 +416,14 @@ hsGroupVals hsGroup =
hsPatSynDetails :: HsPatSynDetails a -> [a]
hsPatSynDetails patDetails =
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ case patDetails of
+ InfixCon name1 name2 -> [name1, name2]
+ PrefixCon fields -> fields
+ RecCon fields -> concatMap
+ (\field -> [recordPatSynSelectorId field, recordPatSynPatVar field])
+ fields
+#else
case patDetails of
InfixPatSyn name1 name2 -> [name1, name2]
PrefixPatSyn name -> name
@@ -382,8 +431,13 @@ hsPatSynDetails patDetails =
concatMap
(\field -> [recordPatSynSelectorId field, recordPatSynPatVar field])
fields
+#endif
-#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
+
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+unwrapName :: LIEWrappedName a -> Located a
+unwrapName = ieLWrappedName
+#elif MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
unwrapName :: LIEWrappedName Name -> Located Name
unwrapName = ieLWrappedName
#else
@@ -391,7 +445,11 @@ unwrapName :: Located Name -> Located Name
unwrapName n = n
#endif
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ieLocNames :: IE pass -> [Located (IdP pass)]
+#else
ieLocNames :: IE Name -> [Located Name]
+#endif
ieLocNames (IEVar n) = [unwrapName n]
ieLocNames (IEThingAbs n) = [unwrapName n]
ieLocNames (IEThingAll n) = [unwrapName n]
@@ -909,7 +967,11 @@ collectDocs = go Nothing []
go (Just prev) docs (d:ds) = finished prev docs (go (Just d) [] ds)
finished decl docs rest = (decl, reverse docs) : rest
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn]
+#else
ungroup :: HsGroup Name -> [LHsDecl Name]
+#endif
ungroup group_ =
#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
mkDecls (tyClGroupTyClDecls . hs_tyclds) TyClD group_ ++
@@ -939,7 +1001,11 @@ mkDecls field con struct = [L loc (con decl) | L loc decl <- field struct]
sortByLoc :: [Located a] -> [Located a]
sortByLoc = L.sortBy (comparing getLoc)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+classDeclDocs :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
+#else
classDeclDocs :: TyClDecl Name -> [(LHsDecl Name, [HsDocString])]
+#endif
classDeclDocs class_ = collectDocs . sortByLoc $ decls
where
decls = docs ++ defs ++ sigs ++ ats
@@ -948,13 +1014,21 @@ classDeclDocs class_ = collectDocs . sortByLoc $ decls
sigs = mkDecls tcdSigs SigD class_
ats = mkDecls tcdATs (TyClD . FamDecl) class_
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+conDeclDocs :: ConDecl GhcRn -> [(Name, [HsDocString], SrcSpan)]
+#else
conDeclDocs :: ConDecl Name -> [(Name, [HsDocString], SrcSpan)]
+#endif
conDeclDocs conDecl =
map (\(L span n) -> (n, maybe [] ((: []) . unLoc) $ con_doc conDecl, span)) .
getConNames $
conDecl
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+selectorDocs :: ConDecl pass -> [(PostRn pass (IdP pass), [HsDocString], SrcSpan)]
+#else
selectorDocs :: ConDecl name -> [(PostRn name name, [HsDocString], SrcSpan)]
+#endif
selectorDocs con =
case getConDetails con of
RecCon (L _ flds) ->
@@ -967,10 +1041,13 @@ selectorDocs con =
flds
_ -> []
-subordinateNamesWithDocs ::
- [GenLocated SrcSpan (HsDecl Name)] -> [(Name, [HsDocString], SrcSpan)]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+subordinateNamesWithDocs :: [GenLocated SrcSpan (HsDecl GhcRn)] -> [(Name, [HsDocString], SrcSpan)]
+#else
+subordinateNamesWithDocs :: [GenLocated SrcSpan (HsDecl Name)] -> [(Name, [HsDocString], SrcSpan)]
+#endif
subordinateNamesWithDocs =
- concatMap
+ concatMap
(\(L span tyClDecl) ->
case tyClDecl of
TyClD classDecl@ClassDecl {..} ->
@@ -981,15 +1058,24 @@ subordinateNamesWithDocs =
concatMap (\(L _ con) -> conDeclDocs con ++ selectorDocs con) $
dd_cons tcdDataDefn
InstD (DataFamInstD DataFamInstDecl {..}) ->
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ concatMap (conDeclDocs . unLoc) . dd_cons . feqn_rhs . hsib_body $ dfid_eqn
+#else
concatMap (conDeclDocs . unLoc) . dd_cons $ dfid_defn
+#endif
_ -> [])
+
isUserLSig :: LSig name -> Bool
isUserLSig (L _ TypeSig {}) = True
isUserLSig (L _ ClassOpSig {}) = True
isUserLSig _ = False
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+getMainDeclBinder :: HsDecl pass -> [IdP pass]
+#else
getMainDeclBinder :: HsDecl name -> [name]
+#endif
getMainDeclBinder (TyClD d) = [tcdName d]
getMainDeclBinder (ValD d) =
case collectHsBindBinders d of
@@ -1000,7 +1086,11 @@ getMainDeclBinder (ForD (ForeignImport name _ _ _)) = [unLoc name]
getMainDeclBinder (ForD ForeignExport {}) = []
getMainDeclBinder _ = []
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+sigNameNoLoc :: Sig pass -> [IdP pass]
+#else
sigNameNoLoc :: Sig name -> [name]
+#endif
sigNameNoLoc (TypeSig ns _) = map unLoc ns
sigNameNoLoc (ClassOpSig _ ns _) = map unLoc ns
#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
@@ -1013,7 +1103,7 @@ sigNameNoLoc (InlineSig n _) = [unLoc n]
sigNameNoLoc (FixSig (FixitySig ns _)) = map unLoc ns
sigNameNoLoc _ = []
-clsInstDeclSrcSpan :: ClsInstDecl name -> SrcSpan
+clsInstDeclSrcSpan :: ClsInstDecl a -> SrcSpan
clsInstDeclSrcSpan ClsInstDecl {cid_poly_ty = ty} = getLoc (hsSigType ty)
hsDocsToDocH :: DynFlags -> GlobalRdrEnv -> [HsDocString] -> Doc Name
@@ -1091,6 +1181,9 @@ rename dflags gre = rn
DocEmpty -> DocEmpty
DocString str -> DocString str
DocHeader (Header l t) -> DocHeader $ Header l (rn t)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ DocTable t -> DocTable (rn <$> t)
+#endif
-- | Wrap an identifier that's out of scope (i.e. wasn't found in
-- 'GlobalReaderEnv' during 'rename') in an appropriate doc. Currently
@@ -1108,6 +1201,7 @@ outOfScope dflags x =
Orig _ occ -> monospaced occ
Exact name -> monospaced name -- Shouldn't happen since x is out of scope
where
+ monospaced :: (Outputable a) => a -> Doc b
monospaced a = DocMonospaced (DocString (showPpr dflags a))
makeAnchorId :: String -> String
diff --git a/src/HaskellCodeExplorer/ModuleInfo.hs b/src/HaskellCodeExplorer/ModuleInfo.hs
index cc81a36..ddd7e9f 100644
--- a/src/HaskellCodeExplorer/ModuleInfo.hs
+++ b/src/HaskellCodeExplorer/ModuleInfo.hs
@@ -6,6 +6,7 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE StrictData #-}
module HaskellCodeExplorer.ModuleInfo
@@ -23,8 +24,11 @@ import qualified Data.Map.Strict as M
import qualified Data.IntMap.Strict as IM
import qualified Data.IntervalMap.Strict as IVM
import qualified Data.List as L hiding (span)
-import Data.Maybe(fromMaybe,mapMaybe)
-import Data.Ord(comparing)
+import Data.Maybe (fromMaybe, mapMaybe)
+import Data.Ord (comparing)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+import HsExtension (GhcRn)
+#endif
import qualified Data.Set as S
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
@@ -307,10 +311,17 @@ createDefinitionSiteMap ::
-> HCE.SourceCodeTransformation
-> ModuleInfo
-> [Name]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ -> HsGroup GhcRn
+#else
-> HsGroup Name
+#endif
-> (HCE.DefinitionSiteMap, [Name])
createDefinitionSiteMap flags currentPackageId compId defSiteMap fileMap globalRdrEnv transformation modInfo dataFamTyCons hsGroup =
- let allDecls :: [GenLocated SrcSpan (HsDecl Name)]
+ let
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ allDecls :: [GenLocated SrcSpan (HsDecl GhcRn)]
+#endif
allDecls = L.sortBy (comparing getLoc) . ungroup $ hsGroup
(instanceDeclsWithDocs, valueAndTypeDeclsWithDocs) =
L.partition
@@ -465,7 +476,11 @@ docWithNamesToHtml flags packageId compId transformation fileMap defSiteMap =
createDeclarations ::
DynFlags
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ -> HsGroup GhcRn
+#else
-> HsGroup Name
+#endif
-> TypeEnv
-> S.Set Name
-> HCE.SourceCodeTransformation
@@ -483,8 +498,9 @@ createDeclarations flags hsGroup typeEnv exportedSet transformation =
Nothing -> Nothing
-- | Top-level functions
--------------------------------------------------------------------------------
- valToDeclarations ::
- GenLocated SrcSpan (HsBindLR Name Name) -> [HCE.Declaration]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ valToDeclarations :: GenLocated SrcSpan (HsBindLR GhcRn GhcRn) -> [HCE.Declaration]
+#endif
valToDeclarations (L loc bind) =
map
(\name ->
@@ -498,7 +514,9 @@ createDeclarations flags hsGroup typeEnv exportedSet transformation =
vals = concatMap valToDeclarations $ hsGroupVals hsGroup
-- | Data, newtype, type, type family, data family or class declaration
--------------------------------------------------------------------------------
- tyClToDeclaration :: GenLocated SrcSpan (TyClDecl Name) -> HCE.Declaration
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ tyClToDeclaration :: GenLocated SrcSpan (TyClDecl GhcRn) -> HCE.Declaration
+#endif
tyClToDeclaration (L loc tyClDecl) =
HCE.Declaration
HCE.TyClD
@@ -512,7 +530,9 @@ createDeclarations flags hsGroup typeEnv exportedSet transformation =
hsGroup
-- | Instances
--------------------------------------------------------------------------------
- instToDeclaration :: GenLocated SrcSpan (InstDecl Name) -> HCE.Declaration
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ instToDeclaration :: GenLocated SrcSpan (InstDecl GhcRn) -> HCE.Declaration
+#endif
instToDeclaration (L loc inst) =
HCE.Declaration
HCE.InstD
@@ -529,8 +549,10 @@ createDeclarations flags hsGroup typeEnv exportedSet transformation =
hsGroup
-- | Foreign functions
--------------------------------------------------------------------------------
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
foreignFunToDeclaration ::
- GenLocated SrcSpan (ForeignDecl Name) -> HCE.Declaration
+ GenLocated SrcSpan (ForeignDecl GhcRn) -> HCE.Declaration
+#endif
foreignFunToDeclaration (L loc fd) =
let name = unLoc $ fd_name fd
in HCE.Declaration
@@ -588,7 +610,11 @@ foldAST environment typecheckedModule =
case mbExported of
Just lieNames ->
mapMaybe
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ (\(L span ie,_) ->
+#else
(\(L span ie) ->
+#endif
case ie of
IEModuleContents (L _ modName) ->
Just
diff --git a/src/HaskellCodeExplorer/Types.hs b/src/HaskellCodeExplorer/Types.hs
index 9e3667d..f94b3af 100644
--- a/src/HaskellCodeExplorer/Types.hs
+++ b/src/HaskellCodeExplorer/Types.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DeriveDataTypeable #-}
@@ -47,6 +48,11 @@ import Documentation.Haddock.Types
, Header(..)
, Hyperlink(..)
, Picture(..)
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ , Table(..)
+ , TableCell(..)
+ , TableRow(..)
+#endif
)
import GHC.Generics (Generic)
import Prelude hiding (id)
@@ -781,7 +787,7 @@ docToHtml modToHtml idToHtml = toStrict . renderHtml . toH
in htmlPrompt >> htmlExpression >>
mapM_ (Html.span . Html.toHtml) (unlines results))
examples
- toH (DocString str) = Html.span . Html.toHtml $ T.pack str
+ toH (DocString str) = Html.span . Html.toHtml $ T.pack str
toH (DocHeader (Header level doc)) = toHeader level $ toH doc
where
toHeader 1 = Html.h1
@@ -790,6 +796,18 @@ docToHtml modToHtml idToHtml = toStrict . renderHtml . toH
toHeader 4 = Html.h4
toHeader 5 = Html.h5
toHeader _ = Html.h6
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
+ toH (DocTable (Table hs bs)) =
+ let tableRowToH tdOrTh (TableRow cells) =
+ Html.tr $ mapM_ (tableCellToH tdOrTh) cells
+ tableCellToH tdOrTh (TableCell colspan rowspan doc) =
+ (tdOrTh $ toH doc) Html.!?
+ (colspan /= 1, (Attr.colspan (Html.stringValue $ show colspan))) Html.!?
+ (rowspan /= 1, (Attr.rowspan (Html.stringValue $ show rowspan)))
+ in Html.table $
+ Html.thead (mapM_ (tableRowToH Html.th) hs) >>
+ Html.tbody (mapM_ (tableRowToH Html.td) bs)
+#endif
instance A.ToJSON HaskellModuleName where
toJSON (HaskellModuleName name) = A.String name
diff --git a/stack-8.2.2.yaml b/stack-8.2.2.yaml
new file mode 100644
index 0000000..96d1825
--- /dev/null
+++ b/stack-8.2.2.yaml
@@ -0,0 +1,10 @@
+resolver: lts-11.3
+packages:
+- '.'
+packages:
+ - .
+ - location: vendor/cabal-helper-0.8.1.2
+ extra-dep: true
+extra-deps:
+ - cabal-plan-0.4.0.0
+ - pretty-show-1.8.2
diff --git a/stack-8.4.3.yaml b/stack-8.4.3.yaml
deleted file mode 100644
index f3b6036..0000000
--- a/stack-8.4.3.yaml
+++ /dev/null
@@ -1,9 +0,0 @@
-# stack build haskell-code-explorer:haskell-code-server --stack-yaml=stack-8.4.3.yaml
-resolver: lts-12.4
-packages:
-- '.'
-allow-newer: true
-extra-deps:
- - cabal-helper-0.8.1.0
- - cabal-plan-0.3.0.0
-
diff --git a/stack.yaml b/stack.yaml
index 96d1825..f086c39 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -1,10 +1,8 @@
-resolver: lts-11.3
+resolver: lts-12.12
packages:
- '.'
-packages:
- - .
- - location: vendor/cabal-helper-0.8.1.2
- extra-dep: true
+- location: vendor/cabal-helper-0.8.1.2
+ extra-dep: true
+allow-newer: true
extra-deps:
- - cabal-plan-0.4.0.0
- - pretty-show-1.8.2
+ - cabal-plan-0.4.0.0
diff --git a/test/Main.hs b/test/Main.hs
index f2247fb..11b94fb 100644
--- a/test/Main.hs
+++ b/test/Main.hs
@@ -140,17 +140,25 @@ moduleInfoSpec modInfo =
it "returns valid map of identifiers " $
let removeLocationInfo :: HCE.LocationInfo -> HCE.LocationInfo
removeLocationInfo _ = HCE.UnknownLocation ""
- in U.transformBi
- removeLocationInfo
- (HCE.idInfoMap (modInfo :: HCE.ModuleInfo)) `shouldBe`
- U.transformBi removeLocationInfo testIdInfoMap
+ removePackageVersionFromExternalId :: HCE.ExternalId -> HCE.ExternalId
+ removePackageVersionFromExternalId extId@(HCE.ExternalId textId) = case T.splitOn "|" textId of
+ packageId:rest -> case T.splitOn "-" packageId of
+ packageIdParts@(_:_) -> HCE.ExternalId $ T.intercalate "|" ((T.intercalate "-" (init packageIdParts)) : rest)
+ _ -> extId
+ _ -> extId
+ cleanup :: HCE.IdentifierInfoMap -> HCE.IdentifierInfoMap
+ cleanup = U.transformBi removeLocationInfo . U.transformBi removePackageVersionFromExternalId
+ in
+ cleanup (HCE.idInfoMap (modInfo :: HCE.ModuleInfo)) `shouldBe` cleanup testIdInfoMap
#endif
it "returns valid map of identifier occurrences" $
HCE.idOccMap (modInfo :: HCE.ModuleInfo) `shouldBe` testIdOccMap
-stackYamlArg :: [String]
-#if MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
+stackYamlArg :: [String]
+#if MIN_VERSION_GLASGOW_HASKELL(8,4,3,0)
stackYamlArg = []
+#elif MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)
+stackYamlArg = ["--stack-yaml=stack-8.2.2.yaml" ]
#else
stackYamlArg = ["--stack-yaml=stack-8.0.2.yaml" ]
#endif
@@ -177,7 +185,7 @@ buildAndIndexTestPackage currentDir = do
_ <-
readProcess
stackExecutable
- (["build", "--test"] ++ stackYamlArg)
+ (["build", "--test","--force-dirty"] ++ stackYamlArg)
""
runLoggingT
(createPackageInfo
@@ -1209,3 +1217,5 @@ testIdInfoMap =
, isExported = False
})
]
+
+
diff --git a/test/test-package/stack-8.2.2.yaml b/test/test-package/stack-8.2.2.yaml
new file mode 100644
index 0000000..5bad591
--- /dev/null
+++ b/test/test-package/stack-8.2.2.yaml
@@ -0,0 +1 @@
+resolver: lts-11.3
diff --git a/test/test-package/stack.yaml b/test/test-package/stack.yaml
index 5bad591..80a9a5a 100644
--- a/test/test-package/stack.yaml
+++ b/test/test-package/stack.yaml
@@ -1 +1 @@
-resolver: lts-11.3
+resolver: lts-12.12