Merge branch 'ghci-style-load2' of github.com:khorser/ghc-mod into khorser-ghci-style-load2

Conflicts:
	Language/Haskell/GhcMod/Browse.hs
This commit is contained in:
Kazu Yamamoto 2013-11-20 14:28:20 +09:00
commit 831fc67c8c
2 changed files with 26 additions and 1 deletions

View File

@ -8,6 +8,7 @@ import Data.Maybe (catMaybes)
import DataCon (dataConRepType)
import FastString (mkFastString)
import GHC
import Panic(throwGhcException)
import Language.Haskell.GhcMod.Doc (showUnqualifiedPage)
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Types
@ -39,9 +40,23 @@ browse opt cradle mdlName = do
void $ initializeFlagsWithCradle opt cradle [] False
getModule >>= getModuleInfo >>= listExports
where
getModule = findModule (mkModuleName mdlName) (mkFastString <$> packageId opt)
getModule = findModule mdlname mpkgid `gcatch` fallback
mdlname = mkModuleName mdlName
mpkgid = mkFastString <$> packageId opt
listExports Nothing = return []
listExports (Just mdinfo) = processExports opt mdinfo
-- findModule works only for package modules, moreover,
-- you cannot load a package module. On the other hand,
-- to browse a local module you need to load it first.
-- If CmdLineError is signalled, we assume the user
-- tried browsing a local module.
fallback (CmdLineError _) = loadAndFind
fallback e = throwGhcException e
loadAndFind = do
setTargetFiles [mdlName]
checkSlowAndSet
void $ load LoadAllTargets
findModule mdlname Nothing
processExports :: Options -> ModuleInfo -> Ghc [String]
processExports opt minfo = mapM (showExport opt minfo) $ removeOps $ modInfoExports minfo

View File

@ -2,8 +2,11 @@ module BrowseSpec where
import Control.Applicative
import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Cradle
import Test.Hspec
import Dir
spec :: Spec
spec = do
describe "browseModule" $ do
@ -22,3 +25,10 @@ spec = do
cradle <- findCradle
syms <- lines <$> browseModule defaultOptions { detailed = True} cradle "Data.Either"
syms `shouldContain` ["Left :: a -> Either a b"]
describe "browseModule local" $ do
it "lists symbols in a local module" $ do
withDirectory_ "test/data" $ do
cradle <- findCradleWithoutSandbox
syms <- lines <$> browseModule defaultOptions cradle "Baz"
syms `shouldContain` ["baz"]