Merge pull request #257 from DanielG/dev-monad

Migrate Browse and Check to GhcMod monad
This commit is contained in:
Kazu Yamamoto 2014-05-15 10:45:54 +09:00
commit e3ff15862f
24 changed files with 320 additions and 263 deletions

View File

@ -14,7 +14,7 @@ module Language.Haskell.GhcMod (
, Expression , Expression
-- * 'IO' utilities -- * 'IO' utilities
, bootInfo , bootInfo
, browseModule , browse
, checkSyntax , checkSyntax
, lintSyntax , lintSyntax
, expandTemplate , expandTemplate

View File

@ -2,27 +2,25 @@ module Language.Haskell.GhcMod.Boot where
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import CoreMonad (liftIO, liftIO) import CoreMonad (liftIO, liftIO)
import GHC (Ghc)
import Language.Haskell.GhcMod.Browse import Language.Haskell.GhcMod.Browse
import Language.Haskell.GhcMod.Flag import Language.Haskell.GhcMod.Flag
import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Lang import Language.Haskell.GhcMod.Lang
import Language.Haskell.GhcMod.List import Language.Haskell.GhcMod.List
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
-- | Printing necessary information for front-end booting. -- | Printing necessary information for front-end booting.
bootInfo :: Options -> Cradle -> IO String bootInfo :: Options -> IO String
bootInfo opt cradle = withGHC' $ do bootInfo opt = runGhcMod opt $ boot
initializeFlagsWithCradle opt cradle
boot opt
-- | Printing necessary information for front-end booting. -- | Printing necessary information for front-end booting.
boot :: Options -> Ghc String boot :: GhcMod String
boot opt = do boot = do
mods <- modules opt opt <- options
mods <- modules
langs <- liftIO $ listLanguages opt langs <- liftIO $ listLanguages opt
flags <- liftIO $ listFlags opt flags <- liftIO $ listFlags opt
pre <- concat <$> mapM (browse opt) preBrowsedModules pre <- concat <$> mapM browse preBrowsedModules
return $ mods ++ langs ++ flags ++ pre return $ mods ++ langs ++ flags ++ pre
preBrowsedModules :: [String] preBrowsedModules :: [String]

View File

@ -1,6 +1,5 @@
module Language.Haskell.GhcMod.Browse ( module Language.Haskell.GhcMod.Browse (
browseModule browse
, browse
, browseAll) , browseAll)
where where
@ -11,11 +10,13 @@ import Data.List (sort)
import Data.Maybe (catMaybes) import Data.Maybe (catMaybes)
import Exception (ghandle) import Exception (ghandle)
import FastString (mkFastString) import FastString (mkFastString)
import GHC (Ghc, GhcException(CmdLineError), ModuleInfo, Name, TyThing, DynFlags, Type, TyCon, Module) import GHC (GhcException(CmdLineError), ModuleInfo, Name, TyThing, DynFlags, Type, TyCon, Module)
import qualified GHC as G import qualified GHC as G
import Language.Haskell.GhcMod.Doc (showPage, showOneLine, styleUnqualified) import Language.Haskell.GhcMod.Doc (showPage, showOneLine, styleUnqualified)
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Gap import Language.Haskell.GhcMod.Gap
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Name (getOccString) import Name (getOccString)
import Outputable (ppr, Outputable) import Outputable (ppr, Outputable)
@ -27,28 +28,15 @@ import Type (dropForAlls, splitFunTy_maybe, mkFunTy, isPredTy)
-- | Getting functions, classes, etc from a module. -- | Getting functions, classes, etc from a module.
-- 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 browse :: ModuleString -- ^ A module name. (e.g. \"Data.List\")
-> Cradle -> GhcMod String
-> ModuleString -- ^ A module name. (e.g. \"Data.List\") browse pkgmdl = convert' . sort =<< (listExports =<< getModule)
-> IO String
browseModule opt cradle pkgmdl = withGHC' $ do
initializeFlagsWithCradle opt cradle
browse opt pkgmdl
-- | Getting functions, classes, etc from a module.
-- If 'detailed' is 'True', their types are also obtained.
-- If 'operators' is 'True', operators are also returned.
browse :: Options
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
-> Ghc String
browse opt pkgmdl = do
convert opt . sort <$> (getModule >>= listExports)
where where
(mpkg,mdl) = splitPkgMdl pkgmdl (mpkg,mdl) = splitPkgMdl pkgmdl
mdlname = G.mkModuleName mdl mdlname = G.mkModuleName mdl
mpkgid = mkFastString <$> mpkg mpkgid = mkFastString <$> mpkg
listExports Nothing = return [] listExports Nothing = return []
listExports (Just mdinfo) = processExports opt mdinfo listExports (Just mdinfo) = processExports mdinfo
-- findModule works only for package modules, moreover, -- findModule works only for package modules, moreover,
-- you cannot load a package module. On the other hand, -- you cannot load a package module. On the other hand,
-- to browse a local module you need to load it first. -- to browse a local module you need to load it first.
@ -73,19 +61,22 @@ splitPkgMdl pkgmdl = case break (==':') pkgmdl of
(mdl,"") -> (Nothing,mdl) (mdl,"") -> (Nothing,mdl)
(pkg,_:mdl) -> (Just pkg,mdl) (pkg,_:mdl) -> (Just pkg,mdl)
processExports :: Options -> ModuleInfo -> Ghc [String] processExports :: ModuleInfo -> GhcMod [String]
processExports opt minfo = mapM (showExport opt minfo) $ removeOps $ G.modInfoExports minfo processExports minfo = do
where opt <- options
let
removeOps removeOps
| operators opt = id | operators opt = id
| otherwise = filter (isAlpha . head . getOccString) | otherwise = filter (isAlpha . head . getOccString)
mapM (showExport opt minfo) $ removeOps $ G.modInfoExports minfo
showExport :: Options -> ModuleInfo -> Name -> Ghc String showExport :: Options -> ModuleInfo -> Name -> GhcMod String
showExport opt minfo e = do showExport opt minfo e = do
mtype' <- mtype mtype' <- mtype
return $ concat $ catMaybes [mqualified, Just $ formatOp $ getOccString e, mtype'] return $ concat $ catMaybes [mqualified, Just $ formatOp $ getOccString e, mtype']
where where
mqualified = (G.moduleNameString (G.moduleName $ G.nameModule e) ++ ".") `justIf` qualified opt mqualified = (G.moduleNameString (G.moduleName $ G.nameModule e) ++ ".") `justIf` qualified opt
mtype :: GhcMod (Maybe String)
mtype mtype
| detailed opt = do | detailed opt = do
tyInfo <- G.modInfoLookupName minfo e tyInfo <- G.modInfoLookupName minfo e
@ -100,7 +91,7 @@ showExport opt minfo e = do
| isAlpha n = nm | isAlpha n = nm
| otherwise = "(" ++ nm ++ ")" | otherwise = "(" ++ nm ++ ")"
formatOp "" = error "formatOp" formatOp "" = error "formatOp"
inOtherModule :: Name -> Ghc (Maybe TyThing) inOtherModule :: Name -> GhcMod (Maybe TyThing)
inOtherModule nm = G.getModuleInfo (G.nameModule nm) >> G.lookupGlobalName nm inOtherModule nm = G.getModuleInfo (G.nameModule nm) >> G.lookupGlobalName nm
justIf :: a -> Bool -> Maybe a justIf :: a -> Bool -> Maybe a
justIf x True = Just x justIf x True = Just x
@ -147,7 +138,7 @@ showOutputable dflag = unwords . lines . showPage dflag styleUnqualified . ppr
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Browsing all functions in all system/user modules. -- | Browsing all functions in all system/user modules.
browseAll :: DynFlags -> Ghc [(String,String)] browseAll :: DynFlags -> GhcMod [(String,String)]
browseAll dflag = do browseAll dflag = do
ms <- G.packageDbModules True ms <- G.packageDbModules True
is <- mapM G.getModuleInfo ms is <- mapM G.getModuleInfo ms

View File

@ -6,24 +6,20 @@ module Language.Haskell.GhcMod.Check (
) where ) where
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import GHC (Ghc)
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
import qualified Language.Haskell.GhcMod.Gap as Gap import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Logger import Language.Haskell.GhcMod.Logger
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Monad
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Checking syntax of a target file using GHC. -- | Checking syntax of a target file using GHC.
-- Warnings and errors are returned. -- Warnings and errors are returned.
checkSyntax :: Options checkSyntax :: [FilePath] -- ^ The target files.
-> Cradle -> GhcMod String
-> [FilePath] -- ^ The target files. checkSyntax [] = return ""
-> IO String checkSyntax files = withErrorHandler sessionName $ do
checkSyntax _ _ [] = return "" either id id <$> check files
checkSyntax opt cradle files = withGHC sessionName $ do
initializeFlagsWithCradle opt cradle
either id id <$> check opt files
where where
sessionName = case files of sessionName = case files of
[file] -> file [file] -> file
@ -33,23 +29,20 @@ checkSyntax opt cradle files = withGHC sessionName $ do
-- | Checking syntax of a target file using GHC. -- | Checking syntax of a target file using GHC.
-- Warnings and errors are returned. -- Warnings and errors are returned.
check :: Options check :: [FilePath] -- ^ The target files.
-> [FilePath] -- ^ The target files. -> GhcMod (Either String String)
-> Ghc (Either String String) check fileNames = do
check opt fileNames = withLogger opt setAllWaringFlags $ withLogger setAllWaringFlags $ do
setTargetFiles fileNames setTargetFiles fileNames
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Expanding Haskell Template. -- | Expanding Haskell Template.
expandTemplate :: Options expandTemplate :: [FilePath] -- ^ The target files.
-> Cradle -> GhcMod String
-> [FilePath] -- ^ The target files. expandTemplate [] = return ""
-> IO String expandTemplate files = withErrorHandler sessionName $ do
expandTemplate _ _ [] = return "" either id id <$> expand files
expandTemplate opt cradle files = withGHC sessionName $ do
initializeFlagsWithCradle opt cradle
either id id <$> expand opt files
where where
sessionName = case files of sessionName = case files of
[file] -> file [file] -> file
@ -58,8 +51,7 @@ expandTemplate opt cradle files = withGHC sessionName $ do
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Expanding Haskell Template. -- | Expanding Haskell Template.
expand :: Options expand :: [FilePath] -- ^ The target files.
-> [FilePath] -- ^ The target files. -> GhcMod (Either String String)
-> Ghc (Either String String) expand fileNames = withLogger (Gap.setDumpSplices . setNoWaringFlags) $
expand opt fileNames = withLogger opt (Gap.setDumpSplices . setNoWaringFlags) $
setTargetFiles fileNames setTargetFiles fileNames

View File

@ -0,0 +1,103 @@
{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.Convert (convert, convert') where
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types
import Control.Applicative ((<$>))
type Builder = String -> String
-- |
--
-- >>> replace '"' "\\\"" "foo\"bar" ""
-- "foo\\\"bar"
replace :: Char -> String -> String -> Builder
replace _ _ [] = id
replace c cs (x:xs)
| x == c = (cs ++) . replace c cs xs
| otherwise = (x :) . replace c cs xs
inter :: Char -> [Builder] -> Builder
inter _ [] = id
inter c bs = foldr1 (\x y -> x . (c:) . y) bs
convert' :: ToString a => a -> GhcMod String
convert' x = flip convert x <$> options
convert :: ToString a => Options -> a -> String
convert opt@Options { outputStyle = LispStyle } x = toLisp opt x "\n"
convert opt@Options { outputStyle = PlainStyle } x
| str == "\n" = ""
| otherwise = str
where
str = toPlain opt x "\n"
class ToString a where
toLisp :: Options -> a -> Builder
toPlain :: Options -> a -> Builder
lineSep :: Options -> String
lineSep opt = lsep
where
LineSeparator lsep = lineSeparator opt
-- |
--
-- >>> toLisp defaultOptions "fo\"o" ""
-- "\"fo\\\"o\""
-- >>> toPlain defaultOptions "foo" ""
-- "foo"
instance ToString String where
toLisp opt = quote opt
toPlain opt = replace '\n' (lineSep opt)
-- |
--
-- >>> toLisp defaultOptions ["foo", "bar", "ba\"z"] ""
-- "(\"foo\" \"bar\" \"ba\\\"z\")"
-- >>> toPlain defaultOptions ["foo", "bar", "baz"] ""
-- "foo\nbar\nbaz"
instance ToString [String] where
toLisp opt = toSexp1 opt
toPlain opt = inter '\n' . map (toPlain opt)
-- |
--
-- >>> let inp = [((1,2,3,4),"foo"),((5,6,7,8),"bar")] :: [((Int,Int,Int,Int),String)]
-- >>> toLisp defaultOptions inp ""
-- "((1 2 3 4 \"foo\") (5 6 7 8 \"bar\"))"
-- >>> toPlain defaultOptions inp ""
-- "1 2 3 4 \"foo\"\n5 6 7 8 \"bar\""
instance ToString [((Int,Int,Int,Int),String)] where
toLisp opt = toSexp2 . map toS
where
toS x = ('(' :) . tupToString opt x . (')' :)
toPlain opt = inter '\n' . map (tupToString opt)
toSexp1 :: Options -> [String] -> Builder
toSexp1 opt ss = ('(' :) . inter ' ' (map (quote opt) ss) . (')' :)
toSexp2 :: [Builder] -> Builder
toSexp2 ss = ('(' :) . (inter ' ' ss) . (')' :)
tupToString :: Options -> ((Int,Int,Int,Int),String) -> Builder
tupToString opt ((a,b,c,d),s) = (show a ++) . (' ' :)
. (show b ++) . (' ' :)
. (show c ++) . (' ' :)
. (show d ++) . (' ' :)
. quote opt s -- fixme: quote is not necessary
quote :: Options -> String -> Builder
quote opt str = ("\"" ++) . (quote' str ++) . ("\"" ++)
where
lsep = lineSep opt
quote' [] = []
quote' (x:xs)
| x == '\n' = lsep ++ quote' xs
| x == '\\' = "\\\\" ++ quote' xs
| x == '"' = "\\\"" ++ quote' xs
| otherwise = x : quote' xs
----------------------------------------------------------------

View File

@ -7,6 +7,7 @@ import Data.List (intercalate)
import Data.Maybe (fromMaybe, isJust, fromJust) import Data.Maybe (fromMaybe, isJust, fromJust)
import Language.Haskell.GhcMod.CabalApi import Language.Haskell.GhcMod.CabalApi
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
---------------------------------------------------------------- ----------------------------------------------------------------

View File

@ -5,10 +5,10 @@ module Language.Haskell.GhcMod.Find where
import Data.Function (on) import Data.Function (on)
import Data.List (groupBy, sort) import Data.List (groupBy, sort)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import GHC (Ghc)
import qualified GHC as G import qualified GHC as G
import Language.Haskell.GhcMod.Browse (browseAll) import Language.Haskell.GhcMod.Browse (browseAll)
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
#ifndef MIN_VERSION_containers #ifndef MIN_VERSION_containers
@ -31,13 +31,11 @@ type Symbol = String
newtype SymMdlDb = SymMdlDb (Map Symbol [ModuleString]) newtype SymMdlDb = SymMdlDb (Map Symbol [ModuleString])
-- | Finding modules to which the symbol belong. -- | Finding modules to which the symbol belong.
findSymbol :: Options -> Cradle -> Symbol -> IO String findSymbol :: Symbol -> GhcMod String
findSymbol opt cradle sym = withGHC' $ do findSymbol sym = convert' =<< lookupSym sym <$> getSymMdlDb
initializeFlagsWithCradle opt cradle
lookupSym opt sym <$> getSymMdlDb
-- | Creating 'SymMdlDb'. -- | Creating 'SymMdlDb'.
getSymMdlDb :: Ghc SymMdlDb getSymMdlDb :: GhcMod SymMdlDb
getSymMdlDb = do getSymMdlDb = do
sm <- G.getSessionDynFlags >>= browseAll sm <- G.getSessionDynFlags >>= browseAll
#if MIN_VERSION_containers(0,5,0) #if MIN_VERSION_containers(0,5,0)
@ -52,5 +50,8 @@ getSymMdlDb = do
tieup x = (head (map fst x), map snd x) tieup x = (head (map fst x), map snd x)
-- | Looking up 'SymMdlDb' with 'Symbol' to find modules. -- | Looking up 'SymMdlDb' with 'Symbol' to find modules.
lookupSym :: Options -> Symbol -> SymMdlDb -> String lookupSym :: Symbol -> SymMdlDb -> [ModuleString]
lookupSym opt sym (SymMdlDb db) = convert opt $ fromMaybe [] (M.lookup sym db) lookupSym sym (SymMdlDb db) = fromMaybe [] (M.lookup sym db)
lookupSym' :: Options -> Symbol -> SymMdlDb -> String
lookupSym' opt sym db = convert opt $ lookupSym sym db

View File

@ -1,6 +1,7 @@
module Language.Haskell.GhcMod.Flag where module Language.Haskell.GhcMod.Flag where
import qualified Language.Haskell.GhcMod.Gap as Gap import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
-- | Listing GHC flags. (e.g -fno-warn-orphans) -- | Listing GHC flags. (e.g -fno-warn-orphans)

View File

@ -164,22 +164,25 @@ getDynamicFlags = do
mlibdir <- getSystemLibDir mlibdir <- getSystemLibDir
G.runGhc mlibdir G.getSessionDynFlags G.runGhc mlibdir G.getSessionDynFlags
withDynFlags :: (DynFlags -> DynFlags) -> Ghc a -> Ghc a withDynFlags :: GhcMonad m
withDynFlags setFlag body = G.gbracket setup teardown (\_ -> body) => (DynFlags -> DynFlags)
-> m a
-> m a
withDynFlags setFlags body = G.gbracket setup teardown (\_ -> body)
where where
setup = do setup = do
dflag <- G.getSessionDynFlags dflags <- G.getSessionDynFlags
void $ G.setSessionDynFlags (setFlag dflag) void $ G.setSessionDynFlags (setFlags dflags)
return dflag return dflags
teardown = void . G.setSessionDynFlags teardown = void . G.setSessionDynFlags
withCmdFlags :: [GHCOption] -> Ghc a -> Ghc a withCmdFlags :: GhcMonad m => [GHCOption] -> m a -> m a
withCmdFlags flags body = G.gbracket setup teardown (\_ -> body) withCmdFlags flags body = G.gbracket setup teardown (\_ -> body)
where where
setup = do setup = do
dflag <- G.getSessionDynFlags >>= addCmdOpts flags dflags <- G.getSessionDynFlags >>= addCmdOpts flags
void $ G.setSessionDynFlags dflag void $ G.setSessionDynFlags dflags
return dflag return dflags
teardown = void . G.setSessionDynFlags teardown = void . G.setSessionDynFlags
---------------------------------------------------------------- ----------------------------------------------------------------

View File

@ -45,7 +45,7 @@ import ErrUtils
import FastString import FastString
import HscTypes import HscTypes
import Language.Haskell.GhcMod.GHCChoice import Language.Haskell.GhcMod.GHCChoice
import Language.Haskell.GhcMod.Types hiding (convert) import Language.Haskell.GhcMod.Types
import NameSet import NameSet
import Outputable import Outputable
import PprTyThing import PprTyThing

View File

@ -14,6 +14,7 @@ module Language.Haskell.GhcMod.Ghc (
, SymMdlDb , SymMdlDb
, getSymMdlDb , getSymMdlDb
, lookupSym , lookupSym
, lookupSym'
) where ) where
import Language.Haskell.GhcMod.Boot import Language.Haskell.GhcMod.Boot

View File

@ -25,6 +25,7 @@ import Language.Haskell.GhcMod.GHCApi
import Language.Haskell.GhcMod.Gap (HasType(..), setDeferTypeErrors) import Language.Haskell.GhcMod.Gap (HasType(..), setDeferTypeErrors)
import qualified Language.Haskell.GhcMod.Gap as Gap import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Convert
import Outputable (PprStyle) import Outputable (PprStyle)
import TcHsSyn (hsPatType) import TcHsSyn (hsPatType)

View File

@ -2,6 +2,7 @@ module Language.Haskell.GhcMod.Lang where
import DynFlags (supportedLanguagesAndExtensions) import DynFlags (supportedLanguagesAndExtensions)
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.GhcMod.Convert
-- | Listing language extensions. -- | Listing language extensions.

View File

@ -3,6 +3,7 @@ module Language.Haskell.GhcMod.Lint where
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Control.Exception (handle, SomeException(..)) import Control.Exception (handle, SomeException(..))
import Language.Haskell.GhcMod.Logger (checkErrorPrefix) import Language.Haskell.GhcMod.Logger (checkErrorPrefix)
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Language.Haskell.HLint (hlint) import Language.Haskell.HLint (hlint)

View File

@ -3,9 +3,9 @@ module Language.Haskell.GhcMod.List (listModules, modules) where
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Control.Exception (SomeException(..)) import Control.Exception (SomeException(..))
import Data.List (nub, sort) import Data.List (nub, sort)
import GHC (Ghc)
import qualified GHC as G import qualified GHC as G
import Language.Haskell.GhcMod.GHCApi import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Convert
import Language.Haskell.GhcMod.Types import Language.Haskell.GhcMod.Types
import Packages (pkgIdMap, exposedModules, sourcePackageId, display) import Packages (pkgIdMap, exposedModules, sourcePackageId, display)
import UniqFM (eltsUFM) import UniqFM (eltsUFM)
@ -14,13 +14,13 @@ import UniqFM (eltsUFM)
-- | Listing installed modules. -- | Listing installed modules.
listModules :: Options -> Cradle -> IO String listModules :: Options -> Cradle -> IO String
listModules opt cradle = withGHC' $ do listModules opt _ = runGhcMod opt $ modules
initializeFlagsWithCradle opt cradle
modules opt
-- | Listing installed modules. -- | Listing installed modules.
modules :: Options -> Ghc String modules :: GhcMod String
modules opt = convert opt . arrange <$> (getModules `G.gcatch` handler) modules = do
opt <- options
convert opt . (arrange opt) <$> (getModules `G.gcatch` handler)
where where
getModules = getExposedModules <$> G.getSessionDynFlags getModules = getExposedModules <$> G.getSessionDynFlags
getExposedModules = concatMap exposedModules' getExposedModules = concatMap exposedModules'
@ -29,8 +29,8 @@ modules opt = convert opt . arrange <$> (getModules `G.gcatch` handler)
map G.moduleNameString (exposedModules p) map G.moduleNameString (exposedModules p)
`zip` `zip`
repeat (display $ sourcePackageId p) repeat (display $ sourcePackageId p)
arrange = nub . sort . map dropPkgs arrange opt = nub . sort . map (dropPkgs opt)
dropPkgs (name, pkg) dropPkgs opt (name, pkg)
| detailed opt = name ++ " " ++ pkg | detailed opt = name ++ " " ++ pkg
| otherwise = name | otherwise = name
handler (SomeException _) = return [] handler (SomeException _) = return []

View File

@ -6,20 +6,22 @@ module Language.Haskell.GhcMod.Logger (
) where ) where
import Bag (Bag, bagToList) import Bag (Bag, bagToList)
import Control.Applicative ((<$>)) import Control.Applicative ((<$>),(*>))
import CoreMonad (liftIO) import CoreMonad (liftIO)
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef) import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
import Data.List (isPrefixOf) import Data.List (isPrefixOf)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo) import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
import Exception (ghandle) import Exception (ghandle)
import GHC (Ghc, DynFlags, SrcSpan, Severity(SevError)) import GHC (DynFlags, SrcSpan, Severity(SevError))
import qualified GHC as G import qualified GHC as G
import HscTypes (SourceError, srcErrorMessages) import HscTypes (SourceError, srcErrorMessages)
import Language.Haskell.GhcMod.Doc (showPage, getStyle) import Language.Haskell.GhcMod.Doc (showPage, getStyle)
import Language.Haskell.GhcMod.GHCApi (withDynFlags, withCmdFlags) import Language.Haskell.GhcMod.GHCApi (withDynFlags, withCmdFlags)
import qualified Language.Haskell.GhcMod.Gap as Gap import qualified Language.Haskell.GhcMod.Gap as Gap
import Language.Haskell.GhcMod.Types (Options(..), convert) import Language.Haskell.GhcMod.Convert (convert')
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types (Options(..))
import Outputable (PprStyle, SDoc) import Outputable (PprStyle, SDoc)
import System.FilePath (normalise) import System.FilePath (normalise)
@ -32,11 +34,11 @@ newtype LogRef = LogRef (IORef Builder)
newLogRef :: IO LogRef newLogRef :: IO LogRef
newLogRef = LogRef <$> newIORef id newLogRef = LogRef <$> newIORef id
readAndClearLogRef :: Options -> LogRef -> IO String readAndClearLogRef :: LogRef -> GhcMod String
readAndClearLogRef opt (LogRef ref) = do readAndClearLogRef (LogRef ref) = do
b <- readIORef ref b <- liftIO $ readIORef ref
writeIORef ref id liftIO $ writeIORef ref id
return $! convert opt (b []) convert' (b [])
appendLogRef :: DynFlags -> LogRef -> DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO () appendLogRef :: DynFlags -> LogRef -> DynFlags -> Severity -> SrcSpan -> PprStyle -> SDoc -> IO ()
appendLogRef df (LogRef ref) _ sev src style msg = do appendLogRef df (LogRef ref) _ sev src style msg = do
@ -46,28 +48,29 @@ appendLogRef df (LogRef ref) _ sev src style msg = do
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Set the session flag (e.g. "-Wall" or "-w:") then -- | Set the session flag (e.g. "-Wall" or "-w:") then
-- executes a body. Log messages are returned as 'String'. -- executes a body. Logged messages are returned as 'String'.
-- Right is success and Left is failure. -- Right is success and Left is failure.
withLogger :: Options -> (DynFlags -> DynFlags) -> Ghc () -> Ghc (Either String String) withLogger :: (DynFlags -> DynFlags)
withLogger opt setDF body = ghandle (sourceError opt) $ do -> GhcMod ()
-> GhcMod (Either String String)
withLogger setDF body = ghandle sourceError $ do
logref <- liftIO $ newLogRef logref <- liftIO $ newLogRef
wflags <- filter ("-fno-warn" `isPrefixOf`) . ghcOpts <$> options
withDynFlags (setLogger logref . setDF) $ do withDynFlags (setLogger logref . setDF) $ do
withCmdFlags wflags $ do withCmdFlags wflags $ do body *> (Right <$> readAndClearLogRef logref)
body
liftIO $ Right <$> readAndClearLogRef opt logref
where where
setLogger logref df = Gap.setLogAction df $ appendLogRef df logref setLogger logref df = Gap.setLogAction df $ appendLogRef df logref
wflags = filter ("-fno-warn" `isPrefixOf`) $ ghcOpts opt
---------------------------------------------------------------- ----------------------------------------------------------------
-- | Converting 'SourceError' to 'String'. -- | Converting 'SourceError' to 'String'.
sourceError :: Options -> SourceError -> Ghc (Either String String) sourceError :: SourceError -> GhcMod (Either String String)
sourceError opt err = do sourceError err = do
dflag <- G.getSessionDynFlags dflags <- G.getSessionDynFlags
style <- getStyle style <- toGhcMod getStyle
let ret = convert opt . errBagToStrList dflag style . srcErrorMessages $ err ret <- convert' $ (errBagToStrList dflags style . srcErrorMessages $ err)
return (Left ret) return $ Left ret
errBagToStrList :: DynFlags -> PprStyle -> Bag ErrMsg -> [String] errBagToStrList :: DynFlags -> PprStyle -> Bag ErrMsg -> [String]
errBagToStrList dflag style = map (ppErrMsg dflag style) . reverse . bagToList errBagToStrList dflag style = map (ppErrMsg dflag style) . reverse . bagToList

View File

@ -7,7 +7,9 @@ module Language.Haskell.GhcMod.Monad (
, GhcModState(..) , GhcModState(..)
, runGhcMod' , runGhcMod'
, runGhcMod , runGhcMod
, withErrorHandler
, toGhcMod , toGhcMod
, options
, module Control.Monad.Reader.Class , module Control.Monad.Reader.Class
, module Control.Monad.Writer.Class , module Control.Monad.Writer.Class
, module Control.Monad.State.Class , module Control.Monad.State.Class
@ -46,6 +48,10 @@ import Control.Monad.Reader.Class
import Control.Monad.Writer.Class import Control.Monad.Writer.Class
import Control.Monad.State.Class import Control.Monad.State.Class
import System.IO (hPutStr, hPrint, stderr)
import System.Exit (exitSuccess)
data GhcModEnv = GhcModEnv { data GhcModEnv = GhcModEnv {
gmGhcSession :: !(IORef HscEnv) gmGhcSession :: !(IORef HscEnv)
, gmOptions :: Options , gmOptions :: Options
@ -83,22 +89,38 @@ runGhcMod' r s a = do
(a', s',w) <- runRWST (unGhcMod $ initGhcMonad (Just libdir) >> a) r s (a', s',w) <- runRWST (unGhcMod $ initGhcMonad (Just libdir) >> a) r s
return (a',(s',w)) return (a',(s',w))
runGhcMod :: Options -> GhcMod a -> IO a runGhcMod :: Options -> GhcMod a -> IO a
runGhcMod opt a = do runGhcMod opt action = do
session <- newIORef (error "empty session") session <- newIORef (error "empty session")
cradle <- findCradle cradle <- findCradle
let env = GhcModEnv { gmGhcSession = session let env = GhcModEnv { gmGhcSession = session
, gmOptions = opt , gmOptions = opt
, gmCradle = cradle } , gmCradle = cradle }
fst <$> runGhcMod' env defaultState (a' cradle) (a,(_,_)) <- runGhcMod' env defaultState $ do
where dflags <- getSessionDynFlags
a' cradle = (toGhcMod $ initializeFlagsWithCradle opt cradle) >> a defaultCleanupHandler dflags $ do
toGhcMod $ initializeFlagsWithCradle opt cradle
action
return a
withErrorHandler :: String -> GhcMod a -> GhcMod a
withErrorHandler label = ghandle ignore
where
ignore :: SomeException -> GhcMod a
ignore e = liftIO $ do
hPutStr stderr $ label ++ ":0:0:Error:"
hPrint stderr e
exitSuccess
toGhcMod :: Ghc a -> GhcMod a toGhcMod :: Ghc a -> GhcMod a
toGhcMod a = do toGhcMod a = do
s <- gmGhcSession <$> ask s <- gmGhcSession <$> ask
liftIO $ unGhc a $ Session s liftIO $ unGhc a $ Session s
options :: GhcMod Options
options = gmOptions <$> ask
instance MonadBase IO GhcMod where instance MonadBase IO GhcMod where
liftBase = GhcMod . liftBase liftBase = GhcMod . liftBase

View File

@ -1,5 +1,3 @@
{-# LANGUAGE FlexibleInstances #-}
module Language.Haskell.GhcMod.Types where module Language.Haskell.GhcMod.Types where
import Data.List (intercalate) import Data.List (intercalate)
@ -39,98 +37,6 @@ defaultOptions = Options {
---------------------------------------------------------------- ----------------------------------------------------------------
type Builder = String -> String
-- |
--
-- >>> replace '"' "\\\"" "foo\"bar" ""
-- "foo\\\"bar"
replace :: Char -> String -> String -> Builder
replace _ _ [] = id
replace c cs (x:xs)
| x == c = (cs ++) . replace c cs xs
| otherwise = (x :) . replace c cs xs
inter :: Char -> [Builder] -> Builder
inter _ [] = id
inter c bs = foldr1 (\x y -> x . (c:) . y) bs
convert :: ToString a => Options -> a -> String
convert opt@Options { outputStyle = LispStyle } x = toLisp opt x "\n"
convert opt@Options { outputStyle = PlainStyle } x
| str == "\n" = ""
| otherwise = str
where
str = toPlain opt x "\n"
class ToString a where
toLisp :: Options -> a -> Builder
toPlain :: Options -> a -> Builder
lineSep :: Options -> String
lineSep opt = lsep
where
LineSeparator lsep = lineSeparator opt
-- |
--
-- >>> toLisp defaultOptions "fo\"o" ""
-- "\"fo\\\"o\""
-- >>> toPlain defaultOptions "foo" ""
-- "foo"
instance ToString String where
toLisp opt = quote opt
toPlain opt = replace '\n' (lineSep opt)
-- |
--
-- >>> toLisp defaultOptions ["foo", "bar", "ba\"z"] ""
-- "(\"foo\" \"bar\" \"ba\\\"z\")"
-- >>> toPlain defaultOptions ["foo", "bar", "baz"] ""
-- "foo\nbar\nbaz"
instance ToString [String] where
toLisp opt = toSexp1 opt
toPlain opt = inter '\n' . map (toPlain opt)
-- |
--
-- >>> let inp = [((1,2,3,4),"foo"),((5,6,7,8),"bar")] :: [((Int,Int,Int,Int),String)]
-- >>> toLisp defaultOptions inp ""
-- "((1 2 3 4 \"foo\") (5 6 7 8 \"bar\"))"
-- >>> toPlain defaultOptions inp ""
-- "1 2 3 4 \"foo\"\n5 6 7 8 \"bar\""
instance ToString [((Int,Int,Int,Int),String)] where
toLisp opt = toSexp2 . map toS
where
toS x = ('(' :) . tupToString opt x . (')' :)
toPlain opt = inter '\n' . map (tupToString opt)
toSexp1 :: Options -> [String] -> Builder
toSexp1 opt ss = ('(' :) . inter ' ' (map (quote opt) ss) . (')' :)
toSexp2 :: [Builder] -> Builder
toSexp2 ss = ('(' :) . (inter ' ' ss) . (')' :)
tupToString :: Options -> ((Int,Int,Int,Int),String) -> Builder
tupToString opt ((a,b,c,d),s) = (show a ++) . (' ' :)
. (show b ++) . (' ' :)
. (show c ++) . (' ' :)
. (show d ++) . (' ' :)
. quote opt s -- fixme: quote is not necessary
quote :: Options -> String -> Builder
quote opt str = ("\"" ++) . (quote' str ++) . ("\"" ++)
where
lsep = lineSep opt
quote' [] = []
quote' (x:xs)
| x == '\n' = lsep ++ quote' xs
| x == '\\' = "\\\\" ++ quote' xs
| x == '"' = "\\\"" ++ quote' xs
| otherwise = x : quote' xs
----------------------------------------------------------------
-- | The environment where this library is used. -- | The environment where this library is used.
data Cradle = Cradle { data Cradle = Cradle {
-- | The directory where this library is executed. -- | The directory where this library is executed.

View File

@ -63,6 +63,7 @@ Library
Language.Haskell.GhcMod.Cabal18 Language.Haskell.GhcMod.Cabal18
Language.Haskell.GhcMod.Check Language.Haskell.GhcMod.Check
Language.Haskell.GhcMod.Cradle Language.Haskell.GhcMod.Cradle
Language.Haskell.GhcMod.Convert
Language.Haskell.GhcMod.Debug Language.Haskell.GhcMod.Debug
Language.Haskell.GhcMod.Doc Language.Haskell.GhcMod.Doc
Language.Haskell.GhcMod.Find Language.Haskell.GhcMod.Find
@ -155,6 +156,7 @@ Test-Suite spec
LintSpec LintSpec
ListSpec ListSpec
GhcPkgSpec GhcPkgSpec
TestUtils
Build-Depends: base >= 4.0 && < 5 Build-Depends: base >= 4.0 && < 5
, containers , containers
, deepseq , deepseq

View File

@ -9,6 +9,7 @@ import qualified Control.Exception as E
import Data.Typeable (Typeable) import Data.Typeable (Typeable)
import Data.Version (showVersion) import Data.Version (showVersion)
import Language.Haskell.GhcMod import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Monad
import Paths_ghc_mod import Paths_ghc_mod
import System.Console.GetOpt (OptDescr(..), ArgDescr(..), ArgOrder(..)) import System.Console.GetOpt (OptDescr(..), ArgDescr(..), ArgOrder(..))
import qualified System.Console.GetOpt as O import qualified System.Console.GetOpt as O
@ -112,17 +113,17 @@ main = flip E.catches handlers $ do
"list" -> listModules opt cradle "list" -> listModules opt cradle
"lang" -> listLanguages opt "lang" -> listLanguages opt
"flag" -> listFlags opt "flag" -> listFlags opt
"browse" -> concat <$> mapM (browseModule opt cradle) remainingArgs "browse" -> runGhcMod opt $ concat <$> mapM browse remainingArgs
"check" -> checkSyntax opt cradle remainingArgs "check" -> runGhcMod opt $ checkSyntax remainingArgs
"expand" -> expandTemplate opt cradle remainingArgs "expand" -> runGhcMod opt $ expandTemplate remainingArgs
"debug" -> debugInfo opt cradle "debug" -> debugInfo opt cradle
"info" -> nArgs 3 infoExpr opt cradle cmdArg1 cmdArg3 "info" -> nArgs 3 infoExpr opt cradle cmdArg1 cmdArg3
"type" -> nArgs 4 $ typeExpr opt cradle cmdArg1 (read cmdArg3) (read cmdArg4) "type" -> nArgs 4 $ typeExpr opt cradle cmdArg1 (read cmdArg3) (read cmdArg4)
"find" -> nArgs 1 $ findSymbol opt cradle cmdArg1 "find" -> runGhcMod opt $ nArgs 1 $ findSymbol cmdArg1
"lint" -> nArgs 1 withFile (lintSyntax opt) cmdArg1 "lint" -> nArgs 1 withFile (lintSyntax opt) cmdArg1
"root" -> rootInfo opt cradle "root" -> rootInfo opt cradle
"doc" -> nArgs 1 $ packageDoc opt cradle cmdArg1 "doc" -> nArgs 1 $ packageDoc opt cradle cmdArg1
"boot" -> bootInfo opt cradle "boot" -> bootInfo opt
"version" -> return progVersion "version" -> return progVersion
"help" -> return $ O.usageInfo usage argspec "help" -> return $ O.usageInfo usage argspec
cmd -> E.throw (NoSuchCommand cmd) cmd -> E.throw (NoSuchCommand cmd)

View File

@ -35,6 +35,7 @@ import GHC (Ghc)
import qualified GHC as G import qualified GHC as G
import Language.Haskell.GhcMod import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Ghc import Language.Haskell.GhcMod.Ghc
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Internal import Language.Haskell.GhcMod.Internal
import Paths_ghc_mod import Paths_ghc_mod
import System.Console.GetOpt import System.Console.GetOpt
@ -116,9 +117,8 @@ replace (x:xs) = x : replace xs
---------------------------------------------------------------- ----------------------------------------------------------------
run :: Cradle -> Maybe FilePath -> Options -> Ghc a -> IO a run :: Cradle -> Maybe FilePath -> Options -> GhcMod a -> IO a
run cradle mlibdir opt body = G.runGhc mlibdir $ do run _ _ opt body = runGhcMod opt $ do
initializeFlagsWithCradle opt cradle
dflags <- G.getSessionDynFlags dflags <- G.getSessionDynFlags
G.defaultCleanupHandler dflags body G.defaultCleanupHandler dflags body
@ -133,19 +133,19 @@ setupDB cradle mlibdir opt mvar = E.handle handler $ do
---------------------------------------------------------------- ----------------------------------------------------------------
loop :: Options -> Set FilePath -> MVar SymMdlDb -> Ghc () loop :: Options -> Set FilePath -> MVar SymMdlDb -> GhcMod ()
loop opt set mvar = do loop opt set mvar = do
cmdArg <- liftIO getLine cmdArg <- liftIO getLine
let (cmd,arg') = break (== ' ') cmdArg let (cmd,arg') = break (== ' ') cmdArg
arg = dropWhile (== ' ') arg' arg = dropWhile (== ' ') arg'
(ret,ok,set') <- case cmd of (ret,ok,set') <- case cmd of
"check" -> checkStx opt set arg "check" -> checkStx opt set arg
"find" -> findSym opt set arg mvar "find" -> findSym set arg mvar
"lint" -> lintStx opt set arg "lint" -> toGhcMod $ lintStx opt set arg
"info" -> showInfo opt set arg "info" -> toGhcMod $ showInfo opt set arg
"type" -> showType opt set arg "type" -> toGhcMod $ showType opt set arg
"boot" -> bootIt opt set "boot" -> bootIt set
"browse" -> browseIt opt set arg "browse" -> browseIt set arg
"quit" -> return ("quit", False, set) "quit" -> return ("quit", False, set)
"" -> return ("quit", False, set) "" -> return ("quit", False, set)
_ -> return ([], True, set) _ -> return ([], True, set)
@ -162,11 +162,11 @@ loop opt set mvar = do
checkStx :: Options checkStx :: Options
-> Set FilePath -> Set FilePath
-> FilePath -> FilePath
-> Ghc (String, Bool, Set FilePath) -> GhcMod (String, Bool, Set FilePath)
checkStx opt set file = do checkStx _ set file = do
set' <- newFileSet set file set' <- toGhcMod $ newFileSet set file
let files = S.toList set' let files = S.toList set'
eret <- check opt files eret <- check files
case eret of case eret of
Right ret -> return (ret, True, set') Right ret -> return (ret, True, set')
Left ret -> return (ret, True, set) -- fxime: set Left ret -> return (ret, True, set) -- fxime: set
@ -199,11 +199,12 @@ isSameMainFile file (Just x)
---------------------------------------------------------------- ----------------------------------------------------------------
findSym :: Options -> Set FilePath -> String -> MVar SymMdlDb findSym :: Set FilePath -> String -> MVar SymMdlDb
-> Ghc (String, Bool, Set FilePath) -> GhcMod (String, Bool, Set FilePath)
findSym opt set sym mvar = do findSym set sym mvar = do
db <- liftIO $ readMVar mvar db <- liftIO $ readMVar mvar
let ret = lookupSym opt sym db opt <- options
let ret = lookupSym' opt sym db
return (ret, True, set) return (ret, True, set)
lintStx :: Options -> Set FilePath -> FilePath lintStx :: Options -> Set FilePath -> FilePath
@ -255,17 +256,15 @@ showType opt set fileArg = do
---------------------------------------------------------------- ----------------------------------------------------------------
bootIt :: Options bootIt :: Set FilePath
-> Set FilePath -> GhcMod (String, Bool, Set FilePath)
-> Ghc (String, Bool, Set FilePath) bootIt set = do
bootIt opt set = do ret <- boot
ret <- boot opt
return (ret, True, set) return (ret, True, set)
browseIt :: Options browseIt :: Set FilePath
-> Set FilePath
-> ModuleString -> ModuleString
-> Ghc (String, Bool, Set FilePath) -> GhcMod (String, Bool, Set FilePath)
browseIt opt set mdl = do browseIt set mdl = do
ret <- browse opt mdl ret <- browse mdl
return (ret, True, set) return (ret, True, set)

View File

@ -5,30 +5,30 @@ import Language.Haskell.GhcMod
import Language.Haskell.GhcMod.Cradle import Language.Haskell.GhcMod.Cradle
import Test.Hspec import Test.Hspec
import TestUtils
import Dir import Dir
spec :: Spec spec :: Spec
spec = do spec = do
describe "browseModule" $ do describe "browse" $ do
it "lists up symbols in the module" $ do it "lists up symbols in the module" $ do
cradle <- findCradle syms <- runD $ lines <$> browse "Data.Map"
syms <- lines <$> browseModule defaultOptions cradle "Data.Map"
syms `shouldContain` ["differenceWithKey"] syms `shouldContain` ["differenceWithKey"]
describe "browseModule -d" $ do describe "browse -d" $ do
it "lists up symbols with type info in the module" $ do it "lists up symbols with type info in the module" $ do
cradle <- findCradle syms <- run defaultOptions { detailed = True }
syms <- lines <$> browseModule defaultOptions { detailed = True } cradle "Data.Either" $ lines <$> browse "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
cradle <- findCradle cradle <- findCradle
syms <- lines <$> browseModule defaultOptions { detailed = True} cradle "Data.Either" syms <- run defaultOptions { detailed = True}
$ lines <$> browse "Data.Either"
syms `shouldContain` ["Left :: a -> Either a b"] syms `shouldContain` ["Left :: a -> Either a b"]
describe "browseModule local" $ do describe "browse local" $ do
it "lists symbols in a local module" $ do it "lists symbols in a local module" $ do
withDirectory_ "test/data" $ do withDirectory_ "test/data" $ do
cradle <- findCradleWithoutSandbox syms <- runID $ lines <$> browse "Baz"
syms <- lines <$> browseModule defaultOptions cradle "Baz"
syms `shouldContain` ["baz"] syms `shouldContain` ["baz"]

View File

@ -6,6 +6,7 @@ import Language.Haskell.GhcMod.Cradle
import System.FilePath import System.FilePath
import Test.Hspec import Test.Hspec
import TestUtils
import Dir import Dir
spec :: Spec spec :: Spec
@ -13,31 +14,26 @@ spec = do
describe "checkSyntax" $ do describe "checkSyntax" $ do
it "can check even if an executable depends on its library" $ do it "can check even if an executable depends on its library" $ do
withDirectory_ "test/data/ghc-mod-check" $ do withDirectory_ "test/data/ghc-mod-check" $ do
cradle <- findCradleWithoutSandbox res <- runID $ checkSyntax ["main.hs"]
res <- checkSyntax defaultOptions cradle ["main.hs"]
res `shouldBe` "main.hs:5:1:Warning: Top-level binding with no type signature: main :: IO ()\n" res `shouldBe` "main.hs:5:1:Warning: Top-level binding with no type signature: main :: IO ()\n"
it "can check even if a test module imports another test module located at different directory" $ do it "can check even if a test module imports another test module located at different directory" $ do
withDirectory_ "test/data/check-test-subdir" $ do withDirectory_ "test/data/check-test-subdir" $ do
cradle <- findCradleWithoutSandbox res <- runID $ checkSyntax ["test/Bar/Baz.hs"]
res <- checkSyntax defaultOptions cradle ["test/Bar/Baz.hs"]
res `shouldSatisfy` (("test" </> "Foo.hs:3:1:Warning: Top-level binding with no type signature: foo :: [Char]\n") `isSuffixOf`) res `shouldSatisfy` (("test" </> "Foo.hs:3:1:Warning: Top-level binding with no type signature: foo :: [Char]\n") `isSuffixOf`)
it "can detect mutually imported modules" $ do it "can detect mutually imported modules" $ do
withDirectory_ "test/data" $ do withDirectory_ "test/data" $ do
cradle <- findCradleWithoutSandbox res <- runID $ checkSyntax ["Mutual1.hs"]
res <- checkSyntax defaultOptions cradle ["Mutual1.hs"]
res `shouldSatisfy` ("Module imports form a cycle" `isInfixOf`) res `shouldSatisfy` ("Module imports form a cycle" `isInfixOf`)
it "can check a module using QuasiQuotes" $ do it "can check a module using QuasiQuotes" $ do
withDirectory_ "test/data" $ do withDirectory_ "test/data" $ do
cradle <- findCradleWithoutSandbox res <- runID $ checkSyntax ["Baz.hs"]
res <- checkSyntax defaultOptions cradle ["Baz.hs"]
res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`) res `shouldSatisfy` ("Baz.hs:5:1:Warning:" `isPrefixOf`)
context "without errors" $ do context "without errors" $ do
it "doesn't output empty line" $ do it "doesn't output empty line" $ do
withDirectory_ "test/data/ghc-mod-check/Data" $ do withDirectory_ "test/data/ghc-mod-check/Data" $ do
cradle <- findCradleWithoutSandbox res <- runID $ checkSyntax ["Foo.hs"]
res <- checkSyntax defaultOptions cradle ["Foo.hs"]
res `shouldBe` "" res `shouldBe` ""

34
test/TestUtils.hs Normal file
View File

@ -0,0 +1,34 @@
module TestUtils (
run
, runD
, runI
, runID
, runIsolatedGhcMod
, isolateCradle
, module Language.Haskell.GhcMod.Monad
, module Language.Haskell.GhcMod.Types
) where
import Language.Haskell.GhcMod.Monad
import Language.Haskell.GhcMod.Types
isolateCradle :: GhcMod a -> GhcMod a
isolateCradle action =
local modifyEnv $ action
where
modifyEnv e = e { gmCradle = (gmCradle e) { cradlePkgDbStack = [GlobalDb] } }
runIsolatedGhcMod :: Options -> GhcMod a -> IO a
runIsolatedGhcMod opt action = runGhcMod opt $ isolateCradle action
-- | Run GhcMod in isolated cradle with default options
runID = runIsolatedGhcMod defaultOptions
-- | Run GhcMod in isolated cradle
runI = runIsolatedGhcMod
-- | Run GhcMod
run = runGhcMod
-- | Run GhcMod with default options
runD = runGhcMod defaultOptions