Skip to content

Commit

Permalink
RFCT Replace unnecessary uses of missingH utils
Browse files Browse the repository at this point in the history
  • Loading branch information
luispedro committed Apr 6, 2020
1 parent e810320 commit a63ac18
Show file tree
Hide file tree
Showing 5 changed files with 21 additions and 15 deletions.
4 changes: 3 additions & 1 deletion NGLess/FileManagement.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,7 @@ import System.FilePath (takeBaseName, takeDirectory, (</>), (<.>), (-<
import Control.Monad (unless, forM_, when)
import System.Posix.Files (setFileMode)
import System.Posix.Internals (c_getpid)
import Data.String.Utils (endswith)
import Data.List (isSuffixOf)

import System.Directory
import System.IO
Expand Down Expand Up @@ -74,6 +74,8 @@ data Compression = NoCompression
| ZStdCompression
deriving (Eq)

endswith = flip isSuffixOf

inferCompression :: FilePath -> Compression
inferCompression fp
| endswith ".gz" fp = GzipCompression
Expand Down
6 changes: 3 additions & 3 deletions NGLess/StandardModules/Mappers/Bwa.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{- Copyright 2013-2019 NGLess Authors
{- Copyright 2013-2020 NGLess Authors
- License: MIT
-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -11,7 +11,7 @@ module StandardModules.Mappers.Bwa

import System.Directory (doesFileExist)
import System.Posix (getFileStatus, fileSize, FileOffset)
import System.Path (splitExt)
import System.FilePath (splitExtension)
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as B

Expand All @@ -32,7 +32,7 @@ import Utils.Process (runProcess)
-- of bwa use different indices
indexPrefix :: FilePath -> NGLessIO FilePath
indexPrefix base = do
let (basename, ext) = splitExt base
let (basename, ext) = splitExtension base
return $ basename ++ "-bwa-" ++ bwaVersion ++ ext

-- | Checks whether all necessary files are present for a BWA index
Expand Down
6 changes: 3 additions & 3 deletions NGLess/StandardModules/Mappers/Minimap2.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{- Copyright 2018-2019 NGLess Authors
{- Copyright 2018-2020 NGLess Authors
- License: MIT
-}
{-# LANGUAGE RankNTypes #-}
Expand All @@ -10,7 +10,7 @@ module StandardModules.Mappers.Minimap2
) where

import System.Directory (doesFileExist)
import System.Path (splitExt)
import System.FilePath (splitExtension)
import Control.Monad.IO.Class (liftIO)
import qualified Data.Vector as V
import qualified Data.ByteString as B
Expand Down Expand Up @@ -38,7 +38,7 @@ import FileManagement (makeNGLTempFile, minimap2Bin)

indexName :: FilePath -> FilePath
indexName fp = base ++ "-minimap2-" ++ minimap2Version ++ ext ++ ".mm2.idx"
where (base, ext) = splitExt fp
where (base, ext) = splitExtension fp

hasValidIndex :: FilePath -> NGLessIO Bool
hasValidIndex = liftIO . doesFileExist . indexName
Expand Down
14 changes: 8 additions & 6 deletions NGLess/StandardModules/Mocat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,12 +20,12 @@ import Control.Monad.Extra (unlessM)
import System.Directory (doesDirectoryExist)
import System.FilePath
import System.FilePath.Glob
import Data.List.Utils
import Control.Monad.IO.Class (liftIO)
import Control.Monad
import Data.Maybe
import Data.Default
import Data.List (sort, isInfixOf)
import Data.List (sort, nub, isInfixOf, isSuffixOf)


import Output
import NGLess
Expand All @@ -35,6 +35,8 @@ import FileManagement
import Utils.Conduit
import Utils.Utils (dropEnd)

endswith = flip isSuffixOf

exts :: [FilePath]
exts = do
fq <- ["fq", "fastq"]
Expand All @@ -48,8 +50,8 @@ pairedEnds = do
return (s1 ++ "." ++ end, s2 ++ "." ++ end)

buildSingle m1
| "pair.1" `isInfixOf` m1 = replace "pair.1" "single" m1
| "pair.2" `isInfixOf` m1 = replace "pair.2" "single" m1
| "pair.1" `isInfixOf` m1 = T.unpack $ T.replace "pair.1" "single" (T.pack m1)
| "pair.2" `isInfixOf` m1 = T.unpack $ T.replace "pair.2" "single" (T.pack m1)
| otherwise = "MARKER_FOR_FILE_WHICH_DOES_NOT_EXIST"

mocatSamplePaired :: [FilePath] -> T.Text -> Bool -> NGLessIO [Expression]
Expand All @@ -60,8 +62,8 @@ mocatSamplePaired fqfiles encoding doQC = do
| (endswith p1 fp) -> Just (fp, dropEnd (length p1) fp ++ p2)
| (endswith p2 fp) -> Just (dropEnd (length p2) fp ++ p1, fp)
| otherwise -> Nothing
-- match1 returns repeated entries if both pair.1 and pair.2 exist, uniq removes duplicate records
matched1 = uniq $ mapMaybe match1 fqfiles
-- match1 returns repeated entries if both pair.1 and pair.2 exist, `nub` removes duplicate records
matched1 = nub $ mapMaybe match1 fqfiles
encodeStr = ConstStr . T.pack
(exps,used) <- fmap unzip $ forM matched1 $ \(m1,m2) -> do
let singles = buildSingle m1
Expand Down
6 changes: 4 additions & 2 deletions NGLess/Validation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,8 +15,7 @@ import Control.Monad.Extra (whenJust)
import Control.Monad.Writer.Strict
import Control.Monad.RWS
import Control.Monad (foldM_)
import Data.String.Utils (endswith)
import Data.List (find)
import Data.List (find, isSuffixOf)
import Data.Maybe
import Data.Char (isUpper)
import Data.Foldable (asum)
Expand All @@ -27,6 +26,9 @@ import NGLess.NGError
import BuiltinFunctions
import Utils.Suggestion


endswith = flip isSuffixOf

findMethod :: MethodName -> Maybe MethodInfo
findMethod m = find ((==m) . methodName) builtinMethods

Expand Down

0 comments on commit a63ac18

Please sign in to comment.