Skip to content

Commit

Permalink
RFCT Use Control.Monad.{findM,firstJustM}
Browse files Browse the repository at this point in the history
  • Loading branch information
luispedro committed Feb 15, 2024
1 parent 1800b01 commit 2ab1313
Show file tree
Hide file tree
Showing 4 changed files with 12 additions and 29 deletions.
9 changes: 3 additions & 6 deletions NGLess/BuiltinModules/Samples.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ import qualified Data.Aeson.KeyMap as Aeson
import qualified Data.Aeson.Key as Aeson
import qualified Data.Yaml as Yaml
import qualified Data.Vector as V
import Control.Monad.Extra (findM)
import Control.Monad.IO.Class (liftIO)
import System.FilePath ((</>), isAbsolute)

Expand All @@ -31,7 +32,6 @@ import Language
import Data.FastQ
import Modules
import NGLess
import Utils.Utils (findM)

data SampleData = SampleData
{ sampleName :: !T.Text
Expand Down Expand Up @@ -118,11 +118,8 @@ executeLoadSample fname kwargs = do
samples <- executeLoadSampleList fname []
case samples of
NGOList l -> do
found <- findM l $ \case
s@(NGOReadSet n _) ->
if n == sample
then return (Just s)
else return Nothing
found <- flip findM l $ \case
NGOReadSet n _ -> return (n == sample)
_ -> throwShouldNotOccur "load_sample_from_yaml: sample list is not a list of samples"
case found of
Just s -> return s
Expand Down
13 changes: 4 additions & 9 deletions NGLess/FileManagement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ import qualified Conduit as C
import Conduit ((.|))
import System.FilePath (takeDirectory, (</>), (<.>), (-<.>))
import Control.Monad (unless, forM_, when)
import Control.Monad.Extra (firstJustM)
import System.Posix.Files (setFileMode, createSymbolicLink)
import System.Posix.Internals (c_getpid)
import Data.List (isSuffixOf, isPrefixOf)
Expand All @@ -63,7 +64,7 @@ import NGLess.NGLEnvironment
import qualified Dependencies.Embedded as Deps
import NGLess.NGError
import Utils.LockFile
import Utils.Utils (findM, withOutputFile)
import Utils.Utils (withOutputFile)


{- Note on temporary files
Expand Down Expand Up @@ -277,7 +278,7 @@ binPath User = ((</> "bin") . nConfUserDirectory) <$> nglConfiguration
-- | Attempts to find the absolute path for the requested binary (checks permissions)
findBin :: FilePath -> NGLessIO (Maybe FilePath)
findBin fname = do
nglPath <- findM [Root, User] $ \p -> do
nglPath <- flip firstJustM [Root, User] $ \p -> do
path <- (</> fname) <$> binPath p
ex <- canExecute path
if ex
Expand Down Expand Up @@ -388,18 +389,12 @@ expandPath fbase = do
searchpath <- nConfSearchPath <$> nglConfiguration
outputListLno' TraceOutput ["Looking for file '", fbase, "' (search path is ", show searchpath, ")"]
let candidates = expandPath' fbase searchpath
findMaybeM candidates $ \p -> do
flip firstJustM candidates $ \p -> do
outputListLno' TraceOutput ["Looking for file (", fbase, ") in ", p]
exists <- liftIO (SD.doesFileExist p)
return $! if exists
then Just p
else Nothing
where
findMaybeM :: Monad m => [a] -> (a -> m (Maybe b)) -> m (Maybe b)
findMaybeM [] _ = return Nothing
findMaybeM (x:xs) f = f x >>= \case
Nothing -> findMaybeM xs f
val -> return val

expandPath' :: FilePath -> [FilePath] -> [FilePath]
expandPath' fbase search = case RE.matchedText $ fbase RE.?=~ [RE.re|<(@{%id})?>|] of
Expand Down
7 changes: 4 additions & 3 deletions NGLess/ReferenceDatabases.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Data.Foldable
import Data.Maybe

import Control.Monad (liftM2)
import Control.Monad.Extra (firstJustM)
import Control.Applicative ((<|>))
import Control.Monad.IO.Class (liftIO)
import Control.Monad.Trans.Resource(release)
Expand All @@ -39,7 +40,7 @@ import NGLess
import Dependencies.Versions (bwaVersion)
import Utils.Network (downloadExpandTar, downloadOrCopyFile, downloadFile, isUrl)
import Utils.LockFile (withLockFile, LockParameters(..), WhenExistsStrategy(..))
import Utils.Utils (findM, withOutputFile)
import Utils.Utils (withOutputFile)

data ReferenceFilePaths = ReferenceFilePaths
{ rfpFaFile :: Maybe FilePath
Expand Down Expand Up @@ -108,8 +109,8 @@ downloadIfUrl basedir fname (Just path)
moduleDirectReference :: T.Text -> NGLessIO (Maybe ReferenceFilePaths)
moduleDirectReference rname = do
mods <- ngleLoadedModules <$> nglEnvironment
findM mods $ \m ->
findM (modReferences m) $ \case
flip firstJustM mods $ \m ->
flip firstJustM (modReferences m) $ \case
ExternalReference eref fafile gtffile mapfile
| eref == rname -> do
fafile' <- downloadIfUrl (modPath m) (T.unpack rname <.> "fna.gz") (Just fafile)
Expand Down
12 changes: 1 addition & 11 deletions NGLess/Utils/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{- Copyright 2015-2019 NGLess Authors
{- Copyright 2015-2024 NGLess Authors
- License: MIT
-}

Expand All @@ -9,7 +9,6 @@ module Utils.Utils
, maybeM
, mapMaybeM
, fmapMaybeM
, findM
, uniq
, allSame
, passthrough
Expand Down Expand Up @@ -74,15 +73,6 @@ moveOrCopy oldfp newfp = renameFile oldfp newfp `catch` (\e -> case ioeGetErrorT
UnsupportedOperation -> copyFile oldfp newfp
_ -> ioError e)

-- | Monadic version of find: returns the result of the first application of
-- the argument which is not 'Nothing' or, if all applications fail, return
-- 'Nothing'
findM :: Monad m => [a] -> (a -> m (Maybe b)) -> m (Maybe b)
findM [] _ = return Nothing
findM (x:xs) f = f x >>= \case
Nothing -> findM xs f
val -> return val

secondM :: Monad m => (a -> m b) -> (c,a) -> m (c,b)
secondM f (a,c) = (a,) <$> f c
{-# INLINE secondM #-}
Expand Down

0 comments on commit 2ab1313

Please sign in to comment.