[Browse] Option to show symbol parents

E.g. Nothing is a constructor of Maybe, so it has
parent Maybe.

This is useful for completion, e.g. with `(..)` imports
This commit is contained in:
Nikolay Yakimov 2016-03-14 21:16:20 +03:00
parent 346d0868e0
commit 8e33dbd88d
4 changed files with 20 additions and 6 deletions

View File

@ -7,12 +7,13 @@ import Language.Haskell.GhcMod.Flag
import Language.Haskell.GhcMod.Lang
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Modules
import Language.Haskell.GhcMod.Types (defaultBrowseOpts)
-- | Printing necessary information for front-end booting.
boot :: IOish m => GhcModT m String
boot = concat <$> sequence ms
where
ms = [modules False, languages, flags, concat <$> mapM (browse (BrowseOpts False False False)) preBrowsedModules]
ms = [modules False, languages, flags, concat <$> mapM (browse defaultBrowseOpts) preBrowsedModules]
preBrowsedModules :: [String]
preBrowsedModules = [

View File

@ -11,6 +11,7 @@ import Data.List
import Data.Maybe
import FastString
import GHC
import HscTypes
import qualified GHC as G
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Doc (showPage, styleUnqualified)
@ -96,14 +97,20 @@ showExport opt minfo e = do
mqualified = (G.moduleNameString (G.moduleName $ G.nameModule e) ++ ".") `justIf` optBrowseQualified opt
mtype :: m (Maybe String)
mtype
| optBrowseDetailed opt = do
| optBrowseDetailed opt || optBrowseParents opt = do
tyInfo <- G.modInfoLookupName minfo e
-- If nothing found, load dependent module and lookup global
tyResult <- maybe (inOtherModule e) (return . Just) tyInfo
dflag <- G.getSessionDynFlags
return $ do
typeName <- tyResult >>= showThing dflag
(" :: " ++ typeName) `justIf` optBrowseDetailed opt
let sig = do
typeName <- tyResult >>= showThing dflag
(" :: " ++ typeName) `justIf` optBrowseDetailed opt
let parent = do
thing <- fmap getOccString $ tyResult >>= tyThingParent_maybe
(" ; " ++ thing) `justIf` optBrowseParents opt
return $ case concat $ catMaybes [sig, parent] of
[] -> Nothing
x -> Just x
| otherwise = return Nothing
formatOp nm
| null nm = error "formatOp"

View File

@ -388,13 +388,15 @@ data BrowseOpts = BrowseOpts {
-- ^ If 'True', "browseWith" also returns operators.
, optBrowseDetailed :: Bool
-- ^ If 'True', "browseWith" also returns types.
, optBrowseParents :: Bool
-- ^ If 'True', "browseWith" also returns parents.
, optBrowseQualified :: Bool
-- ^ If 'True', "browseWith" will return fully qualified name
} deriving (Show)
-- | Default "BrowseOpts" instance
defaultBrowseOpts :: BrowseOpts
defaultBrowseOpts = BrowseOpts False False False
defaultBrowseOpts = BrowseOpts False False False False
mkLabel ''GhcModCaches
mkLabel ''GhcModState

View File

@ -255,6 +255,10 @@ browseArgSpec = CmdBrowse
$$ long "detailed"
<=> short 'd'
<=> help "Print symbols with accompanying signature"
<*> switch
$$ long "parents"
<=> short 'p'
<=> help "Print symbols parents"
<*> switch
$$ long "qualified"
<=> short 'q'