Add back -d
option to modules
command
This commit is contained in:
parent
eb5d0fc867
commit
2151363dd6
@ -38,6 +38,7 @@ module Language.Haskell.GhcMod.Gap (
|
|||||||
, occName
|
, occName
|
||||||
, listVisibleModuleNames
|
, listVisibleModuleNames
|
||||||
, listVisibleModules
|
, listVisibleModules
|
||||||
|
, lookupModulePackageInAllPackages
|
||||||
, Language.Haskell.GhcMod.Gap.isSynTyCon
|
, Language.Haskell.GhcMod.Gap.isSynTyCon
|
||||||
, parseModuleHeader
|
, parseModuleHeader
|
||||||
) where
|
) where
|
||||||
@ -89,20 +90,18 @@ import RdrName (rdrNameOcc)
|
|||||||
|
|
||||||
#if __GLASGOW_HASKELL__ < 710
|
#if __GLASGOW_HASKELL__ < 710
|
||||||
import UniqFM (eltsUFM)
|
import UniqFM (eltsUFM)
|
||||||
import Packages (exposedModules, exposed, pkgIdMap)
|
import Module
|
||||||
import PackageConfig (PackageConfig, packageConfigId)
|
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
#if __GLASGOW_HASKELL__ >= 704
|
#if __GLASGOW_HASKELL__ >= 704
|
||||||
import qualified Data.IntSet as I (IntSet, empty)
|
import qualified Data.IntSet as I (IntSet, empty)
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
|
||||||
import Bag
|
import Bag
|
||||||
import Lexer as L
|
import Lexer as L
|
||||||
import Parser
|
import Parser
|
||||||
import SrcLoc
|
import SrcLoc
|
||||||
|
import Packages
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
@ -476,6 +475,20 @@ listVisibleModuleNames :: DynFlags -> [ModuleName]
|
|||||||
listVisibleModuleNames = allExposedModules
|
listVisibleModuleNames = allExposedModules
|
||||||
#endif
|
#endif
|
||||||
|
|
||||||
|
lookupModulePackageInAllPackages ::
|
||||||
|
DynFlags -> ModuleName -> [String]
|
||||||
|
lookupModulePackageInAllPackages df mn =
|
||||||
|
#if __GLASGOW_HASKELL__ >= 710
|
||||||
|
unpackSPId . sourcePackageId . snd <$> lookupModuleInAllPackages df mn
|
||||||
|
where
|
||||||
|
unpackSPId (SourcePackageId fs) = unpackFS fs
|
||||||
|
#else
|
||||||
|
unpackPId . sourcePackageId . fst <$> lookupModuleInAllPackages df mn
|
||||||
|
where
|
||||||
|
unpackPId pid = packageIdString $ mkPackageId pid
|
||||||
|
-- n ++ "-" ++ showVersion v
|
||||||
|
#endif
|
||||||
|
|
||||||
listVisibleModules :: DynFlags -> [GHC.Module]
|
listVisibleModules :: DynFlags -> [GHC.Module]
|
||||||
listVisibleModules df = let
|
listVisibleModules df = let
|
||||||
#if __GLASGOW_HASKELL__ >= 710
|
#if __GLASGOW_HASKELL__ >= 710
|
||||||
|
@ -1,15 +1,26 @@
|
|||||||
module Language.Haskell.GhcMod.Modules (modules) where
|
module Language.Haskell.GhcMod.Modules (modules) where
|
||||||
|
|
||||||
import qualified GHC as G
|
import Control.Arrow
|
||||||
|
import Data.List
|
||||||
import Language.Haskell.GhcMod.Convert
|
import Language.Haskell.GhcMod.Convert
|
||||||
|
import Language.Haskell.GhcMod.Types
|
||||||
import Language.Haskell.GhcMod.Monad
|
import Language.Haskell.GhcMod.Monad
|
||||||
import Language.Haskell.GhcMod.Gap (listVisibleModuleNames)
|
import Language.Haskell.GhcMod.Gap ( listVisibleModuleNames
|
||||||
import Module (moduleNameString)
|
, lookupModulePackageInAllPackages
|
||||||
|
)
|
||||||
|
|
||||||
|
import qualified GHC as G
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
-- | Listing installed modules.
|
-- | Listing installed modules.
|
||||||
modules :: (IOish m, GmEnv m) => m String
|
modules :: (IOish m, GmEnv m) => m String
|
||||||
modules = do
|
modules = do
|
||||||
dflags <- runGmPkgGhc G.getSessionDynFlags
|
Options { detailed } <- options
|
||||||
convert' $ map moduleNameString $ listVisibleModuleNames dflags
|
df <- runGmPkgGhc G.getSessionDynFlags
|
||||||
|
let mns = listVisibleModuleNames df
|
||||||
|
pmnss = map (first moduleNameString) $ zip mns (modulePkg df `map` mns)
|
||||||
|
convert' $ nub [ if detailed then pkg ++ " " ++ mn else mn
|
||||||
|
| (mn, pkgs) <- pmnss, pkg <- pkgs ]
|
||||||
|
where
|
||||||
|
modulePkg df = lookupModulePackageInAllPackages df
|
||||||
|
@ -88,6 +88,9 @@ ghcModUsage =
|
|||||||
\\n\
|
\\n\
|
||||||
\ - list [FLAGS...] | modules [FLAGS...]\n\
|
\ - list [FLAGS...] | modules [FLAGS...]\n\
|
||||||
\ List all visible modules.\n\
|
\ List all visible modules.\n\
|
||||||
|
\ Flags:\n\
|
||||||
|
\ -d\n\
|
||||||
|
\ Print package modules belong to.\n\
|
||||||
\\n\
|
\\n\
|
||||||
\ - lang\n\
|
\ - lang\n\
|
||||||
\ List all known GHC language extensions.\n\
|
\ List all known GHC language extensions.\n\
|
||||||
@ -558,7 +561,8 @@ modulesCmd, languagesCmd, flagsCmd, browseCmd, checkSyntaxCmd, expandTemplateCmd
|
|||||||
findSymbolCmd, lintCmd, rootInfoCmd, pkgDocCmd, dumpSymbolCmd, bootCmd
|
findSymbolCmd, lintCmd, rootInfoCmd, pkgDocCmd, dumpSymbolCmd, bootCmd
|
||||||
:: IOish m => [String] -> GhcModT m String
|
:: IOish m => [String] -> GhcModT m String
|
||||||
|
|
||||||
modulesCmd = withParseCmd' "modules" [] $ \[] -> modules
|
modulesCmd = withParseCmd' "modules" s $ \[] -> modules
|
||||||
|
where s = modulesArgSpec
|
||||||
languagesCmd = withParseCmd' "lang" [] $ \[] -> languages
|
languagesCmd = withParseCmd' "lang" [] $ \[] -> languages
|
||||||
flagsCmd = withParseCmd' "flag" [] $ \[] -> flags
|
flagsCmd = withParseCmd' "flag" [] $ \[] -> flags
|
||||||
debugInfoCmd = withParseCmd' "debug" [] $ \[] -> debugInfo
|
debugInfoCmd = withParseCmd' "debug" [] $ \[] -> debugInfo
|
||||||
@ -571,7 +575,7 @@ findSymbolCmd = withParseCmd' "find" [] $ \[sym] -> findSymbol sym
|
|||||||
pkgDocCmd = withParseCmd' "doc" [] $ \[mdl] -> pkgDoc mdl
|
pkgDocCmd = withParseCmd' "doc" [] $ \[mdl] -> pkgDoc mdl
|
||||||
lintCmd = withParseCmd' "lint" s $ \[file] -> lint file
|
lintCmd = withParseCmd' "lint" s $ \[file] -> lint file
|
||||||
where s = hlintArgSpec
|
where s = hlintArgSpec
|
||||||
browseCmd = withParseCmd s $ \mdls -> concat <$> browse `mapM` mdls
|
browseCmd = withParseCmd s $ \mdls -> concat <$> browse `mapM` mdls
|
||||||
where s = browseArgSpec
|
where s = browseArgSpec
|
||||||
checkSyntaxCmd = withParseCmd [] $ checkAction checkSyntax
|
checkSyntaxCmd = withParseCmd [] $ checkAction checkSyntax
|
||||||
expandTemplateCmd = withParseCmd [] $ checkAction expandTemplate
|
expandTemplateCmd = withParseCmd [] $ checkAction expandTemplate
|
||||||
@ -601,6 +605,14 @@ locAction' _ action [f,_,line,col,expr] = action f (read line) (read col) expr
|
|||||||
locAction' _ action [f, line,col,expr] = action f (read line) (read col) expr
|
locAction' _ action [f, line,col,expr] = action f (read line) (read col) expr
|
||||||
locAction' cmd _ _ = throw $ InvalidCommandLine (Left cmd)
|
locAction' cmd _ _ = throw $ InvalidCommandLine (Left cmd)
|
||||||
|
|
||||||
|
|
||||||
|
modulesArgSpec :: [OptDescr (Options -> Options)]
|
||||||
|
modulesArgSpec =
|
||||||
|
[ option "d" ["detailed"] "Print package modules belong to." $
|
||||||
|
NoArg $ \o -> o { detailed = True }
|
||||||
|
]
|
||||||
|
|
||||||
|
|
||||||
hlintArgSpec :: [OptDescr (Options -> Options)]
|
hlintArgSpec :: [OptDescr (Options -> Options)]
|
||||||
hlintArgSpec =
|
hlintArgSpec =
|
||||||
[ option "h" ["hlintOpt"] "Option to be passed to hlint" $
|
[ option "h" ["hlintOpt"] "Option to be passed to hlint" $
|
||||||
|
Loading…
Reference in New Issue
Block a user