{-# LANGUAGE DeriveGeneric #-}
module SLynx.Filter.Options
( FilterRowsArguments (..),
FilterColsArguments (..),
filterRowsArguments,
filterColsArguments,
)
where
import Control.Applicative
import ELynx.Data.Alphabet.Alphabet
import ELynx.Tools
import Options.Applicative
import SLynx.Tools
data FilterRowsArguments = FilterRowsArguments
{ FilterRowsArguments -> Alphabet
frAlphabet :: Alphabet,
FilterRowsArguments -> FilePath
frInFile :: FilePath,
FilterRowsArguments -> Maybe Int
frLonger :: Maybe Int,
FilterRowsArguments -> Maybe Int
frShorter :: Maybe Int,
FilterRowsArguments -> Bool
frStandard :: Bool
}
deriving (FilterRowsArguments -> FilterRowsArguments -> Bool
(FilterRowsArguments -> FilterRowsArguments -> Bool)
-> (FilterRowsArguments -> FilterRowsArguments -> Bool)
-> Eq FilterRowsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterRowsArguments -> FilterRowsArguments -> Bool
$c/= :: FilterRowsArguments -> FilterRowsArguments -> Bool
== :: FilterRowsArguments -> FilterRowsArguments -> Bool
$c== :: FilterRowsArguments -> FilterRowsArguments -> Bool
Eq, Int -> FilterRowsArguments -> ShowS
[FilterRowsArguments] -> ShowS
FilterRowsArguments -> FilePath
(Int -> FilterRowsArguments -> ShowS)
-> (FilterRowsArguments -> FilePath)
-> ([FilterRowsArguments] -> ShowS)
-> Show FilterRowsArguments
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [FilterRowsArguments] -> ShowS
$cshowList :: [FilterRowsArguments] -> ShowS
show :: FilterRowsArguments -> FilePath
$cshow :: FilterRowsArguments -> FilePath
showsPrec :: Int -> FilterRowsArguments -> ShowS
$cshowsPrec :: Int -> FilterRowsArguments -> ShowS
Show, (forall x. FilterRowsArguments -> Rep FilterRowsArguments x)
-> (forall x. Rep FilterRowsArguments x -> FilterRowsArguments)
-> Generic FilterRowsArguments
forall x. Rep FilterRowsArguments x -> FilterRowsArguments
forall x. FilterRowsArguments -> Rep FilterRowsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilterRowsArguments x -> FilterRowsArguments
$cfrom :: forall x. FilterRowsArguments -> Rep FilterRowsArguments x
Generic)
instance Reproducible FilterRowsArguments where
inFiles :: FilterRowsArguments -> [FilePath]
inFiles = FilePath -> [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> [FilePath])
-> (FilterRowsArguments -> FilePath)
-> FilterRowsArguments
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilterRowsArguments -> FilePath
frInFile
outSuffixes :: FilterRowsArguments -> [FilePath]
outSuffixes FilterRowsArguments
_ = [FilePath
".fasta"]
getSeed :: FilterRowsArguments -> Maybe SeedOpt
getSeed FilterRowsArguments
_ = Maybe SeedOpt
forall a. Maybe a
Nothing
setSeed :: FilterRowsArguments -> SeedOpt -> FilterRowsArguments
setSeed = FilterRowsArguments -> SeedOpt -> FilterRowsArguments
forall a b. a -> b -> a
const
parser :: Parser FilterRowsArguments
parser = Parser FilterRowsArguments
filterRowsArguments
cmdName :: FilePath
cmdName = FilePath
"filter-rows"
cmdDsc :: [FilePath]
cmdDsc = [FilePath
"Filter rows (or sequences) found in input files."]
instance FromJSON FilterRowsArguments
instance ToJSON FilterRowsArguments
data FilterColsArguments = FilterColsArguments
{ FilterColsArguments -> Alphabet
fcAlphabet :: Alphabet,
FilterColsArguments -> FilePath
fcInFile :: FilePath,
FilterColsArguments -> Maybe Double
fcStandard :: Maybe Double
}
deriving (FilterColsArguments -> FilterColsArguments -> Bool
(FilterColsArguments -> FilterColsArguments -> Bool)
-> (FilterColsArguments -> FilterColsArguments -> Bool)
-> Eq FilterColsArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FilterColsArguments -> FilterColsArguments -> Bool
$c/= :: FilterColsArguments -> FilterColsArguments -> Bool
== :: FilterColsArguments -> FilterColsArguments -> Bool
$c== :: FilterColsArguments -> FilterColsArguments -> Bool
Eq, Int -> FilterColsArguments -> ShowS
[FilterColsArguments] -> ShowS
FilterColsArguments -> FilePath
(Int -> FilterColsArguments -> ShowS)
-> (FilterColsArguments -> FilePath)
-> ([FilterColsArguments] -> ShowS)
-> Show FilterColsArguments
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [FilterColsArguments] -> ShowS
$cshowList :: [FilterColsArguments] -> ShowS
show :: FilterColsArguments -> FilePath
$cshow :: FilterColsArguments -> FilePath
showsPrec :: Int -> FilterColsArguments -> ShowS
$cshowsPrec :: Int -> FilterColsArguments -> ShowS
Show, (forall x. FilterColsArguments -> Rep FilterColsArguments x)
-> (forall x. Rep FilterColsArguments x -> FilterColsArguments)
-> Generic FilterColsArguments
forall x. Rep FilterColsArguments x -> FilterColsArguments
forall x. FilterColsArguments -> Rep FilterColsArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FilterColsArguments x -> FilterColsArguments
$cfrom :: forall x. FilterColsArguments -> Rep FilterColsArguments x
Generic)
instance Reproducible FilterColsArguments where
inFiles :: FilterColsArguments -> [FilePath]
inFiles = FilePath -> [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> [FilePath])
-> (FilterColsArguments -> FilePath)
-> FilterColsArguments
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilterColsArguments -> FilePath
fcInFile
outSuffixes :: FilterColsArguments -> [FilePath]
outSuffixes FilterColsArguments
_ = [FilePath
".fasta"]
getSeed :: FilterColsArguments -> Maybe SeedOpt
getSeed FilterColsArguments
_ = Maybe SeedOpt
forall a. Maybe a
Nothing
setSeed :: FilterColsArguments -> SeedOpt -> FilterColsArguments
setSeed = FilterColsArguments -> SeedOpt -> FilterColsArguments
forall a b. a -> b -> a
const
parser :: Parser FilterColsArguments
parser = Parser FilterColsArguments
filterColsArguments
cmdName :: FilePath
cmdName = FilePath
"filter-columns"
cmdDsc :: [FilePath]
cmdDsc = [FilePath
"Filter columns of multi sequence alignments."]
instance FromJSON FilterColsArguments
instance ToJSON FilterColsArguments
filterRowsArguments :: Parser FilterRowsArguments
filterRowsArguments :: Parser FilterRowsArguments
filterRowsArguments =
Alphabet
-> FilePath
-> Maybe Int
-> Maybe Int
-> Bool
-> FilterRowsArguments
FilterRowsArguments
(Alphabet
-> FilePath
-> Maybe Int
-> Maybe Int
-> Bool
-> FilterRowsArguments)
-> Parser Alphabet
-> Parser
(FilePath -> Maybe Int -> Maybe Int -> Bool -> FilterRowsArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Alphabet
alphabetOpt
Parser
(FilePath -> Maybe Int -> Maybe Int -> Bool -> FilterRowsArguments)
-> Parser FilePath
-> Parser (Maybe Int -> Maybe Int -> Bool -> FilterRowsArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath
inFileArg
Parser (Maybe Int -> Maybe Int -> Bool -> FilterRowsArguments)
-> Parser (Maybe Int)
-> Parser (Maybe Int -> Bool -> FilterRowsArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Int)
filterLongerThanOpt
Parser (Maybe Int -> Bool -> FilterRowsArguments)
-> Parser (Maybe Int) -> Parser (Bool -> FilterRowsArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Int)
filterShorterThanOpt
Parser (Bool -> FilterRowsArguments)
-> Parser Bool -> Parser FilterRowsArguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
filterStandardChars
filterLongerThanOpt :: Parser (Maybe Int)
filterLongerThanOpt :: Parser (Maybe Int)
filterLongerThanOpt =
Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Int -> Parser (Maybe Int))
-> Parser Int -> Parser (Maybe Int)
forall a b. (a -> b) -> a -> b
$
ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
$
FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"longer-than" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"LENGTH"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help
FilePath
"Only keep sequences longer than LENGTH"
filterShorterThanOpt :: Parser (Maybe Int)
filterShorterThanOpt :: Parser (Maybe Int)
filterShorterThanOpt =
Parser Int -> Parser (Maybe Int)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Int -> Parser (Maybe Int))
-> Parser Int -> Parser (Maybe Int)
forall a b. (a -> b) -> a -> b
$
ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
$
FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"shorter-than" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"LENGTH"
Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help
FilePath
"Only keep sequences shorter than LENGTH"
filterStandardChars :: Parser Bool
filterStandardChars :: Parser Bool
filterStandardChars =
Mod FlagFields Bool -> Parser Bool
switch (Mod FlagFields Bool -> Parser Bool)
-> Mod FlagFields Bool -> Parser Bool
forall a b. (a -> b) -> a -> b
$
FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"standard-characters"
Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields Bool
forall (f :: * -> *) a. FilePath -> Mod f a
help
FilePath
"Only keep sequences containing at least one standard (i.e., non-IUPAC) character"
filterColsArguments :: Parser FilterColsArguments
filterColsArguments :: Parser FilterColsArguments
filterColsArguments =
Alphabet -> FilePath -> Maybe Double -> FilterColsArguments
FilterColsArguments (Alphabet -> FilePath -> Maybe Double -> FilterColsArguments)
-> Parser Alphabet
-> Parser (FilePath -> Maybe Double -> FilterColsArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Alphabet
alphabetOpt Parser (FilePath -> Maybe Double -> FilterColsArguments)
-> Parser FilePath -> Parser (Maybe Double -> FilterColsArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath
inFileArg Parser (Maybe Double -> FilterColsArguments)
-> Parser (Maybe Double) -> Parser FilterColsArguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe Double)
filterStandardOpt
filterStandardOpt :: Parser (Maybe Double)
filterStandardOpt :: Parser (Maybe Double)
filterStandardOpt =
Parser Double -> Parser (Maybe Double)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser Double -> Parser (Maybe Double))
-> Parser Double -> Parser (Maybe Double)
forall a b. (a -> b) -> a -> b
$
ReadM Double -> Mod OptionFields Double -> Parser Double
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Double
forall a. Read a => ReadM a
auto (Mod OptionFields Double -> Parser Double)
-> Mod OptionFields Double -> Parser Double
forall a b. (a -> b) -> a -> b
$
FilePath -> Mod OptionFields Double
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"standard-chars"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Double
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"DOUBLE"
Mod OptionFields Double
-> Mod OptionFields Double -> Mod OptionFields Double
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Double
forall (f :: * -> *) a. FilePath -> Mod f a
help
FilePath
"Keep columns with a proportion standard (non-IUPAC) characters larger than DOUBLE in [0,1]"
inFileArg :: Parser FilePath
inFileArg :: Parser FilePath
inFileArg =
Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument (Mod ArgumentFields FilePath -> Parser FilePath)
-> Mod ArgumentFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"INPUT-FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Read sequences from INPUT-FILE"