cleaning up check, splice flag and logger.
This commit is contained in:
parent
74cde29ae0
commit
c45415a367
@ -16,6 +16,7 @@ module Language.Haskell.GhcMod (
|
|||||||
, browseModule
|
, browseModule
|
||||||
, checkSyntax
|
, checkSyntax
|
||||||
, lintSyntax
|
, lintSyntax
|
||||||
|
, expandTemplate
|
||||||
, infoExpr
|
, infoExpr
|
||||||
, typeExpr
|
, typeExpr
|
||||||
, listModules
|
, listModules
|
||||||
|
@ -6,7 +6,6 @@ module Language.Haskell.GhcMod.Browse (
|
|||||||
|
|
||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
import Control.Exception (SomeException(..))
|
import Control.Exception (SomeException(..))
|
||||||
import Control.Monad (void)
|
|
||||||
import Data.Char (isAlpha)
|
import Data.Char (isAlpha)
|
||||||
import Data.List (sort)
|
import Data.List (sort)
|
||||||
import Data.Maybe (catMaybes)
|
import Data.Maybe (catMaybes)
|
||||||
@ -33,7 +32,7 @@ browseModule :: Options
|
|||||||
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
-> ModuleString -- ^ A module name. (e.g. \"Data.List\")
|
||||||
-> IO String
|
-> IO String
|
||||||
browseModule opt cradle pkgmdl = withGHC' $ do
|
browseModule opt cradle pkgmdl = withGHC' $ do
|
||||||
void $ initializeFlagsWithCradle opt cradle [] False
|
initializeFlagsWithCradle opt cradle []
|
||||||
browse opt pkgmdl
|
browse opt pkgmdl
|
||||||
|
|
||||||
-- | Getting functions, classes, etc from a module.
|
-- | Getting functions, classes, etc from a module.
|
||||||
|
@ -1,10 +1,15 @@
|
|||||||
module Language.Haskell.GhcMod.Check (checkSyntax, check) where
|
module Language.Haskell.GhcMod.Check (
|
||||||
|
checkSyntax
|
||||||
|
, check
|
||||||
|
, expandTemplate
|
||||||
|
, expand
|
||||||
|
) where
|
||||||
|
|
||||||
import CoreMonad (liftIO)
|
import Exception (ghandle)
|
||||||
import GHC (Ghc)
|
import GHC (Ghc)
|
||||||
import qualified GHC as G
|
|
||||||
import Language.Haskell.GhcMod.ErrMsg
|
import Language.Haskell.GhcMod.ErrMsg
|
||||||
import Language.Haskell.GhcMod.GHCApi
|
import Language.Haskell.GhcMod.GHCApi
|
||||||
|
import qualified Language.Haskell.GhcMod.Gap as Gap
|
||||||
import Language.Haskell.GhcMod.Types
|
import Language.Haskell.GhcMod.Types
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
@ -15,28 +20,51 @@ checkSyntax :: Options
|
|||||||
-> Cradle
|
-> Cradle
|
||||||
-> [FilePath] -- ^ The target files.
|
-> [FilePath] -- ^ The target files.
|
||||||
-> IO String
|
-> IO String
|
||||||
checkSyntax _ _ [] = error "ghc-mod: checkSyntax: No files given"
|
checkSyntax _ _ [] = return ""
|
||||||
checkSyntax opt cradle files = withGHC sessionName (check opt cradle files)
|
checkSyntax opt cradle files = withGHC sessionName $ do
|
||||||
|
initializeFlagsWithCradle opt cradle options
|
||||||
|
check opt files
|
||||||
where
|
where
|
||||||
sessionName = case files of
|
sessionName = case files of
|
||||||
[file] -> file
|
[file] -> file
|
||||||
_ -> "MultipleFiles"
|
_ -> "MultipleFiles"
|
||||||
|
options = "-Wall" : ghcOpts opt
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
-- | 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 :: Options
|
||||||
-> Cradle
|
|
||||||
-> [FilePath] -- ^ The target files.
|
-> [FilePath] -- ^ The target files.
|
||||||
-> Ghc String
|
-> Ghc String
|
||||||
check _ _ [] = error "ghc-mod: check: No files given"
|
check opt fileNames = ghandle (handleErrMsg opt) $
|
||||||
check opt cradle fileNames = checkIt `G.gcatch` handleErrMsg opt
|
withLogger opt $ setTargetFiles fileNames
|
||||||
|
|
||||||
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
-- | Expanding syntax of a target file using GHC.
|
||||||
|
-- Warnings and errors are returned.
|
||||||
|
expandTemplate :: Options
|
||||||
|
-> Cradle
|
||||||
|
-> [FilePath] -- ^ The target files.
|
||||||
|
-> IO String
|
||||||
|
expandTemplate _ _ [] = return ""
|
||||||
|
expandTemplate opt cradle files = withGHC sessionName $ do
|
||||||
|
initializeFlagsWithCradle opt cradle options
|
||||||
|
expand opt files
|
||||||
where
|
where
|
||||||
checkIt = do
|
sessionName = case files of
|
||||||
(readLog,_) <- initializeFlagsWithCradle opt cradle options True
|
[file] -> file
|
||||||
setTargetFiles fileNames
|
_ -> "MultipleFiles"
|
||||||
liftIO readLog
|
options = "-w:" : ghcOpts opt
|
||||||
options
|
|
||||||
| expandSplice opt = "-w:" : ghcOpts opt
|
----------------------------------------------------------------
|
||||||
| otherwise = "-Wall" : ghcOpts opt
|
|
||||||
|
-- | Expanding syntax of a target file using GHC.
|
||||||
|
-- Warnings and errors are returned.
|
||||||
|
expand :: Options
|
||||||
|
-> [FilePath] -- ^ The target files.
|
||||||
|
-> Ghc String
|
||||||
|
expand opt fileNames = ghandle (handleErrMsg opt) $
|
||||||
|
withDynFlags Gap.setDumpSplices $
|
||||||
|
withLogger opt $ setTargetFiles fileNames
|
||||||
|
@ -2,13 +2,14 @@
|
|||||||
|
|
||||||
module Language.Haskell.GhcMod.ErrMsg (
|
module Language.Haskell.GhcMod.ErrMsg (
|
||||||
LogReader
|
LogReader
|
||||||
, setLogger
|
, withLogger
|
||||||
, handleErrMsg
|
, handleErrMsg
|
||||||
, checkErrorPrefix
|
, checkErrorPrefix
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Bag (Bag, bagToList)
|
import Bag (Bag, bagToList)
|
||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
|
import CoreMonad (liftIO)
|
||||||
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
|
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
|
||||||
import Data.Maybe (fromMaybe)
|
import Data.Maybe (fromMaybe)
|
||||||
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
|
import ErrUtils (ErrMsg, errMsgShortDoc, errMsgExtraInfo)
|
||||||
@ -16,6 +17,7 @@ import GHC (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)
|
||||||
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.Types (Options, convert)
|
||||||
import Outputable (PprStyle, SDoc)
|
import Outputable (PprStyle, SDoc)
|
||||||
@ -48,14 +50,12 @@ appendLogRef df (LogRef ref) _ sev src style msg = do
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
setLogger :: Bool -> DynFlags -> Options -> IO (DynFlags, LogReader)
|
withLogger :: Options -> Ghc () -> Ghc String
|
||||||
setLogger False df _ = return (newdf, undefined)
|
withLogger opt body = do
|
||||||
where
|
logref <- liftIO $ newLogRef
|
||||||
newdf = Gap.setLogAction df $ \_ _ _ _ _ -> return ()
|
withDynFlags (\df -> Gap.setLogAction df $ appendLogRef df logref) $ do
|
||||||
setLogger True df opt = do
|
body
|
||||||
logref <- newLogRef
|
liftIO $ readAndClearLogRef opt logref
|
||||||
let newdf = Gap.setLogAction df $ appendLogRef df logref
|
|
||||||
return (newdf, readAndClearLogRef opt logref)
|
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
|
@ -2,7 +2,6 @@
|
|||||||
|
|
||||||
module Language.Haskell.GhcMod.Find where
|
module Language.Haskell.GhcMod.Find where
|
||||||
|
|
||||||
import Control.Monad (void)
|
|
||||||
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)
|
||||||
@ -34,7 +33,7 @@ newtype SymMdlDb = SymMdlDb (Map Symbol [ModuleString])
|
|||||||
-- | Find modules to which the symbol belong.
|
-- | Find modules to which the symbol belong.
|
||||||
findSymbol :: Options -> Cradle -> Symbol -> IO String
|
findSymbol :: Options -> Cradle -> Symbol -> IO String
|
||||||
findSymbol opt cradle sym = withGHC' $ do
|
findSymbol opt cradle sym = withGHC' $ do
|
||||||
void $ initializeFlagsWithCradle opt cradle [] False
|
initializeFlagsWithCradle opt cradle []
|
||||||
lookupSym opt sym <$> getSymMdlDb
|
lookupSym opt sym <$> getSymMdlDb
|
||||||
|
|
||||||
-- | Creating 'SymMdlDb'.
|
-- | Creating 'SymMdlDb'.
|
||||||
|
@ -12,7 +12,6 @@ module Language.Haskell.GhcMod.GHCApi (
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.Haskell.GhcMod.CabalApi
|
import Language.Haskell.GhcMod.CabalApi
|
||||||
import Language.Haskell.GhcMod.ErrMsg
|
|
||||||
import Language.Haskell.GhcMod.GHCChoice
|
import Language.Haskell.GhcMod.GHCChoice
|
||||||
import Language.Haskell.GhcMod.GhcPkg
|
import Language.Haskell.GhcMod.GhcPkg
|
||||||
|
|
||||||
@ -20,7 +19,6 @@ import Control.Applicative ((<$>))
|
|||||||
import Control.Monad (forM, void, unless)
|
import Control.Monad (forM, void, unless)
|
||||||
import CoreMonad (liftIO)
|
import CoreMonad (liftIO)
|
||||||
import Data.Maybe (isJust, fromJust)
|
import Data.Maybe (isJust, fromJust)
|
||||||
import Distribution.PackageDescription (PackageDescription)
|
|
||||||
import Exception (ghandle, SomeException(..))
|
import Exception (ghandle, SomeException(..))
|
||||||
import GHC (Ghc, GhcMonad, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
|
import GHC (Ghc, GhcMonad, DynFlags(..), GhcLink(..), HscTarget(..), LoadHowMuch(..))
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
@ -75,9 +73,8 @@ initializeFlagsWithCradle :: GhcMonad m
|
|||||||
=> Options
|
=> Options
|
||||||
-> Cradle
|
-> Cradle
|
||||||
-> [GHCOption]
|
-> [GHCOption]
|
||||||
-> Bool
|
-> m ()
|
||||||
-> m (LogReader, Maybe PackageDescription)
|
initializeFlagsWithCradle opt cradle ghcopts
|
||||||
initializeFlagsWithCradle opt cradle ghcopts logging
|
|
||||||
| cabal = withCabal |||> withSandbox
|
| cabal = withCabal |||> withSandbox
|
||||||
| otherwise = withSandbox
|
| otherwise = withSandbox
|
||||||
where
|
where
|
||||||
@ -86,11 +83,8 @@ initializeFlagsWithCradle opt cradle ghcopts logging
|
|||||||
withCabal = do
|
withCabal = do
|
||||||
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
|
pkgDesc <- liftIO $ parseCabalFile $ fromJust mCradleFile
|
||||||
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
|
compOpts <- liftIO $ getCompilerOptions ghcopts cradle pkgDesc
|
||||||
logger <- initSession CabalPkg opt compOpts logging
|
initSession CabalPkg opt compOpts
|
||||||
return (logger, Just pkgDesc)
|
withSandbox = initSession SingleFile opt compOpts
|
||||||
withSandbox = do
|
|
||||||
logger <- initSession SingleFile opt compOpts logging
|
|
||||||
return (logger, Nothing)
|
|
||||||
where
|
where
|
||||||
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack cradle
|
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack cradle
|
||||||
compOpts
|
compOpts
|
||||||
@ -105,25 +99,18 @@ initSession :: GhcMonad m
|
|||||||
=> Build
|
=> Build
|
||||||
-> Options
|
-> Options
|
||||||
-> CompilerOptions
|
-> CompilerOptions
|
||||||
-> Bool
|
-> m ()
|
||||||
-> m LogReader
|
initSession build Options {..} CompilerOptions {..} = do
|
||||||
initSession build opt compOpts logging = do
|
|
||||||
df <- initDynFlags build opt compOpts
|
|
||||||
(df', lg) <- liftIO $ setLogger logging df opt
|
|
||||||
_ <- G.setSessionDynFlags df'
|
|
||||||
return lg
|
|
||||||
|
|
||||||
initDynFlags :: GhcMonad m => Build -> Options -> CompilerOptions -> m DynFlags
|
|
||||||
initDynFlags build Options {..} CompilerOptions {..} = do
|
|
||||||
df <- G.getSessionDynFlags
|
df <- G.getSessionDynFlags
|
||||||
_ <- G.setSessionDynFlags =<< (addCmdOpts ghcOptions
|
void $ G.setSessionDynFlags =<< (addCmdOpts ghcOptions
|
||||||
$ setLinkerOptions
|
$ setLinkerOptions
|
||||||
$ setIncludeDirs includeDirs
|
$ setIncludeDirs includeDirs
|
||||||
$ setSplice expandSplice
|
|
||||||
$ setBuildEnv build
|
$ setBuildEnv build
|
||||||
|
$ setEmptyLogger
|
||||||
$ Gap.addPackageFlags depPackages df)
|
$ Gap.addPackageFlags depPackages df)
|
||||||
G.getSessionDynFlags
|
|
||||||
|
|
||||||
|
setEmptyLogger :: DynFlags -> DynFlags
|
||||||
|
setEmptyLogger df = Gap.setLogAction df $ \_ _ _ _ _ -> return ()
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
@ -142,12 +129,6 @@ setIncludeDirs idirs df = df { importPaths = idirs }
|
|||||||
setBuildEnv :: Build -> DynFlags -> DynFlags
|
setBuildEnv :: Build -> DynFlags -> DynFlags
|
||||||
setBuildEnv build = setHideAllPackages build . setCabalPackage build
|
setBuildEnv build = setHideAllPackages build . setCabalPackage build
|
||||||
|
|
||||||
-- | Set option in 'DynFlags' to Expand template haskell if first argument is
|
|
||||||
-- True
|
|
||||||
setSplice :: Bool -> DynFlags -> DynFlags
|
|
||||||
setSplice False = id
|
|
||||||
setSplice True = Gap.setDumpSplices
|
|
||||||
|
|
||||||
-- At the moment with this option set ghc only prints different error messages,
|
-- At the moment with this option set ghc only prints different error messages,
|
||||||
-- suggesting the user to add a hidden package to the build-depends in his cabal
|
-- suggesting the user to add a hidden package to the build-depends in his cabal
|
||||||
-- file for example
|
-- file for example
|
||||||
|
@ -41,7 +41,7 @@ infoExpr :: Options
|
|||||||
-> Expression -- ^ A Haskell expression.
|
-> Expression -- ^ A Haskell expression.
|
||||||
-> IO String
|
-> IO String
|
||||||
infoExpr opt cradle file expr = withGHC' $ do
|
infoExpr opt cradle file expr = withGHC' $ do
|
||||||
void $ initializeFlagsWithCradle opt cradle noWaringOptions False
|
initializeFlagsWithCradle opt cradle noWaringOptions
|
||||||
info opt file expr
|
info opt file expr
|
||||||
|
|
||||||
-- | Obtaining information of a target expression. (GHCi's info:)
|
-- | Obtaining information of a target expression. (GHCi's info:)
|
||||||
@ -79,7 +79,7 @@ typeExpr :: Options
|
|||||||
-> Int -- ^ Column number.
|
-> Int -- ^ Column number.
|
||||||
-> IO String
|
-> IO String
|
||||||
typeExpr opt cradle file lineNo colNo = withGHC' $ do
|
typeExpr opt cradle file lineNo colNo = withGHC' $ do
|
||||||
void $ initializeFlagsWithCradle opt cradle noWaringOptions False
|
initializeFlagsWithCradle opt cradle noWaringOptions
|
||||||
types opt file lineNo colNo
|
types opt file lineNo colNo
|
||||||
|
|
||||||
-- | Obtaining type of a target expression. (GHCi's type:)
|
-- | Obtaining type of a target expression. (GHCi's type:)
|
||||||
|
@ -26,6 +26,7 @@ module Language.Haskell.GhcMod.Internal (
|
|||||||
, setTargetFiles
|
, setTargetFiles
|
||||||
, addTargetFiles
|
, addTargetFiles
|
||||||
, handleErrMsg
|
, handleErrMsg
|
||||||
|
, withLogger
|
||||||
-- * 'Ghc' Choice
|
-- * 'Ghc' Choice
|
||||||
, (||>)
|
, (||>)
|
||||||
, goNext
|
, goNext
|
||||||
|
@ -2,7 +2,6 @@ module Language.Haskell.GhcMod.List (listModules, modules) where
|
|||||||
|
|
||||||
import Control.Applicative ((<$>))
|
import Control.Applicative ((<$>))
|
||||||
import Control.Exception (SomeException(..))
|
import Control.Exception (SomeException(..))
|
||||||
import Control.Monad (void)
|
|
||||||
import Data.List (nub, sort)
|
import Data.List (nub, sort)
|
||||||
import GHC (Ghc)
|
import GHC (Ghc)
|
||||||
import qualified GHC as G
|
import qualified GHC as G
|
||||||
@ -16,7 +15,7 @@ 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 cradle = withGHC' $ do
|
||||||
void $ initializeFlagsWithCradle opt cradle [] False
|
initializeFlagsWithCradle opt cradle []
|
||||||
modules opt
|
modules opt
|
||||||
|
|
||||||
-- | Listing installed modules.
|
-- | Listing installed modules.
|
||||||
|
@ -21,8 +21,6 @@ data Options = Options {
|
|||||||
, detailed :: Bool
|
, detailed :: Bool
|
||||||
-- | If 'True', 'browse' will return fully qualified name
|
-- | If 'True', 'browse' will return fully qualified name
|
||||||
, qualified :: Bool
|
, qualified :: Bool
|
||||||
-- | Whether or not Template Haskell should be expanded.
|
|
||||||
, expandSplice :: Bool
|
|
||||||
-- | Line separator string.
|
-- | Line separator string.
|
||||||
, lineSeparator :: LineSeparator
|
, lineSeparator :: LineSeparator
|
||||||
}
|
}
|
||||||
@ -36,7 +34,6 @@ defaultOptions = Options {
|
|||||||
, operators = False
|
, operators = False
|
||||||
, detailed = False
|
, detailed = False
|
||||||
, qualified = False
|
, qualified = False
|
||||||
, expandSplice = False
|
|
||||||
, lineSeparator = LineSeparator "\0"
|
, lineSeparator = LineSeparator "\0"
|
||||||
}
|
}
|
||||||
|
|
||||||
|
@ -116,7 +116,7 @@ main = flip E.catches handlers $ do
|
|||||||
"flag" -> listFlags opt
|
"flag" -> listFlags opt
|
||||||
"browse" -> concat <$> mapM (browseModule opt cradle) remainingArgs
|
"browse" -> concat <$> mapM (browseModule opt cradle) remainingArgs
|
||||||
"check" -> checkSyntax opt cradle remainingArgs
|
"check" -> checkSyntax opt cradle remainingArgs
|
||||||
"expand" -> checkSyntax opt { expandSplice = True } cradle remainingArgs
|
"expand" -> expandTemplate opt cradle 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)
|
||||||
|
@ -119,34 +119,34 @@ replace (x:xs) = x : replace xs
|
|||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
run :: Cradle -> Maybe FilePath -> Options -> (Logger -> Ghc a) -> IO a
|
run :: Cradle -> Maybe FilePath -> Options -> Ghc a -> IO a
|
||||||
run cradle mlibdir opt body = G.runGhc mlibdir $ do
|
run cradle mlibdir opt body = G.runGhc mlibdir $ do
|
||||||
(readLog,_) <- initializeFlagsWithCradle opt cradle ["-Wall"] True
|
initializeFlagsWithCradle opt cradle ["-Wall"]
|
||||||
dflags <- G.getSessionDynFlags
|
dflags <- G.getSessionDynFlags
|
||||||
G.defaultCleanupHandler dflags $ body readLog
|
G.defaultCleanupHandler dflags body
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
setupDB :: Cradle -> Maybe FilePath -> Options -> MVar SymMdlDb -> IO ()
|
setupDB :: Cradle -> Maybe FilePath -> Options -> MVar SymMdlDb -> IO ()
|
||||||
setupDB cradle mlibdir opt mvar = E.handle handler $ do
|
setupDB cradle mlibdir opt mvar = E.handle handler $ do
|
||||||
db <- run cradle mlibdir opt $ \_ -> getSymMdlDb
|
db <- run cradle mlibdir opt getSymMdlDb
|
||||||
putMVar mvar db
|
putMVar mvar db
|
||||||
where
|
where
|
||||||
handler (SomeException _) = return () -- fixme: put emptyDb?
|
handler (SomeException _) = return () -- fixme: put emptyDb?
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
loop :: Options -> Set FilePath -> MVar SymMdlDb -> Logger -> Ghc ()
|
loop :: Options -> Set FilePath -> MVar SymMdlDb -> Ghc ()
|
||||||
loop opt set mvar readLog = 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 readLog
|
"check" -> checkStx opt set arg
|
||||||
"find" -> findSym opt set arg mvar
|
"find" -> findSym opt set arg mvar
|
||||||
"lint" -> lintStx opt set arg
|
"lint" -> lintStx opt set arg
|
||||||
"info" -> showInfo opt set arg readLog
|
"info" -> showInfo opt set arg
|
||||||
"type" -> showType opt set arg readLog
|
"type" -> showType opt set arg
|
||||||
"boot" -> bootIt opt set
|
"boot" -> bootIt opt set
|
||||||
"browse" -> browseIt opt set arg
|
"browse" -> browseIt opt set arg
|
||||||
"quit" -> return ("quit", False, set)
|
"quit" -> return ("quit", False, set)
|
||||||
@ -158,22 +158,21 @@ loop opt set mvar readLog = do
|
|||||||
else do
|
else do
|
||||||
liftIO $ putStrLn $ "NG " ++ replace ret
|
liftIO $ putStrLn $ "NG " ++ replace ret
|
||||||
liftIO $ hFlush stdout
|
liftIO $ hFlush stdout
|
||||||
when ok $ loop opt set' mvar readLog
|
when ok $ loop opt set' mvar
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
|
||||||
checkStx :: Options
|
checkStx :: Options
|
||||||
-> Set FilePath
|
-> Set FilePath
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-> Logger
|
|
||||||
-> Ghc (String, Bool, Set FilePath)
|
-> Ghc (String, Bool, Set FilePath)
|
||||||
checkStx opt set file readLog = do
|
checkStx opt set file = do
|
||||||
let add = not $ S.member file set
|
let add = not $ S.member file set
|
||||||
GE.ghandle handler $ do
|
GE.ghandle handler $ do
|
||||||
mdel <- removeMainTarget
|
mdel <- removeMainTarget
|
||||||
when add $ addTargetFiles [file]
|
ret <- withLogger opt $ do
|
||||||
void $ G.load LoadAllTargets
|
when add $ addTargetFiles [file]
|
||||||
ret <- liftIO readLog
|
void $ G.load LoadAllTargets
|
||||||
let set1 = if add then S.insert file set else set
|
let set1 = if add then S.insert file set else set
|
||||||
set2 = case mdel of
|
set2 = case mdel of
|
||||||
Nothing -> set1
|
Nothing -> set1
|
||||||
@ -238,25 +237,21 @@ parseLintOptions optFile = case brk (== ']') (dropWhile (/= '[') optFile) of
|
|||||||
showInfo :: Options
|
showInfo :: Options
|
||||||
-> Set FilePath
|
-> Set FilePath
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-> Logger
|
|
||||||
-> Ghc (String, Bool, Set FilePath)
|
-> Ghc (String, Bool, Set FilePath)
|
||||||
showInfo opt set fileArg readLog = do
|
showInfo opt set fileArg = do
|
||||||
let [file, expr] = words fileArg
|
let [file, expr] = words fileArg
|
||||||
(_, _, set') <- checkStx opt set file readLog
|
(_, _, set') <- checkStx opt set file
|
||||||
ret <- info opt file expr
|
ret <- info opt file expr
|
||||||
_ <- liftIO readLog
|
|
||||||
return (ret, True, set')
|
return (ret, True, set')
|
||||||
|
|
||||||
showType :: Options
|
showType :: Options
|
||||||
-> Set FilePath
|
-> Set FilePath
|
||||||
-> FilePath
|
-> FilePath
|
||||||
-> Logger
|
|
||||||
-> Ghc (String, Bool, Set FilePath)
|
-> Ghc (String, Bool, Set FilePath)
|
||||||
showType opt set fileArg readLog = do
|
showType opt set fileArg = do
|
||||||
let [file, line, column] = words fileArg
|
let [file, line, column] = words fileArg
|
||||||
(_, _, set') <- checkStx opt set file readLog
|
(_, _, set') <- checkStx opt set file
|
||||||
ret <- types opt file (read line) (read column)
|
ret <- types opt file (read line) (read column)
|
||||||
_ <- liftIO readLog
|
|
||||||
return (ret, True, set')
|
return (ret, True, set')
|
||||||
|
|
||||||
----------------------------------------------------------------
|
----------------------------------------------------------------
|
||||||
|
Loading…
Reference in New Issue
Block a user