Replace fromJust with fromJustNote everywhere
This commit is contained in:
@@ -3,6 +3,7 @@ module Language.Haskell.GhcMod.Browse (
|
||||
BrowseOpts(..)
|
||||
) where
|
||||
|
||||
import Safe
|
||||
import Control.Applicative
|
||||
import Control.Exception (SomeException(..))
|
||||
import Data.Char
|
||||
@@ -49,7 +50,7 @@ browse opts pkgmdl = do
|
||||
goHomeModule = runGmlT [Right mdlname] $ do
|
||||
processExports opts =<< tryModuleInfo =<< G.findModule mdlname Nothing
|
||||
|
||||
tryModuleInfo m = fromJust <$> G.getModuleInfo m
|
||||
tryModuleInfo m = fromJustNote "browse, tryModuleInfo" <$> G.getModuleInfo m
|
||||
|
||||
(mpkg, mdl) = splitPkgMdl pkgmdl
|
||||
mdlname = G.mkModuleName mdl
|
||||
|
||||
@@ -19,6 +19,7 @@ import Language.Haskell.GhcMod.Stack
|
||||
import Language.Haskell.GhcMod.Logging
|
||||
import Language.Haskell.GhcMod.Error
|
||||
|
||||
import Safe
|
||||
import Control.Applicative
|
||||
import Control.Monad.Trans.Maybe
|
||||
import Data.Maybe
|
||||
@@ -46,7 +47,7 @@ findCradle' dir = run $
|
||||
, sandboxCradle dir
|
||||
, plainCradle dir
|
||||
]
|
||||
where run a = fillTempDir =<< (fromJust <$> runMaybeT a)
|
||||
where run a = fillTempDir =<< (fromJustNote "findCradle'" <$> runMaybeT a)
|
||||
|
||||
findSpecCradle :: (GmLog m, IOish m, GmOut m) => FilePath -> m Cradle
|
||||
findSpecCradle dir = do
|
||||
|
||||
@@ -73,6 +73,8 @@ import Language.Haskell.GhcMod.Monad.Out
|
||||
import Language.Haskell.GhcMod.Monad.Newtypes
|
||||
import Language.Haskell.GhcMod.Monad.Orphans ()
|
||||
|
||||
import Safe
|
||||
|
||||
import GHC
|
||||
import DynFlags
|
||||
import Exception
|
||||
@@ -116,13 +118,13 @@ instance (MonadIO m, MonadBaseControl IO m) => GhcMonad (GmlT m) where
|
||||
-- | Get the underlying GHC session
|
||||
gmlGetSession :: (MonadIO m, MonadBaseControl IO m) => GmlT m HscEnv
|
||||
gmlGetSession = do
|
||||
ref <- gmgsSession . fromJust . gmGhcSession <$> gmsGet
|
||||
ref <- gmgsSession . fromJustNote "gmlGetSession" . gmGhcSession <$> gmsGet
|
||||
liftIO $ readIORef ref
|
||||
|
||||
-- | Set the underlying GHC session
|
||||
gmlSetSession :: (MonadIO m, MonadBaseControl IO m) => HscEnv -> GmlT m ()
|
||||
gmlSetSession a = do
|
||||
ref <- gmgsSession . fromJust . gmGhcSession <$> gmsGet
|
||||
ref <- gmgsSession . fromJustNote "gmlSetSession" . gmGhcSession <$> gmsGet
|
||||
liftIO $ flip writeIORef a ref
|
||||
|
||||
instance GhcMonad LightGhc where
|
||||
|
||||
@@ -16,7 +16,7 @@
|
||||
|
||||
module Language.Haskell.GhcMod.Stack where
|
||||
|
||||
|
||||
import Safe
|
||||
import Control.Applicative
|
||||
import Control.Exception as E
|
||||
import Control.Monad
|
||||
@@ -51,7 +51,7 @@ patchStackPrograms _crdl progs = return progs
|
||||
getStackEnv :: (IOish m, GmOut m, GmLog m) => FilePath -> m (Maybe StackEnv)
|
||||
getStackEnv projdir = U.withDirectory_ projdir $ runMaybeT $ do
|
||||
env <- map (liToTup . splitOn ": ") . lines <$> readStack ["path"]
|
||||
let look k = fromJust $ lookup k env
|
||||
let look k = fromJustNote "getStackEnv" $ lookup k env
|
||||
return StackEnv {
|
||||
seDistDir = look "dist-dir"
|
||||
, seBinPath = splitSearchPath $ look "bin-path"
|
||||
|
||||
@@ -40,6 +40,7 @@ import Language.Haskell.GhcMod.LightGhc
|
||||
import Language.Haskell.GhcMod.CustomPackageDb
|
||||
import Language.Haskell.GhcMod.Output
|
||||
|
||||
import Safe
|
||||
import Data.Maybe
|
||||
import Data.Monoid as Monoid
|
||||
import Data.Either
|
||||
@@ -188,13 +189,13 @@ targetGhcOptions crdl sefnmn = do
|
||||
let cns = filter (/= ChSetupHsName) $ Map.keys mcs
|
||||
|
||||
gmLog GmDebug "" $ strDoc $ "Could not find a component assignment, falling back to picking library component in cabal file."
|
||||
return $ gmcGhcOpts $ fromJust $ Map.lookup (head cns) mcs
|
||||
return $ gmcGhcOpts $ fromJustNote "targetGhcOptions, no-assignment" $ Map.lookup (head cns) mcs
|
||||
else do
|
||||
when noCandidates $
|
||||
throwError $ GMECabalCompAssignment mdlcs
|
||||
|
||||
let cn = pickComponent candidates
|
||||
return $ gmcGhcOpts $ fromJust $ Map.lookup cn mcs
|
||||
return $ gmcGhcOpts $ fromJustNote "targetGhcOptions" $ Map.lookup cn mcs
|
||||
|
||||
resolvedComponentsCache :: IOish m => FilePath ->
|
||||
Cached (GhcModT m) GhcModState
|
||||
|
||||
Reference in New Issue
Block a user