Merge pull request #153 from eagletmt/cradle-list-and-browse
Make `ghc-mod list` and `ghc-mod browse` sandbox-aware
This commit is contained in:
commit
8e6e4b952b
@ -1,6 +1,7 @@
|
|||||||
module Language.Haskell.GhcMod.Browse (browseModule, browse) where
|
module Language.Haskell.GhcMod.Browse (browseModule, browse) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
import Control.Monad (void)
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
@ -21,9 +22,10 @@ import Var
|
|||||||
-- If 'detailed' is 'True', their types are also obtained.
|
-- If 'detailed' is 'True', their types are also obtained.
|
||||||
-- If 'operators' is 'True', operators are also returned.
|
-- If 'operators' is 'True', operators are also returned.
|
||||||
browseModule :: Options
|
browseModule :: Options
|
||||||
|
-> Cradle
|
||||||
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
||||||
-> IO String
|
-> IO String
|
||||||
browseModule opt mdlName = convert opt . format <$> withGHCDummyFile (browse opt mdlName)
|
browseModule opt cradle mdlName = convert opt . format <$> withGHCDummyFile (browse opt cradle mdlName)
|
||||||
where
|
where
|
||||||
format
|
format
|
||||||
| operators opt = formatOps
|
| operators opt = formatOps
|
||||||
@ -41,10 +43,11 @@ browseModule opt mdlName = convert opt . format <$> withGHCDummyFile (browse opt
|
|||||||
-- If 'detailed' is 'True', their types are also obtained.
|
-- If 'detailed' is 'True', their types are also obtained.
|
||||||
-- If 'operators' is 'True', operators are also returned.
|
-- If 'operators' is 'True', operators are also returned.
|
||||||
browse :: Options
|
browse :: Options
|
||||||
|
-> Cradle
|
||||||
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
||||||
-> Ghc [String]
|
-> Ghc [String]
|
||||||
browse opt mdlName = do
|
browse opt cradle mdlName = do
|
||||||
initializeFlags opt
|
void $ initializeFlagsWithCradle opt cradle [] False
|
||||||
getModule >>= getModuleInfo >>= listExports
|
getModule >>= getModuleInfo >>= listExports
|
||||||
where
|
where
|
||||||
getModule = findModule (mkModuleName mdlName) Nothing
|
getModule = findModule (mkModuleName mdlName) Nothing
|
||||||
|
@ -1,6 +1,7 @@
|
|||||||
module Language.Haskell.GhcMod.List (listModules, listMods) where
|
module Language.Haskell.GhcMod.List (listModules, listMods) where
|
||||||
|
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
import Control.Monad (void)
|
||||||
import Data.List
|
import Data.List
|
||||||
import GHC
|
import GHC
|
||||||
import Language.Haskell.GhcMod.GHCApi
|
import Language.Haskell.GhcMod.GHCApi
|
||||||
@ -11,13 +12,13 @@ import UniqFM
|
|||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
-- | Listing installed modules.
|
-- | Listing installed modules.
|
||||||
listModules :: Options -> IO String
|
listModules :: Options -> Cradle -> IO String
|
||||||
listModules opt = convert opt . nub . sort <$> withGHCDummyFile (listMods opt)
|
listModules opt cradle = convert opt . nub . sort <$> withGHCDummyFile (listMods opt cradle)
|
||||||
|
|
||||||
-- | Listing installed modules.
|
-- | Listing installed modules.
|
||||||
listMods :: Options -> Ghc [String]
|
listMods :: Options -> Cradle -> Ghc [String]
|
||||||
listMods opt = do
|
listMods opt cradle = do
|
||||||
initializeFlags opt
|
void $ initializeFlagsWithCradle opt cradle [] False
|
||||||
getExposedModules <$> getSessionDynFlags
|
getExposedModules <$> getSessionDynFlags
|
||||||
where
|
where
|
||||||
getExposedModules = map moduleNameString
|
getExposedModules = map moduleNameString
|
||||||
|
@ -96,8 +96,8 @@ main = flip catches handlers $ do
|
|||||||
then f
|
then f
|
||||||
else throw (TooManyArguments cmdArg0)
|
else throw (TooManyArguments cmdArg0)
|
||||||
res <- case cmdArg0 of
|
res <- case cmdArg0 of
|
||||||
"browse" -> concat <$> mapM (browseModule opt) remainingArgs
|
"browse" -> concat <$> mapM (browseModule opt cradle) remainingArgs
|
||||||
"list" -> listModules opt
|
"list" -> listModules opt cradle
|
||||||
"check" -> checkSyntax opt cradle remainingArgs
|
"check" -> checkSyntax opt cradle remainingArgs
|
||||||
"expand" -> checkSyntax opt { expandSplice = True } cradle remainingArgs
|
"expand" -> checkSyntax opt { expandSplice = True } cradle remainingArgs
|
||||||
"debug" -> nArgs 1 $ debugInfo opt cradle cmdArg1
|
"debug" -> nArgs 1 $ debugInfo opt cradle cmdArg1
|
||||||
@ -107,10 +107,10 @@ main = flip catches handlers $ do
|
|||||||
"lang" -> listLanguages opt
|
"lang" -> listLanguages opt
|
||||||
"flag" -> listFlags opt
|
"flag" -> listFlags opt
|
||||||
"boot" -> do
|
"boot" -> do
|
||||||
mods <- listModules opt
|
mods <- listModules opt cradle
|
||||||
langs <- listLanguages opt
|
langs <- listLanguages opt
|
||||||
flags <- listFlags opt
|
flags <- listFlags opt
|
||||||
pre <- concat <$> mapM (browseModule opt) preBrowsedModules
|
pre <- concat <$> mapM (browseModule opt cradle) preBrowsedModules
|
||||||
return $ mods ++ langs ++ flags ++ pre
|
return $ mods ++ langs ++ flags ++ pre
|
||||||
"help" -> return $ usageInfo usage argspec
|
"help" -> return $ usageInfo usage argspec
|
||||||
cmd -> throw (NoSuchCommand cmd)
|
cmd -> throw (NoSuchCommand cmd)
|
||||||
|
@ -8,14 +8,17 @@ spec :: Spec
|
|||||||
spec = do
|
spec = do
|
||||||
describe "browseModule" $ do
|
describe "browseModule" $ do
|
||||||
it "lists up symbols in the module" $ do
|
it "lists up symbols in the module" $ do
|
||||||
syms <- lines <$> browseModule defaultOptions "Data.Map"
|
cradle <- findCradle
|
||||||
|
syms <- lines <$> browseModule defaultOptions cradle "Data.Map"
|
||||||
syms `shouldContain` ["differenceWithKey"]
|
syms `shouldContain` ["differenceWithKey"]
|
||||||
|
|
||||||
describe "browseModule -d" $ do
|
describe "browseModule -d" $ do
|
||||||
it "lists up symbols with type info in the module" $ do
|
it "lists up symbols with type info in the module" $ do
|
||||||
syms <- lines <$> browseModule defaultOptions { detailed = True } "Data.Either"
|
cradle <- findCradle
|
||||||
|
syms <- lines <$> browseModule defaultOptions { detailed = True } cradle "Data.Either"
|
||||||
syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"]
|
syms `shouldContain` ["either :: (a -> c) -> (b -> c) -> Either a b -> c"]
|
||||||
|
|
||||||
it "lists up data constructors with type info in the module" $ do
|
it "lists up data constructors with type info in the module" $ do
|
||||||
syms <- lines <$> browseModule defaultOptions { detailed = True} "Data.Either"
|
cradle <- findCradle
|
||||||
|
syms <- lines <$> browseModule defaultOptions { detailed = True} cradle "Data.Either"
|
||||||
syms `shouldContain` ["Left :: a -> Either a b"]
|
syms `shouldContain` ["Left :: a -> Either a b"]
|
||||||
|
@ -8,5 +8,6 @@ spec :: Spec
|
|||||||
spec = do
|
spec = do
|
||||||
describe "listModules" $ do
|
describe "listModules" $ do
|
||||||
it "lists up module names" $ do
|
it "lists up module names" $ do
|
||||||
modules <- lines <$> listModules defaultOptions
|
cradle <- findCradle
|
||||||
|
modules <- lines <$> listModules defaultOptions cradle
|
||||||
modules `shouldContain` ["Data.Map"]
|
modules `shouldContain` ["Data.Map"]
|
||||||
|
Loading…
Reference in New Issue
Block a user