{-# LANGUAGE DeriveGeneric #-}
module SLynx.Concatenate.Options
( ConcatenateArguments (..),
concatenateArguments,
)
where
import Control.Applicative
import ELynx.Data.Alphabet.Alphabet
import ELynx.Tools
import Options.Applicative
import SLynx.Tools
data ConcatenateArguments = ConcatenateArguments
{ ConcatenateArguments -> Alphabet
ccAlphabet :: Alphabet,
ConcatenateArguments -> [FilePath]
ccInFiles :: [FilePath]
}
deriving (ConcatenateArguments -> ConcatenateArguments -> Bool
(ConcatenateArguments -> ConcatenateArguments -> Bool)
-> (ConcatenateArguments -> ConcatenateArguments -> Bool)
-> Eq ConcatenateArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ConcatenateArguments -> ConcatenateArguments -> Bool
$c/= :: ConcatenateArguments -> ConcatenateArguments -> Bool
== :: ConcatenateArguments -> ConcatenateArguments -> Bool
$c== :: ConcatenateArguments -> ConcatenateArguments -> Bool
Eq, Int -> ConcatenateArguments -> ShowS
[ConcatenateArguments] -> ShowS
ConcatenateArguments -> FilePath
(Int -> ConcatenateArguments -> ShowS)
-> (ConcatenateArguments -> FilePath)
-> ([ConcatenateArguments] -> ShowS)
-> Show ConcatenateArguments
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ConcatenateArguments] -> ShowS
$cshowList :: [ConcatenateArguments] -> ShowS
show :: ConcatenateArguments -> FilePath
$cshow :: ConcatenateArguments -> FilePath
showsPrec :: Int -> ConcatenateArguments -> ShowS
$cshowsPrec :: Int -> ConcatenateArguments -> ShowS
Show, (forall x. ConcatenateArguments -> Rep ConcatenateArguments x)
-> (forall x. Rep ConcatenateArguments x -> ConcatenateArguments)
-> Generic ConcatenateArguments
forall x. Rep ConcatenateArguments x -> ConcatenateArguments
forall x. ConcatenateArguments -> Rep ConcatenateArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConcatenateArguments x -> ConcatenateArguments
$cfrom :: forall x. ConcatenateArguments -> Rep ConcatenateArguments x
Generic)
instance Reproducible ConcatenateArguments where
inFiles :: ConcatenateArguments -> [FilePath]
inFiles = ConcatenateArguments -> [FilePath]
ccInFiles
outSuffixes :: ConcatenateArguments -> [FilePath]
outSuffixes ConcatenateArguments
_ = [FilePath
".fasta"]
getSeed :: ConcatenateArguments -> Maybe SeedOpt
getSeed ConcatenateArguments
_ = Maybe SeedOpt
forall a. Maybe a
Nothing
setSeed :: ConcatenateArguments -> SeedOpt -> ConcatenateArguments
setSeed = ConcatenateArguments -> SeedOpt -> ConcatenateArguments
forall a b. a -> b -> a
const
parser :: Parser ConcatenateArguments
parser = Parser ConcatenateArguments
concatenateArguments
cmdName :: FilePath
cmdName = FilePath
"concatenate"
cmdDsc :: [FilePath]
cmdDsc = [FilePath
"Concatenate sequences found in input files."]
instance FromJSON ConcatenateArguments
instance ToJSON ConcatenateArguments
concatenateArguments :: Parser ConcatenateArguments
concatenateArguments :: Parser ConcatenateArguments
concatenateArguments = Alphabet -> [FilePath] -> ConcatenateArguments
ConcatenateArguments (Alphabet -> [FilePath] -> ConcatenateArguments)
-> Parser Alphabet -> Parser ([FilePath] -> ConcatenateArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Alphabet
alphabetOpt Parser ([FilePath] -> ConcatenateArguments)
-> Parser [FilePath] -> Parser ConcatenateArguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath -> Parser [FilePath]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
some Parser FilePath
inFileArg
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"