{-# LANGUAGE OverloadedStrings #-}
module Poseidon.CLI.OptparseApplicativeParsers where
import Poseidon.CLI.Chronicle (ChronOperation (..))
import Poseidon.CLI.Forge (ForgeOutMode (..))
import Poseidon.CLI.Jannocoalesce (CoalesceJannoColumnSpec (..),
JannoSourceSpec (..))
import Poseidon.CLI.List (ListEntity (..),
RepoLocationSpec (..))
import Poseidon.CLI.Rectify (ChecksumsToRectify (..),
PackageVersionUpdate (..))
import Poseidon.CLI.Validate (ValidatePlan (..))
import Poseidon.Contributor (ContributorSpec (..),
contributorSpecParser)
import Poseidon.EntityTypes (EntitiesList, EntityInput (..),
PoseidonEntity, SignedEntitiesList,
SignedEntity,
readEntitiesFromString)
import Poseidon.GenotypeData (GenoDataSource (..),
GenotypeDataSpec (..),
GenotypeFileSpec (..),
SNPSetSpec (..))
import Poseidon.ServerClient (AddJannoColSpec (..),
ArchiveEndpoint (..))
import Poseidon.Utils (ErrorLength (..), LogMode (..),
TestMode (..),
renderPoseidonException,
showParsecErr)
import Poseidon.Version (VersionComponent (..),
parseVersion)
import Control.Applicative ((<|>))
import qualified Data.ByteString.Char8 as BSC
import Data.List (intercalate)
import Data.List.Split (splitOn)
import Data.Version (Version)
import qualified Options.Applicative as OP
import SequenceFormats.Plink (PlinkPopNameMode (PlinkPopNameAsBoth, PlinkPopNameAsFamily, PlinkPopNameAsPhenotype))
import System.FilePath (splitExtension, splitExtensions,
takeExtension, (<.>))
import qualified Text.Parsec as P
import Text.Read (readMaybe)
parseChronOperation :: OP.Parser ChronOperation
parseChronOperation :: Parser ChronOperation
parseChronOperation = (String -> ChronOperation
CreateChron (String -> ChronOperation)
-> Parser String -> Parser ChronOperation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseChronOutPath) Parser ChronOperation
-> Parser ChronOperation -> Parser ChronOperation
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> ChronOperation
UpdateChron (String -> ChronOperation)
-> Parser String -> Parser ChronOperation
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseChronUpdatePath)
parseTimetravelSourcePath :: OP.Parser FilePath
parseTimetravelSourcePath :: Parser String
parseTimetravelSourcePath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"srcDir" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
's' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DIR" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to the Git-versioned source directory where the chronFile applies.")
parseTimetravelChronPath :: OP.Parser FilePath
parseTimetravelChronPath :: Parser String
parseTimetravelChronPath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"chronFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'c' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to the chronicle definition file.")
parseChronOutPath :: OP.Parser FilePath
parseChronOutPath :: Parser String
parseChronOutPath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'o' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to the resulting chronicle definition file.")
parseChronUpdatePath :: OP.Parser FilePath
parseChronUpdatePath :: Parser String
parseChronUpdatePath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"updateFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'u' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to the chronicle definition file that should be updated. \
\This file will be overwritten! \
\But the update procedure does not change the package entries \
\that are already in the chronicle definition file. \
\It only adds new entries.")
parseMaybePoseidonVersion :: OP.Parser (Maybe Version)
parseMaybePoseidonVersion :: Parser (Maybe Version)
parseMaybePoseidonVersion = ReadM (Maybe Version)
-> Mod OptionFields (Maybe Version) -> Parser (Maybe Version)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (Version -> Maybe Version
forall a. a -> Maybe a
Just (Version -> Maybe Version)
-> ReadM Version -> ReadM (Maybe Version)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Either String Version) -> ReadM Version
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String Version
readPoseidonVersionString) (
String -> Mod OptionFields (Maybe Version)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"poseidonVersion" Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe Version)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"?.?.?" Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe Version)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Poseidon version the packages should be updated to: \
\e.g. \"2.5.3\"." Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
-> Mod OptionFields (Maybe Version)
forall a. Semigroup a => a -> a -> a
<>
Maybe Version -> Mod OptionFields (Maybe Version)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe Version
forall a. Maybe a
Nothing
)
where
readPoseidonVersionString :: String -> Either String Version
readPoseidonVersionString :: String -> Either String Version
readPoseidonVersionString String
s = case Parsec String () Version
-> () -> String -> String -> Either ParseError Version
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () Version
parseVersion () String
"" String
s of
Left ParseError
p -> String -> Either String Version
forall a b. a -> Either a b
Left (ParseError -> String
showParsecErr ParseError
p)
Right Version
x -> Version -> Either String Version
forall a b. b -> Either a b
Right Version
x
parseDebugMode :: OP.Parser LogMode
parseDebugMode :: Parser LogMode
parseDebugMode = LogMode -> Mod FlagFields LogMode -> Parser LogMode
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' LogMode
VerboseLog (
String -> Mod FlagFields LogMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"debug" Mod FlagFields LogMode
-> Mod FlagFields LogMode -> Mod FlagFields LogMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields LogMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Short for --logMode VerboseLog."
)
parseLogMode :: OP.Parser LogMode
parseLogMode :: Parser LogMode
parseLogMode = ReadM LogMode -> Mod OptionFields LogMode -> Parser LogMode
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String LogMode) -> ReadM LogMode
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String LogMode
readLogMode) (
String -> Mod OptionFields LogMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"logMode" Mod OptionFields LogMode
-> Mod OptionFields LogMode -> Mod OptionFields LogMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields LogMode
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"MODE" Mod OptionFields LogMode
-> Mod OptionFields LogMode -> Mod OptionFields LogMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields LogMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"How information should be reported: \
\NoLog, SimpleLog, DefaultLog, ServerLog or VerboseLog." Mod OptionFields LogMode
-> Mod OptionFields LogMode -> Mod OptionFields LogMode
forall a. Semigroup a => a -> a -> a
<>
LogMode -> Mod OptionFields LogMode
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value LogMode
DefaultLog Mod OptionFields LogMode
-> Mod OptionFields LogMode -> Mod OptionFields LogMode
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields LogMode
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
where
readLogMode :: String -> Either String LogMode
readLogMode :: String -> Either String LogMode
readLogMode String
s = case String
s of
String
"NoLog" -> LogMode -> Either String LogMode
forall a b. b -> Either a b
Right LogMode
NoLog
String
"SimpleLog" -> LogMode -> Either String LogMode
forall a b. b -> Either a b
Right LogMode
SimpleLog
String
"DefaultLog" -> LogMode -> Either String LogMode
forall a b. b -> Either a b
Right LogMode
DefaultLog
String
"ServerLog" -> LogMode -> Either String LogMode
forall a b. b -> Either a b
Right LogMode
ServerLog
String
"VerboseLog" -> LogMode -> Either String LogMode
forall a b. b -> Either a b
Right LogMode
VerboseLog
String
_ -> String -> Either String LogMode
forall a b. a -> Either a b
Left String
"must be NoLog, SimpleLog, DefaultLog, ServerLog or VerboseLog"
parseTestMode :: OP.Parser TestMode
parseTestMode :: Parser TestMode
parseTestMode = ReadM TestMode -> Mod OptionFields TestMode -> Parser TestMode
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String TestMode) -> ReadM TestMode
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String TestMode
readTestMode) (
String -> Mod OptionFields TestMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"testMode" Mod OptionFields TestMode
-> Mod OptionFields TestMode -> Mod OptionFields TestMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields TestMode
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"MODE" Mod OptionFields TestMode
-> Mod OptionFields TestMode -> Mod OptionFields TestMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields TestMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"\"Testing\" activates a test mode; relevant only \
\for developers in very specific edge cases." Mod OptionFields TestMode
-> Mod OptionFields TestMode -> Mod OptionFields TestMode
forall a. Semigroup a => a -> a -> a
<>
TestMode -> Mod OptionFields TestMode
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value TestMode
Production Mod OptionFields TestMode
-> Mod OptionFields TestMode -> Mod OptionFields TestMode
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields TestMode
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault Mod OptionFields TestMode
-> Mod OptionFields TestMode -> Mod OptionFields TestMode
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields TestMode
forall (f :: * -> *) a. Mod f a
OP.internal
)
where
readTestMode :: String -> Either String TestMode
readTestMode :: String -> Either String TestMode
readTestMode String
s = case String
s of
String
"Testing" -> TestMode -> Either String TestMode
forall a b. b -> Either a b
Right TestMode
Testing
String
"Production" -> TestMode -> Either String TestMode
forall a b. b -> Either a b
Right TestMode
Production
String
_ -> String -> Either String TestMode
forall a b. a -> Either a b
Left String
"must be Testing or Production"
parseErrorLength :: OP.Parser ErrorLength
parseErrorLength :: Parser ErrorLength
parseErrorLength = ReadM ErrorLength
-> Mod OptionFields ErrorLength -> Parser ErrorLength
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String ErrorLength) -> ReadM ErrorLength
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String ErrorLength
readErrorLengthString) (
String -> Mod OptionFields ErrorLength
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"errLength" Mod OptionFields ErrorLength
-> Mod OptionFields ErrorLength -> Mod OptionFields ErrorLength
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields ErrorLength
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"INT" Mod OptionFields ErrorLength
-> Mod OptionFields ErrorLength -> Mod OptionFields ErrorLength
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields ErrorLength
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"After how many characters should a potential genotype data parsing error \
\message be truncated. \"Inf\" for no truncation." Mod OptionFields ErrorLength
-> Mod OptionFields ErrorLength -> Mod OptionFields ErrorLength
forall a. Semigroup a => a -> a -> a
<>
ErrorLength -> Mod OptionFields ErrorLength
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value (Int -> ErrorLength
CharCount Int
1500) Mod OptionFields ErrorLength
-> Mod OptionFields ErrorLength -> Mod OptionFields ErrorLength
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields ErrorLength
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
) where
readErrorLengthString :: String -> Either String ErrorLength
readErrorLengthString :: String -> Either String ErrorLength
readErrorLengthString String
s = do
if String
s String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"Inf"
then ErrorLength -> Either String ErrorLength
forall a b. b -> Either a b
Right ErrorLength
CharInf
else case String -> Maybe Int
forall a. Read a => String -> Maybe a
readMaybe String
s of
Just Int
n -> ErrorLength -> Either String ErrorLength
forall a b. b -> Either a b
Right (ErrorLength -> Either String ErrorLength)
-> ErrorLength -> Either String ErrorLength
forall a b. (a -> b) -> a -> b
$ Int -> ErrorLength
CharCount Int
n
Maybe Int
Nothing -> String -> Either String ErrorLength
forall a b. a -> Either a b
Left String
"must be either \"Inf\" or an integer number"
parseRemoveOld :: OP.Parser Bool
parseRemoveOld :: Parser Bool
parseRemoveOld = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"removeOld" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Remove the old genotype files when creating the new ones."
)
parseChecksumsToRectify :: OP.Parser ChecksumsToRectify
parseChecksumsToRectify :: Parser ChecksumsToRectify
parseChecksumsToRectify = Parser ChecksumsToRectify
parseChecksumNone Parser ChecksumsToRectify
-> Parser ChecksumsToRectify -> Parser ChecksumsToRectify
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ChecksumsToRectify
parseChecksumAll Parser ChecksumsToRectify
-> Parser ChecksumsToRectify -> Parser ChecksumsToRectify
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ChecksumsToRectify
parseChecksumsDetail
where
parseChecksumNone :: OP.Parser ChecksumsToRectify
parseChecksumNone :: Parser ChecksumsToRectify
parseChecksumNone = ChecksumsToRectify -> Parser ChecksumsToRectify
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ChecksumsToRectify
ChecksumNone
parseChecksumAll :: OP.Parser ChecksumsToRectify
parseChecksumAll :: Parser ChecksumsToRectify
parseChecksumAll = ChecksumsToRectify
ChecksumAll ChecksumsToRectify -> Parser () -> Parser ChecksumsToRectify
forall a b. a -> Parser b -> Parser a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$
() -> Mod FlagFields () -> Parser ()
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' () (
String -> Mod FlagFields ()
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"checksumAll" Mod FlagFields () -> Mod FlagFields () -> Mod FlagFields ()
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ()
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Update all checksums.")
parseChecksumsDetail :: OP.Parser ChecksumsToRectify
parseChecksumsDetail :: Parser ChecksumsToRectify
parseChecksumsDetail = Bool -> Bool -> Bool -> Bool -> ChecksumsToRectify
ChecksumsDetail (Bool -> Bool -> Bool -> Bool -> ChecksumsToRectify)
-> Parser Bool
-> Parser (Bool -> Bool -> Bool -> ChecksumsToRectify)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
Parser Bool
parseChecksumGeno Parser (Bool -> Bool -> Bool -> ChecksumsToRectify)
-> Parser Bool -> Parser (Bool -> Bool -> ChecksumsToRectify)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Parser Bool
parseChecksumJanno Parser (Bool -> Bool -> ChecksumsToRectify)
-> Parser Bool -> Parser (Bool -> ChecksumsToRectify)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Parser Bool
parseChecksumSSF Parser (Bool -> ChecksumsToRectify)
-> Parser Bool -> Parser ChecksumsToRectify
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Parser Bool
parseChecksumBib
parseChecksumGeno :: OP.Parser Bool
parseChecksumGeno :: Parser Bool
parseChecksumGeno = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"checksumGeno" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Update genotype data checksums.")
parseChecksumJanno :: OP.Parser Bool
parseChecksumJanno :: Parser Bool
parseChecksumJanno = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"checksumJanno" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Update .janno file checksum.")
parseChecksumSSF :: OP.Parser Bool
parseChecksumSSF :: Parser Bool
parseChecksumSSF = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"checksumSSF" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Update .ssf file checksum")
parseChecksumBib :: OP.Parser Bool
parseChecksumBib :: Parser Bool
parseChecksumBib = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"checksumBib" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Update .bib file checksum.")
parseMaybePackageVersionUpdate :: OP.Parser (Maybe PackageVersionUpdate)
parseMaybePackageVersionUpdate :: Parser (Maybe PackageVersionUpdate)
parseMaybePackageVersionUpdate = Parser PackageVersionUpdate -> Parser (Maybe PackageVersionUpdate)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OP.optional (Parser PackageVersionUpdate
-> Parser (Maybe PackageVersionUpdate))
-> Parser PackageVersionUpdate
-> Parser (Maybe PackageVersionUpdate)
forall a b. (a -> b) -> a -> b
$ VersionComponent -> Maybe String -> PackageVersionUpdate
PackageVersionUpdate (VersionComponent -> Maybe String -> PackageVersionUpdate)
-> Parser VersionComponent
-> Parser (Maybe String -> PackageVersionUpdate)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser VersionComponent
parseVersionComponent Parser (Maybe String -> PackageVersionUpdate)
-> Parser (Maybe String) -> Parser PackageVersionUpdate
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe String)
parseMaybeLog
parseVersionComponent :: OP.Parser VersionComponent
parseVersionComponent :: Parser VersionComponent
parseVersionComponent = ReadM VersionComponent
-> Mod OptionFields VersionComponent -> Parser VersionComponent
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String VersionComponent)
-> ReadM VersionComponent
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String VersionComponent
readVersionComponent) (
String -> Mod OptionFields VersionComponent
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"packageVersion" Mod OptionFields VersionComponent
-> Mod OptionFields VersionComponent
-> Mod OptionFields VersionComponent
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields VersionComponent
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"VPART" Mod OptionFields VersionComponent
-> Mod OptionFields VersionComponent
-> Mod OptionFields VersionComponent
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields VersionComponent
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Part of the package version number in the POSEIDON.yml file \
\that should be updated: \
\Major, Minor or Patch (see https://semver.org)."
)
where
readVersionComponent :: String -> Either String VersionComponent
readVersionComponent :: String -> Either String VersionComponent
readVersionComponent String
s = case String
s of
String
"Major" -> VersionComponent -> Either String VersionComponent
forall a b. b -> Either a b
Right VersionComponent
Major
String
"Minor" -> VersionComponent -> Either String VersionComponent
forall a b. b -> Either a b
Right VersionComponent
Minor
String
"Patch" -> VersionComponent -> Either String VersionComponent
forall a b. b -> Either a b
Right VersionComponent
Patch
String
_ -> String -> Either String VersionComponent
forall a b. a -> Either a b
Left String
"must be Major, Minor or Patch"
parseNoChecksumUpdate :: OP.Parser Bool
parseNoChecksumUpdate :: Parser Bool
parseNoChecksumUpdate = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"noChecksumUpdate" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Should the update of checksums in the POSEIDON.yml file be skipped?"
)
parseMaybeContributors :: OP.Parser (Maybe [ContributorSpec])
parseMaybeContributors :: Parser (Maybe [ContributorSpec])
parseMaybeContributors = ReadM (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
-> Parser (Maybe [ContributorSpec])
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ([ContributorSpec] -> Maybe [ContributorSpec]
forall a. a -> Maybe a
Just ([ContributorSpec] -> Maybe [ContributorSpec])
-> ReadM [ContributorSpec] -> ReadM (Maybe [ContributorSpec])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> Either String [ContributorSpec])
-> ReadM [ContributorSpec]
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String [ContributorSpec]
readContributorString) (
String -> Mod OptionFields (Maybe [ContributorSpec])
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"newContributors" Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe [ContributorSpec])
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DSL" Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe [ContributorSpec])
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Contributors to add to the POSEIDON.yml file \
\ in the form \"[Firstname Lastname](Email address);...\"." Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
-> Mod OptionFields (Maybe [ContributorSpec])
forall a. Semigroup a => a -> a -> a
<>
Maybe [ContributorSpec]
-> Mod OptionFields (Maybe [ContributorSpec])
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe [ContributorSpec]
forall a. Maybe a
Nothing
)
parseContributors :: OP.Parser [ContributorSpec]
parseContributors :: Parser [ContributorSpec]
parseContributors = ReadM [ContributorSpec]
-> Mod OptionFields [ContributorSpec] -> Parser [ContributorSpec]
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String [ContributorSpec])
-> ReadM [ContributorSpec]
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String [ContributorSpec]
readContributorString) (
String -> Mod OptionFields [ContributorSpec]
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"newContributors" Mod OptionFields [ContributorSpec]
-> Mod OptionFields [ContributorSpec]
-> Mod OptionFields [ContributorSpec]
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields [ContributorSpec]
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DSL" Mod OptionFields [ContributorSpec]
-> Mod OptionFields [ContributorSpec]
-> Mod OptionFields [ContributorSpec]
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields [ContributorSpec]
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Contributors to add to the POSEIDON.yml file \
\ in the form \"[Firstname Lastname](Email address);...\"."
)
readContributorString :: String -> Either String [ContributorSpec]
readContributorString :: String -> Either String [ContributorSpec]
readContributorString String
s = case Parsec String () [ContributorSpec]
-> () -> String -> String -> Either ParseError [ContributorSpec]
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () [ContributorSpec]
contributorSpecParser () String
"" String
s of
Left ParseError
p -> String -> Either String [ContributorSpec]
forall a b. a -> Either a b
Left (ParseError -> String
showParsecErr ParseError
p)
Right [ContributorSpec]
x -> [ContributorSpec] -> Either String [ContributorSpec]
forall a b. b -> Either a b
Right [ContributorSpec]
x
parseMaybeLog :: OP.Parser (Maybe String)
parseMaybeLog :: Parser (Maybe String)
parseMaybeLog = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"logText" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"STRING" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Log text for this version in the CHANGELOG file." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing
)
parseLog :: OP.Parser String
parseLog :: Parser String
parseLog = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"logText" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"STRING" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Log text for this version in the CHANGELOG file." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value String
"not specified" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseForce :: OP.Parser Bool
parseForce :: Parser Bool
parseForce = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"force" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Normally the POSEIDON.yml files are only changed if the \
\poseidonVersion is adjusted or any of the checksums change. \
\With --force a package version update can be triggered even \
\if this is not the case."
)
parseForgeEntityInputs :: OP.Parser [EntityInput SignedEntity]
parseForgeEntityInputs :: Parser [EntityInput SignedEntity]
parseForgeEntityInputs = Parser (EntityInput SignedEntity)
-> Parser [EntityInput SignedEntity]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.many Parser (EntityInput SignedEntity)
parseSignedEntityInput
where
parseSignedEntityInput :: Parser (EntityInput SignedEntity)
parseSignedEntityInput = (String -> EntityInput SignedEntity
forall a. String -> EntityInput a
EntitiesFromFile (String -> EntityInput SignedEntity)
-> Parser String -> Parser (EntityInput SignedEntity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseForgeEntitiesFromFile) Parser (EntityInput SignedEntity)
-> Parser (EntityInput SignedEntity)
-> Parser (EntityInput SignedEntity)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (SignedEntitiesList -> EntityInput SignedEntity
forall a. [a] -> EntityInput a
EntitiesDirect (SignedEntitiesList -> EntityInput SignedEntity)
-> Parser SignedEntitiesList -> Parser (EntityInput SignedEntity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SignedEntitiesList
parseForgeEntitiesDirect)
parseFetchEntityInputs :: OP.Parser [EntityInput PoseidonEntity]
parseFetchEntityInputs :: Parser [EntityInput PoseidonEntity]
parseFetchEntityInputs = Parser [EntityInput PoseidonEntity]
forall {a}. Parser [a]
parseDownloadAll Parser [EntityInput PoseidonEntity]
-> Parser [EntityInput PoseidonEntity]
-> Parser [EntityInput PoseidonEntity]
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser (EntityInput PoseidonEntity)
-> Parser [EntityInput PoseidonEntity]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.some Parser (EntityInput PoseidonEntity)
parseEntityInput
where
parseDownloadAll :: Parser [a]
parseDownloadAll = [a] -> Mod FlagFields [a] -> Parser [a]
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' [] (
String -> Mod FlagFields [a]
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"downloadAll" Mod FlagFields [a] -> Mod FlagFields [a] -> Mod FlagFields [a]
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields [a]
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Download all packages the server is offering."
)
parseEntityInput :: Parser (EntityInput PoseidonEntity)
parseEntityInput = (String -> EntityInput PoseidonEntity
forall a. String -> EntityInput a
EntitiesFromFile (String -> EntityInput PoseidonEntity)
-> Parser String -> Parser (EntityInput PoseidonEntity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseFetchEntitiesFromFile) Parser (EntityInput PoseidonEntity)
-> Parser (EntityInput PoseidonEntity)
-> Parser (EntityInput PoseidonEntity)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (EntitiesList -> EntityInput PoseidonEntity
forall a. [a] -> EntityInput a
EntitiesDirect (EntitiesList -> EntityInput PoseidonEntity)
-> Parser EntitiesList -> Parser (EntityInput PoseidonEntity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser EntitiesList
parseFetchEntitiesDirect)
parseIgnorePoseidonVersion :: OP.Parser Bool
parseIgnorePoseidonVersion :: Parser Bool
parseIgnorePoseidonVersion = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ignorePoseidonVersion" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Read packages even if their poseidonVersion is not compatible with trident."
)
parseForgeEntitiesDirect :: OP.Parser SignedEntitiesList
parseForgeEntitiesDirect :: Parser SignedEntitiesList
parseForgeEntitiesDirect = ReadM SignedEntitiesList
-> Mod OptionFields SignedEntitiesList -> Parser SignedEntitiesList
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String SignedEntitiesList)
-> ReadM SignedEntitiesList
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String SignedEntitiesList
forall {a}. EntitySpec a => String -> Either String [a]
readSignedEntities) (
String -> Mod OptionFields SignedEntitiesList
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"forgeString" Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields SignedEntitiesList
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'f' Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields SignedEntitiesList
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DSL" Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
-> Mod OptionFields SignedEntitiesList
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields SignedEntitiesList
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List of packages, groups or individual samples to be combined in the output package. \
\Packages follow the syntax *package_title*, populations/groups are simply group_id and individuals \
\<individual_id>. You can combine multiple values with comma, so for example: \
\\"*package_1*, <individual_1>, <individual_2>, group_1\". Duplicates are treated as one entry. \
\Negative selection is possible by prepending \"-\" to the entity you want to exclude \
\(e.g. \"*package_1*, -<individual_1>, -group_1\"). \
\forge will apply excludes and includes in order. If the first entity is negative, then forge \
\will assume you want to merge all individuals in the packages found in the baseDirs (except the \
\ones explicitly excluded) before the exclude entities are applied. \
\An empty forgeString (and no --forgeFile) will therefore merge all available individuals. \
\If there are individuals in your input packages with equal individual id, but different main group or \
\source package, they can be specified with the special syntax \"<package:group:individual>\".")
where
readSignedEntities :: String -> Either String [a]
readSignedEntities String
s = case String -> Either PoseidonException [a]
forall a. EntitySpec a => String -> Either PoseidonException [a]
readEntitiesFromString String
s of
Left PoseidonException
e -> String -> Either String [a]
forall a b. a -> Either a b
Left (String -> Either String [a]) -> String -> Either String [a]
forall a b. (a -> b) -> a -> b
$ PoseidonException -> String
renderPoseidonException PoseidonException
e
Right [a]
e -> [a] -> Either String [a]
forall a b. b -> Either a b
Right [a]
e
parseFetchEntitiesDirect :: OP.Parser EntitiesList
parseFetchEntitiesDirect :: Parser EntitiesList
parseFetchEntitiesDirect = ReadM EntitiesList
-> Mod OptionFields EntitiesList -> Parser EntitiesList
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String EntitiesList) -> ReadM EntitiesList
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String EntitiesList
forall {a}. EntitySpec a => String -> Either String [a]
readEntities) (
String -> Mod OptionFields EntitiesList
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"fetchString" Mod OptionFields EntitiesList
-> Mod OptionFields EntitiesList -> Mod OptionFields EntitiesList
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields EntitiesList
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'f' Mod OptionFields EntitiesList
-> Mod OptionFields EntitiesList -> Mod OptionFields EntitiesList
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields EntitiesList
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DSL" Mod OptionFields EntitiesList
-> Mod OptionFields EntitiesList -> Mod OptionFields EntitiesList
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields EntitiesList
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List of packages to be downloaded from the remote server. \
\Package names should be wrapped in asterisks: *package_title*. \
\You can combine multiple values with comma, so for example: \"*package_1*, *package_2*, *package_3*\". \
\fetchString uses the same parser as forgeString, but does not allow excludes. If groups or individuals are \
\specified, then packages which include these groups or individuals are included in the download.")
where
readEntities :: String -> Either String [a]
readEntities String
s = case String -> Either PoseidonException [a]
forall a. EntitySpec a => String -> Either PoseidonException [a]
readEntitiesFromString String
s of
Left PoseidonException
e -> String -> Either String [a]
forall a b. a -> Either a b
Left (String -> Either String [a]) -> String -> Either String [a]
forall a b. (a -> b) -> a -> b
$ PoseidonException -> String
renderPoseidonException PoseidonException
e
Right [a]
e -> [a] -> Either String [a]
forall a b. b -> Either a b
Right [a]
e
parseForgeEntitiesFromFile :: OP.Parser FilePath
parseForgeEntitiesFromFile :: Parser String
parseForgeEntitiesFromFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"forgeFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A file with a list of packages, groups or individual samples. \
\Works just as -f, but multiple values can also be separated by newline, not just by comma. \
\Empty lines are ignored and comments start with \"#\", so everything after \"#\" is ignored \
\in one line. \
\Multiple instances of -f and --forgeFile can be given. They will be evaluated according to their \
\input order on the command line.")
parseFetchEntitiesFromFile :: OP.Parser FilePath
parseFetchEntitiesFromFile :: Parser String
parseFetchEntitiesFromFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"fetchFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A file with a list of packages. \
\Works just as -f, but multiple values can also be separated by newline, not just by comma. \
\-f and --fetchFile can be combined.")
parseIntersect :: OP.Parser Bool
parseIntersect :: Parser Bool
parseIntersect = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"intersect" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Whether to output the intersection of the genotype files to be forged. \
\The default (if this option is not set) is to output the union of all SNPs, with genotypes \
\defined as missing in those packages which do not have a SNP that is present in another package. \
\With this option set, the forged dataset will typically have fewer SNPs, but less missingness.")
parseRemoteDummy :: OP.Parser ()
parseRemoteDummy :: Parser ()
parseRemoteDummy = () -> Mod FlagFields () -> Parser ()
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' () (
String -> Mod FlagFields ()
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"remote" Mod FlagFields () -> Mod FlagFields () -> Mod FlagFields ()
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ()
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List packages from a remote server instead the local file system.")
parseOutGenotypeFormat :: Bool -> OP.Parser String
parseOutGenotypeFormat :: Bool -> Parser String
parseOutGenotypeFormat Bool
withDefault =
if Bool
withDefault
then Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption Mod OptionFields String
settingsWithDefault
else Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption Mod OptionFields String
forall {a}. Mod OptionFields a
settingsWithoutDefault
where
settingsWithDefault :: Mod OptionFields String
settingsWithDefault =
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outFormat" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FORMAT" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The format of the output genotype data: EIGENSTRAT or PLINK." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value String
"PLINK" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
settingsWithoutDefault :: Mod OptionFields a
settingsWithoutDefault =
String -> Mod OptionFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outFormat" Mod OptionFields a -> Mod OptionFields a -> Mod OptionFields a
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields a
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FORMAT" Mod OptionFields a -> Mod OptionFields a -> Mod OptionFields a
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields a
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"the format of the output genotype data: EIGENSTRAT or PLINK."
parseGenoDataSources :: OP.Parser [GenoDataSource]
parseGenoDataSources :: Parser [GenoDataSource]
parseGenoDataSources = Parser GenoDataSource -> Parser [GenoDataSource]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.some Parser GenoDataSource
parseGenoDataSource
parseGenoDataSource :: OP.Parser GenoDataSource
parseGenoDataSource :: Parser GenoDataSource
parseGenoDataSource = (String -> GenoDataSource
PacBaseDir (String -> GenoDataSource)
-> Parser String -> Parser GenoDataSource
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseBasePath) Parser GenoDataSource
-> Parser GenoDataSource -> Parser GenoDataSource
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (GenotypeDataSpec -> GenoDataSource
GenoDirect (GenotypeDataSpec -> GenoDataSource)
-> Parser GenotypeDataSpec -> Parser GenoDataSource
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GenotypeDataSpec
parseInGenotypeDataset)
parseRepoLocation :: OP.Parser RepoLocationSpec
parseRepoLocation :: Parser RepoLocationSpec
parseRepoLocation = ([String] -> RepoLocationSpec
RepoLocal ([String] -> RepoLocationSpec)
-> Parser [String] -> Parser RepoLocationSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [String]
parseBasePaths) Parser RepoLocationSpec
-> Parser RepoLocationSpec -> Parser RepoLocationSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser ()
parseRemoteDummy Parser () -> Parser RepoLocationSpec -> Parser RepoLocationSpec
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (ArchiveEndpoint -> RepoLocationSpec
RepoRemote (ArchiveEndpoint -> RepoLocationSpec)
-> Parser ArchiveEndpoint -> Parser RepoLocationSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser ArchiveEndpoint
parseArchiveEndpoint))
parseArchiveEndpoint :: OP.Parser ArchiveEndpoint
parseArchiveEndpoint :: Parser ArchiveEndpoint
parseArchiveEndpoint = String -> Maybe String -> ArchiveEndpoint
ArchiveEndpoint (String -> Maybe String -> ArchiveEndpoint)
-> Parser String -> Parser (Maybe String -> ArchiveEndpoint)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseRemoteURL Parser (Maybe String -> ArchiveEndpoint)
-> Parser (Maybe String) -> Parser ArchiveEndpoint
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe String)
parseMaybeArchiveName
parseValidatePlan :: OP.Parser ValidatePlan
parseValidatePlan :: Parser ValidatePlan
parseValidatePlan =
([String] -> Bool -> Bool -> Bool -> Bool -> Bool -> ValidatePlan
ValPlanBaseDirs ([String] -> Bool -> Bool -> Bool -> Bool -> Bool -> ValidatePlan)
-> Parser [String]
-> Parser (Bool -> Bool -> Bool -> Bool -> Bool -> ValidatePlan)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [String]
parseBasePaths
Parser (Bool -> Bool -> Bool -> Bool -> Bool -> ValidatePlan)
-> Parser Bool
-> Parser (Bool -> Bool -> Bool -> Bool -> ValidatePlan)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseIgnoreGeno
Parser (Bool -> Bool -> Bool -> Bool -> ValidatePlan)
-> Parser Bool -> Parser (Bool -> Bool -> Bool -> ValidatePlan)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseFullGeno
Parser (Bool -> Bool -> Bool -> ValidatePlan)
-> Parser Bool -> Parser (Bool -> Bool -> ValidatePlan)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseIgnoreDuplicates
Parser (Bool -> Bool -> ValidatePlan)
-> Parser Bool -> Parser (Bool -> ValidatePlan)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseIgnoreChecksums
Parser (Bool -> ValidatePlan) -> Parser Bool -> Parser ValidatePlan
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Bool
parseIgnorePoseidonVersion)
Parser ValidatePlan -> Parser ValidatePlan -> Parser ValidatePlan
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> ValidatePlan
ValPlanPoseidonYaml (String -> ValidatePlan) -> Parser String -> Parser ValidatePlan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseInPoseidonYamlFile)
Parser ValidatePlan -> Parser ValidatePlan -> Parser ValidatePlan
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (GenotypeDataSpec -> ValidatePlan
ValPlanGeno (GenotypeDataSpec -> ValidatePlan)
-> Parser GenotypeDataSpec -> Parser ValidatePlan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser GenotypeDataSpec
parseInGenoWithoutSNPSet)
Parser ValidatePlan -> Parser ValidatePlan -> Parser ValidatePlan
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> ValidatePlan
ValPlanJanno (String -> ValidatePlan) -> Parser String -> Parser ValidatePlan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseInJannoFile)
Parser ValidatePlan -> Parser ValidatePlan -> Parser ValidatePlan
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> ValidatePlan
ValPlanSSF (String -> ValidatePlan) -> Parser String -> Parser ValidatePlan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseInSSFile)
Parser ValidatePlan -> Parser ValidatePlan -> Parser ValidatePlan
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (String -> ValidatePlan
ValPlanBib (String -> ValidatePlan) -> Parser String -> Parser ValidatePlan
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseInBibFile)
parseInPoseidonYamlFile :: OP.Parser FilePath
parseInPoseidonYamlFile :: Parser String
parseInPoseidonYamlFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"pyml" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to a POSEIDON.yml file.")
parseInJannoFile :: OP.Parser FilePath
parseInJannoFile :: Parser String
parseInJannoFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"janno" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to a .janno file.")
parseInSSFile :: OP.Parser FilePath
parseInSSFile :: Parser String
parseInSSFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ssf" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to a .ssf file.")
parseInBibFile :: OP.Parser FilePath
parseInBibFile :: Parser String
parseInBibFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"bib" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to a .bib file.")
parseBasePaths :: OP.Parser [FilePath]
parseBasePaths :: Parser [String]
parseBasePaths = Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.some Parser String
parseBasePath
parseBasePath :: OP.Parser FilePath
parseBasePath :: Parser String
parseBasePath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"baseDir" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'd' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DIR" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A base directory to search for Poseidon packages.")
parseInGenoWithoutSNPSet :: OP.Parser GenotypeDataSpec
parseInGenoWithoutSNPSet :: Parser GenotypeDataSpec
parseInGenoWithoutSNPSet = GenotypeFileSpec -> Maybe SNPSetSpec -> GenotypeDataSpec
GenotypeDataSpec (GenotypeFileSpec -> Maybe SNPSetSpec -> GenotypeDataSpec)
-> Parser GenotypeFileSpec
-> Parser (Maybe SNPSetSpec -> GenotypeDataSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser GenotypeFileSpec
parseInGenoOne Parser GenotypeFileSpec
-> Parser GenotypeFileSpec -> Parser GenotypeFileSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser GenotypeFileSpec
parseInGenoSep) Parser (Maybe SNPSetSpec -> GenotypeDataSpec)
-> Parser (Maybe SNPSetSpec) -> Parser GenotypeDataSpec
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SNPSetSpec -> Parser (Maybe SNPSetSpec)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe SNPSetSpec
forall a. Maybe a
Nothing
parseInGenotypeDataset :: OP.Parser GenotypeDataSpec
parseInGenotypeDataset :: Parser GenotypeDataSpec
parseInGenotypeDataset = GenotypeFileSpec -> Maybe SNPSetSpec -> GenotypeDataSpec
GenotypeDataSpec (GenotypeFileSpec -> Maybe SNPSetSpec -> GenotypeDataSpec)
-> Parser GenotypeFileSpec
-> Parser (Maybe SNPSetSpec -> GenotypeDataSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser GenotypeFileSpec
parseInGenoOne Parser GenotypeFileSpec
-> Parser GenotypeFileSpec -> Parser GenotypeFileSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser GenotypeFileSpec
parseInGenoSep) Parser (Maybe SNPSetSpec -> GenotypeDataSpec)
-> Parser (Maybe SNPSetSpec) -> Parser GenotypeDataSpec
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (SNPSetSpec -> Maybe SNPSetSpec
forall a. a -> Maybe a
Just (SNPSetSpec -> Maybe SNPSetSpec)
-> Parser SNPSetSpec -> Parser (Maybe SNPSetSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser SNPSetSpec
parseGenotypeSNPSet)
parseInGenoOne :: OP.Parser GenotypeFileSpec
parseInGenoOne :: Parser GenotypeFileSpec
parseInGenoOne = ReadM GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec -> Parser GenotypeFileSpec
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String GenotypeFileSpec)
-> ReadM GenotypeFileSpec
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String GenotypeFileSpec
readGenoInput) (
String -> Mod OptionFields GenotypeFileSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"genoOne" Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields GenotypeFileSpec
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'p' Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields GenotypeFileSpec
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
-> Mod OptionFields GenotypeFileSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields GenotypeFileSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"One of the input genotype data files. \
\Expects .bed, .bed.gz, .bim, .bim.gz or .fam for PLINK, \
\.geno, .geno.gz, .snp, .snp.gz or .ind for EIGENSTRAT, or\
\.vcf or .vcf.gz for VCF. \
\In case of EIGENSTRAT and PLINK, the two other files must be in the same directory \
\and must have the same base name. If a gzipped file is given, it is assumed that the \
\file pairs (.geno.gz, .snp.gz) or (.bim.gz, .bed.gz) are both zipped, but not the .fam or .ind file. \
\If a .ind or .fam file is given, it is assumed that none of the file triples is zipped.")
where
readGenoInput :: FilePath -> Either String GenotypeFileSpec
readGenoInput :: String -> Either String GenotypeFileSpec
readGenoInput String
p =
let (String
path, String
extension) = String -> (String, String)
splitExtensionsOptGz String
p
in String -> String -> Either String GenotypeFileSpec
makeGenoInput String
path String
extension
makeGenoInput :: String -> String -> Either String GenotypeFileSpec
makeGenoInput String
path String
ext
| String
ext String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".geno", String
".snp", String
".ind"] =
GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. b -> Either a b
Right (GenotypeFileSpec -> Either String GenotypeFileSpec)
-> GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypeEigenstrat (String
path String -> String -> String
<.> String
"geno") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"snp") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"ind") Maybe String
forall a. Maybe a
Nothing
| String
ext String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".geno.gz", String
".snp.gz" ] =
GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. b -> Either a b
Right (GenotypeFileSpec -> Either String GenotypeFileSpec)
-> GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypeEigenstrat (String
path String -> String -> String
<.> String
"geno.gz") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"snp.gz") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"ind") Maybe String
forall a. Maybe a
Nothing
| String
ext String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".bed", String
".bim", String
".fam"] =
GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. b -> Either a b
Right (GenotypeFileSpec -> Either String GenotypeFileSpec)
-> GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypePlink (String
path String -> String -> String
<.> String
"bed") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"bim") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"fam") Maybe String
forall a. Maybe a
Nothing
| String
ext String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".bed.gz", String
".bim.gz" ] =
GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. b -> Either a b
Right (GenotypeFileSpec -> Either String GenotypeFileSpec)
-> GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypePlink (String
path String -> String -> String
<.> String
"bed.gz") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"bim.gz") Maybe String
forall a. Maybe a
Nothing
(String
path String -> String -> String
<.> String
"fam") Maybe String
forall a. Maybe a
Nothing
| String
ext String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String
".vcf", String
".vcf.gz" ] =
GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. b -> Either a b
Right (GenotypeFileSpec -> Either String GenotypeFileSpec)
-> GenotypeFileSpec -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String -> Maybe String -> GenotypeFileSpec
GenotypeVCF (String
path String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
ext) Maybe String
forall a. Maybe a
Nothing
| Bool
otherwise = String -> Either String GenotypeFileSpec
forall a b. a -> Either a b
Left (String -> Either String GenotypeFileSpec)
-> String -> Either String GenotypeFileSpec
forall a b. (a -> b) -> a -> b
$ String
"unknown file extension: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
ext
splitExtensionsOptGz :: FilePath -> (FilePath, String)
splitExtensionsOptGz :: String -> (String, String)
splitExtensionsOptGz String
fp =
if String -> String
takeExtension String
fp String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= String
".gz" then
String -> (String, String)
splitExtension String
fp
else
let (String
path, String
allExtensions) = String -> (String, String)
splitExtensions String
fp
extensionsList :: [String]
extensionsList = Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
1 ([String] -> [String])
-> (String -> [String]) -> String -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"." (String -> [String]) -> String -> [String]
forall a b. (a -> b) -> a -> b
$ String
allExtensions
in case [String]
extensionsList of
[String
"gz"] -> String -> (String, String)
splitExtension String
fp
[String
_, String
"gz"] -> String -> (String, String)
splitExtensions String
fp
[String]
_ ->
let doubleExtension :: String
doubleExtension = (String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++) (String -> String) -> ([String] -> String) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
take Int
2 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
extensionsList
extendedPath :: String
extendedPath = String
path String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"." String -> String -> String
forall a. [a] -> [a] -> [a]
++ (String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." ([String] -> String)
-> ([String] -> [String]) -> [String] -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [String]
forall a. Int -> [a] -> [a]
drop Int
2 ([String] -> [String])
-> ([String] -> [String]) -> [String] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> [String]
forall a. [a] -> [a]
reverse ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ [String]
extensionsList)
in (String
extendedPath, String
doubleExtension)
parseInGenoSep :: OP.Parser GenotypeFileSpec
parseInGenoSep :: Parser GenotypeFileSpec
parseInGenoSep = Parser GenotypeFileSpec
parseEigenstrat Parser GenotypeFileSpec
-> Parser GenotypeFileSpec -> Parser GenotypeFileSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser GenotypeFileSpec
parsePlink Parser GenotypeFileSpec
-> Parser GenotypeFileSpec -> Parser GenotypeFileSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser GenotypeFileSpec
parseVCF
where
parseEigenstrat :: Parser GenotypeFileSpec
parseEigenstrat = String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypeEigenstrat (String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
-> Parser String
-> Parser
(Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Eigenstrat genotype matrix, optionally gzipped" String
"genoFile" [String
".geno", String
".geno.gz"] Parser
(Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
-> Parser (Maybe String)
-> Parser
(String
-> Maybe String -> String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing Parser
(String
-> Maybe String -> String -> Maybe String -> GenotypeFileSpec)
-> Parser String
-> Parser
(Maybe String -> String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Eigenstrat snp positions file, optionally gzipped" String
"snpFile" [String
".snp", String
".snp.gz"] Parser (Maybe String -> String -> Maybe String -> GenotypeFileSpec)
-> Parser (Maybe String)
-> Parser (String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing Parser (String -> Maybe String -> GenotypeFileSpec)
-> Parser String -> Parser (Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Eigenstrat individual file" String
"indFile" [String
".ind"] Parser (Maybe String -> GenotypeFileSpec)
-> Parser (Maybe String) -> Parser GenotypeFileSpec
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing
parsePlink :: Parser GenotypeFileSpec
parsePlink = String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec
GenotypePlink (String
-> Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
-> Parser String
-> Parser
(Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Plink genotype matrix, optionally gzipped" String
"bedFile" [String
".bed", String
".bed.gz"] Parser
(Maybe String
-> String
-> Maybe String
-> String
-> Maybe String
-> GenotypeFileSpec)
-> Parser (Maybe String)
-> Parser
(String
-> Maybe String -> String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing Parser
(String
-> Maybe String -> String -> Maybe String -> GenotypeFileSpec)
-> Parser String
-> Parser
(Maybe String -> String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Plink snp positions file, optionally gzipped" String
"bimFile" [String
".bim", String
".bim.gz"] Parser (Maybe String -> String -> Maybe String -> GenotypeFileSpec)
-> Parser (Maybe String)
-> Parser (String -> Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing Parser (String -> Maybe String -> GenotypeFileSpec)
-> Parser String -> Parser (Maybe String -> GenotypeFileSpec)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"Plink individual file" String
"famFile" [String
".fam"] Parser (Maybe String -> GenotypeFileSpec)
-> Parser (Maybe String) -> Parser GenotypeFileSpec
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing
parseVCF :: Parser GenotypeFileSpec
parseVCF = String -> Maybe String -> GenotypeFileSpec
GenotypeVCF (String -> Maybe String -> GenotypeFileSpec)
-> Parser String -> Parser (Maybe String -> GenotypeFileSpec)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
String -> String -> [String] -> Parser String
parseFileWithEndings String
"VCF (Variant Call Format) file, optionall gzipped" String
"vcfFile" [String
".vcf", String
".vcf.gz"] Parser (Maybe String -> GenotypeFileSpec)
-> Parser (Maybe String) -> Parser GenotypeFileSpec
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*>
Maybe String -> Parser (Maybe String)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
forall a. Maybe a
Nothing
parseFileWithEndings :: String -> String -> [String] -> OP.Parser FilePath
parseFileWithEndings :: String -> String -> [String] -> Parser String
parseFileWithEndings String
help String
long [String]
endings = ReadM String -> Mod OptionFields String -> Parser String
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Maybe String) -> ReadM String
forall a. (String -> Maybe a) -> ReadM a
OP.maybeReader String -> Maybe String
fileEndingReader) (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
long Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help (String
help String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Accepted file endings are " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " [String]
endings) Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE")
where
fileEndingReader :: String -> Maybe FilePath
fileEndingReader :: String -> Maybe String
fileEndingReader String
p =
let (String
_, String
extension) = String -> (String, String)
splitExtensionsOptGz String
p
in if String
extension String -> [String] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
endings then String -> Maybe String
forall a. a -> Maybe a
Just String
p else Maybe String
forall a. Maybe a
Nothing
parseGenotypeSNPSet :: OP.Parser SNPSetSpec
parseGenotypeSNPSet :: Parser SNPSetSpec
parseGenotypeSNPSet = ReadM SNPSetSpec
-> Mod OptionFields SNPSetSpec -> Parser SNPSetSpec
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String SNPSetSpec) -> ReadM SNPSetSpec
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String SNPSetSpec
readSnpSet) (
String -> Mod OptionFields SNPSetSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"snpSet" Mod OptionFields SNPSetSpec
-> Mod OptionFields SNPSetSpec -> Mod OptionFields SNPSetSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields SNPSetSpec
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"SET" Mod OptionFields SNPSetSpec
-> Mod OptionFields SNPSetSpec -> Mod OptionFields SNPSetSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields SNPSetSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The snpSet of the package: 1240K, HumanOrigins or Other. \
\Only relevant for data input with -p|--genoOne or --genoFile + --snpFile + --indFile, \
\because the packages in a -d|--baseDir already have this information in their respective \
\POSEIDON.yml files. (default: Other)" Mod OptionFields SNPSetSpec
-> Mod OptionFields SNPSetSpec -> Mod OptionFields SNPSetSpec
forall a. Semigroup a => a -> a -> a
<>
SNPSetSpec -> Mod OptionFields SNPSetSpec
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value SNPSetSpec
SNPSetOther)
where
readSnpSet :: String -> Either String SNPSetSpec
readSnpSet :: String -> Either String SNPSetSpec
readSnpSet String
s = case String
s of
String
"1240K" -> SNPSetSpec -> Either String SNPSetSpec
forall a b. b -> Either a b
Right SNPSetSpec
SNPSet1240K
String
"HumanOrigins" -> SNPSetSpec -> Either String SNPSetSpec
forall a b. b -> Either a b
Right SNPSetSpec
SNPSetHumanOrigins
String
"Other" -> SNPSetSpec -> Either String SNPSetSpec
forall a b. b -> Either a b
Right SNPSetSpec
SNPSetOther
String
_ -> String -> Either String SNPSetSpec
forall a b. a -> Either a b
Left String
"Could not read snpSet. Must be \"1240K\", \
\\"HumanOrigins\" or \"Other\""
parseOutPackagePath :: OP.Parser FilePath
parseOutPackagePath :: Parser String
parseOutPackagePath = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outPackagePath" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'o' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DIR" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path to the output package directory.")
parseMaybeOutPackagePath :: OP.Parser (Maybe FilePath)
parseMaybeOutPackagePath :: Parser (Maybe String)
parseMaybeOutPackagePath = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
Char -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'o' Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outPackagePath" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DIR" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Path for the converted genotype files to be written to. If a path is provided, only the converted genotype \
\files are written out, with no change of the original package. If no path is provided, \
\genotype files will be converted in-place, including a change in the POSEIDON.yml file to yield an updated valid package" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseMaybeOutPackageName :: OP.Parser (Maybe String)
parseMaybeOutPackageName :: Parser (Maybe String)
parseMaybeOutPackageName = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
Char -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'n' Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outPackageName" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"STRING" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The output package name. This is optional: If no name is provided, \
\then the package name defaults to the basename of the (mandatory) \
\--outPackagePath argument." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseForgeOutMode :: OP.Parser ForgeOutMode
parseForgeOutMode :: Parser ForgeOutMode
parseForgeOutMode =
Parser ForgeOutMode
parseOutOnlyGenoFlag
Parser ForgeOutMode -> Parser ForgeOutMode -> Parser ForgeOutMode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ForgeOutMode
parseMinimalOutputFlag
Parser ForgeOutMode -> Parser ForgeOutMode -> Parser ForgeOutMode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ForgeOutMode
parsePreservePymlFlag
Parser ForgeOutMode -> Parser ForgeOutMode -> Parser ForgeOutMode
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ForgeOutMode -> Parser ForgeOutMode
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ForgeOutMode
NormalOut
parseOutOnlyGenoFlag :: OP.Parser ForgeOutMode
parseOutOnlyGenoFlag :: Parser ForgeOutMode
parseOutOnlyGenoFlag = ForgeOutMode -> Mod FlagFields ForgeOutMode -> Parser ForgeOutMode
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' ForgeOutMode
GenoOut Mod FlagFields ForgeOutMode
forall a. Mod FlagFields a
onlyGenoOutputDocu
onlyGenoOutputDocu :: OP.Mod OP.FlagFields a
onlyGenoOutputDocu :: forall a. Mod FlagFields a
onlyGenoOutputDocu =
String -> Mod FlagFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"onlyGeno" Mod FlagFields a -> Mod FlagFields a -> Mod FlagFields a
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields a
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Should only the resulting genotype data be returned? This means the output will not \
\be a Poseidon package."
parseMinimalOutputFlag :: OP.Parser ForgeOutMode
parseMinimalOutputFlag :: Parser ForgeOutMode
parseMinimalOutputFlag = ForgeOutMode -> Mod FlagFields ForgeOutMode -> Parser ForgeOutMode
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' ForgeOutMode
MinimalOut Mod FlagFields ForgeOutMode
forall a. Mod FlagFields a
minimalOutputDocu
parseMinimalOutputSwitch :: OP.Parser Bool
parseMinimalOutputSwitch :: Parser Bool
parseMinimalOutputSwitch = Mod FlagFields Bool -> Parser Bool
OP.switch Mod FlagFields Bool
forall a. Mod FlagFields a
minimalOutputDocu
minimalOutputDocu :: OP.Mod OP.FlagFields a
minimalOutputDocu :: forall a. Mod FlagFields a
minimalOutputDocu =
String -> Mod FlagFields a
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"minimal" Mod FlagFields a -> Mod FlagFields a -> Mod FlagFields a
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields a
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Should the output Poseidon package be reduced to a necessary minimum?"
parsePreservePymlFlag :: OP.Parser ForgeOutMode
parsePreservePymlFlag :: Parser ForgeOutMode
parsePreservePymlFlag = ForgeOutMode -> Mod FlagFields ForgeOutMode -> Parser ForgeOutMode
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' ForgeOutMode
PreservePymlOut (
String -> Mod FlagFields ForgeOutMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"preservePyml" Mod FlagFields ForgeOutMode
-> Mod FlagFields ForgeOutMode -> Mod FlagFields ForgeOutMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ForgeOutMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Should the output Poseidon package mimic the input package? \
\With this option some fields of the source package's POSEIDON.yml file, \
\its README file and its CHANGELOG file (if available) are copied \
\to the output package. Only works for a singular source package."
)
parsePackageWise :: OP.Parser Bool
parsePackageWise :: Parser Bool
parsePackageWise = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"packagewise" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Skip the within-package selection step in forge. This will result in \
\outputting all individuals in the relevant packages, and hence a superset of the requested \
\individuals/groups. It may result in better performance in cases where one wants to forge \
\entire packages or almost entire packages. Details: Forge conceptually performs two types \
\of selection: First, it identifies which packages in the supplied base directories are \
\relevant to the requested forge, i.e. whether they are either explicitly listed using \
\*PackageName*, or because they contain selected individuals or groups. Second, within each \
\relevant package, individuals which are not requested are removed. This option skips only \
\the second step, but still performs the first.")
parseMaybeSnpFile :: OP.Parser (Maybe FilePath)
parseMaybeSnpFile :: Parser (Maybe String)
parseMaybeSnpFile = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"selectSnps" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"To extract specific SNPs during this forge operation, provide a Snp file. \
\Can be either Eigenstrat (file ending must be '.snp' or '.snp.gz') or Plink (file ending must be '.bim' or '.bim.gz'). \
\When this option is set, the output package will have exactly the SNPs listed in this file. \
\Any SNP not listed in the file will be excluded. If option '--intersect' is also set, only \
\the SNPs overlapping between the SNP file and the forged packages are output." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing)
parseListEntity :: OP.Parser ListEntity
parseListEntity :: Parser ListEntity
parseListEntity = Parser ListEntity
parseListPackages Parser ListEntity -> Parser ListEntity -> Parser ListEntity
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser ListEntity
parseListGroups Parser ListEntity -> Parser ListEntity -> Parser ListEntity
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Parser ()
parseListIndividualsDummy Parser () -> Parser ListEntity -> Parser ListEntity
forall a b. Parser a -> Parser b -> Parser b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Parser ListEntity
parseListIndividualsExtraCols)
where
parseListPackages :: Parser ListEntity
parseListPackages = ListEntity -> Mod FlagFields ListEntity -> Parser ListEntity
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' ListEntity
ListPackages (
String -> Mod FlagFields ListEntity
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"packages" Mod FlagFields ListEntity
-> Mod FlagFields ListEntity -> Mod FlagFields ListEntity
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ListEntity
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List all packages."
)
parseListGroups :: Parser ListEntity
parseListGroups = ListEntity -> Mod FlagFields ListEntity -> Parser ListEntity
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' ListEntity
ListGroups (
String -> Mod FlagFields ListEntity
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"groups" Mod FlagFields ListEntity
-> Mod FlagFields ListEntity -> Mod FlagFields ListEntity
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ListEntity
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List all groups, ignoring any group names after the first as specified in the .janno-file.")
parseListIndividualsDummy :: Parser ()
parseListIndividualsDummy = () -> Mod FlagFields () -> Parser ()
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' () (
String -> Mod FlagFields ()
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"individuals" Mod FlagFields () -> Mod FlagFields () -> Mod FlagFields ()
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields ()
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List all individuals/samples.")
parseListIndividualsExtraCols :: Parser ListEntity
parseListIndividualsExtraCols = AddJannoColSpec -> ListEntity
ListIndividuals (AddJannoColSpec -> ListEntity)
-> Parser AddJannoColSpec -> Parser ListEntity
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Parser AddJannoColSpec
parseAllJannoCols Parser AddJannoColSpec
-> Parser AddJannoColSpec -> Parser AddJannoColSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ([String] -> AddJannoColSpec
AddJannoColList ([String] -> AddJannoColSpec)
-> Parser [String] -> Parser AddJannoColSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.many Parser String
parseExtraCol))
parseAllJannoCols :: Parser AddJannoColSpec
parseAllJannoCols = AddJannoColSpec
-> Mod FlagFields AddJannoColSpec -> Parser AddJannoColSpec
forall a. a -> Mod FlagFields a -> Parser a
OP.flag' AddJannoColSpec
AddJannoColAll (String -> Mod FlagFields AddJannoColSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"fullJanno" Mod FlagFields AddJannoColSpec
-> Mod FlagFields AddJannoColSpec -> Mod FlagFields AddJannoColSpec
forall a. Semigroup a => a -> a -> a
<> String -> Mod FlagFields AddJannoColSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"output all Janno Columns")
parseExtraCol :: Parser String
parseExtraCol = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'j' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"jannoColumn" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"COLNAME" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"List additional fields from the janno files, using the .janno column heading name, such as \
\\"Country\", \"Site\", \"Date_C14_Uncal_BP\", etc..")
parseRawOutput :: OP.Parser Bool
parseRawOutput :: Parser Bool
parseRawOutput = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"raw" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Return the output table as tab-separated values without header. \
\This is useful for piping into grep or awk."
)
parseOnlyLatest :: OP.Parser Bool
parseOnlyLatest :: Parser Bool
parseOnlyLatest = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"onlyLatest" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Consider only the latest versions of packages, or the groups and individuals \
\within the latest versions of packages, respectively."
)
parseIgnoreGeno :: OP.Parser Bool
parseIgnoreGeno :: Parser Bool
parseIgnoreGeno = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ignoreGeno" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Ignore snp and geno file."
)
parseFullGeno :: OP.Parser Bool
parseFullGeno :: Parser Bool
parseFullGeno = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"fullGeno" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Test parsing of all SNPs (by default only the first 100 SNPs are probed)."
)
parseNoExitCode :: OP.Parser Bool
parseNoExitCode :: Parser Bool
parseNoExitCode = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"noExitCode" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Do not produce an explicit exit code."
)
parseIgnoreDuplicates :: OP.Parser Bool
parseIgnoreDuplicates :: Parser Bool
parseIgnoreDuplicates = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ignoreDuplicates" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Do not stop on duplicated individual names in the package collection."
)
parseRemoteURL :: OP.Parser String
parseRemoteURL :: Parser String
parseRemoteURL = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"remoteURL" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"URL" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"URL of the remote Poseidon server." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value String
"https://server.poseidon-adna.org" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseUpgrade :: OP.Parser Bool
parseUpgrade :: Parser Bool
parseUpgrade = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"upgrade" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'u' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Overwrite outdated local package versions."
)
parseInputPlinkPopMode :: OP.Parser PlinkPopNameMode
parseInputPlinkPopMode :: Parser PlinkPopNameMode
parseInputPlinkPopMode = ReadM PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode -> Parser PlinkPopNameMode
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String PlinkPopNameMode)
-> ReadM PlinkPopNameMode
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String PlinkPopNameMode
readPlinkPopName) (
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"inPlinkPopName" Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"MODE" Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Where to read the population/group name from the FAM file in Plink-format. \
\Three options are possible: asFamily (default) | asPhenotype | asBoth." Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
PlinkPopNameMode -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value PlinkPopNameMode
PlinkPopNameAsFamily
)
parseOutputPlinkPopMode :: OP.Parser PlinkPopNameMode
parseOutputPlinkPopMode :: Parser PlinkPopNameMode
parseOutputPlinkPopMode = ReadM PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode -> Parser PlinkPopNameMode
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String PlinkPopNameMode)
-> ReadM PlinkPopNameMode
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String PlinkPopNameMode
readPlinkPopName) (
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outPlinkPopName" Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"MODE" Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Where to write the population/group name into the FAM file in Plink-format. \
\Three options are possible: asFamily (default) | asPhenotype | asBoth. \
\See also --inPlinkPopName." Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
-> Mod OptionFields PlinkPopNameMode
forall a. Semigroup a => a -> a -> a
<>
PlinkPopNameMode -> Mod OptionFields PlinkPopNameMode
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value PlinkPopNameMode
PlinkPopNameAsFamily)
readPlinkPopName :: String -> Either String PlinkPopNameMode
readPlinkPopName :: String -> Either String PlinkPopNameMode
readPlinkPopName String
s = case String
s of
String
"asFamily" -> PlinkPopNameMode -> Either String PlinkPopNameMode
forall a b. b -> Either a b
Right PlinkPopNameMode
PlinkPopNameAsFamily
String
"asPhenotype" -> PlinkPopNameMode -> Either String PlinkPopNameMode
forall a b. b -> Either a b
Right PlinkPopNameMode
PlinkPopNameAsPhenotype
String
"asBoth" -> PlinkPopNameMode -> Either String PlinkPopNameMode
forall a b. b -> Either a b
Right PlinkPopNameMode
PlinkPopNameAsBoth
String
_ -> String -> Either String PlinkPopNameMode
forall a b. a -> Either a b
Left String
"must be asFamily, asPhenotype or asBoth"
parseMaybeZipDir :: OP.Parser (Maybe FilePath)
parseMaybeZipDir :: Parser (Maybe String)
parseMaybeZipDir = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"zipDir" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'z' Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DIR" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A directory to store .zip files in. If not specified, do not generate .zip files." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parsePort :: OP.Parser Int
parsePort :: Parser Int
parsePort = ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ReadM Int
forall a. Read a => ReadM a
OP.auto (
String -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"port" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'p' Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"PORT" Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields Int
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The port on which the server listens." Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Int -> Mod OptionFields Int
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Int
3000 Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields Int
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault)
parseIgnoreChecksums :: OP.Parser Bool
parseIgnoreChecksums :: Parser Bool
parseIgnoreChecksums = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ignoreChecksums" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'c' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Whether to ignore checksums. Useful for speedup in debugging.")
parseMaybeCertFiles :: OP.Parser (Maybe (FilePath, [FilePath], FilePath))
parseMaybeCertFiles :: Parser (Maybe (String, [String], String))
parseMaybeCertFiles = Parser (String, [String], String)
-> Parser (Maybe (String, [String], String))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
OP.optional Parser (String, [String], String)
parseFiles
where
parseFiles :: Parser (String, [String], String)
parseFiles = (,,) (String -> [String] -> String -> (String, [String], String))
-> Parser String
-> Parser ([String] -> String -> (String, [String], String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser String
parseCertFile Parser ([String] -> String -> (String, [String], String))
-> Parser [String] -> Parser (String -> (String, [String], String))
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser [String]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.many Parser String
parseChainFile Parser (String -> (String, [String], String))
-> Parser String -> Parser (String, [String], String)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String
parseKeyFile
parseKeyFile :: OP.Parser FilePath
parseKeyFile :: Parser String
parseKeyFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"keyFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The key file of the TLS Certificate used for HTTPS.")
parseChainFile :: OP.Parser FilePath
parseChainFile :: Parser String
parseChainFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"chainFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The chain file of the TLS Certificate used for HTTPS. Can be given multiple times.")
parseCertFile :: OP.Parser FilePath
parseCertFile :: Parser String
parseCertFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"certFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The cert file of the TLS Certificate used for HTTPS."
)
parseArchiveBasePaths :: OP.Parser [(String, FilePath)]
parseArchiveBasePaths :: Parser [(String, String)]
parseArchiveBasePaths = Parser (String, String) -> Parser [(String, String)]
forall a. Parser a -> Parser [a]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
OP.some Parser (String, String)
parseArchiveBasePath
where
parseArchiveBasePath :: OP.Parser (String, FilePath)
parseArchiveBasePath :: Parser (String, String)
parseArchiveBasePath = ReadM (String, String)
-> Mod OptionFields (String, String) -> Parser (String, String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ((String -> Either String (String, String))
-> ReadM (String, String)
forall a. (String -> Either String a) -> ReadM a
OP.eitherReader String -> Either String (String, String)
parseArchiveNameAndPath) (
String -> Mod OptionFields (String, String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"baseDir" Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields (String, String)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'd' Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (String, String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"DSL" Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
-> Mod OptionFields (String, String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (String, String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A base path, prepended by the corresponding archive name under which \
\packages in this path are being served. Example: arch1=/path/to/basepath. Can \
\be given multiple times. Multiple paths for the same archive are combined internally. \
\The very first named archive is considered to be the default archive on the server.")
parseArchiveNameAndPath :: String -> Either String (String, FilePath)
parseArchiveNameAndPath :: String -> Either String (String, String)
parseArchiveNameAndPath String
str =
let parts :: [String]
parts = String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"=" String
str
in case [String]
parts of
[String
name, String
fp] -> (String, String) -> Either String (String, String)
forall a. a -> Either String a
forall (m :: * -> *) a. Monad m => a -> m a
return (String
name, String
fp)
[String]
_ -> String -> Either String (String, String)
forall a b. a -> Either a b
Left (String -> Either String (String, String))
-> String -> Either String (String, String)
forall a b. (a -> b) -> a -> b
$ String
"could not parse archive and base directory " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
str String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
". Please use format name=path "
parseMaybeArchiveName :: OP.Parser (Maybe String)
parseMaybeArchiveName :: Parser (Maybe String)
parseMaybeArchiveName = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"archive" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"STRING" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The name of the Poseidon package archive that should be queried. \
\If not given, then the query falls back to the default archive of the \
\server selected with --remoteURL. \
\See the archive documentation at https://www.poseidon-adna.org/#/archive_overview \
\for a list of archives currently available from the official Poseidon Web API." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseJannocoalSourceSpec :: OP.Parser JannoSourceSpec
parseJannocoalSourceSpec :: Parser JannoSourceSpec
parseJannocoalSourceSpec = Parser JannoSourceSpec
parseJannocoalSingleSource Parser JannoSourceSpec
-> Parser JannoSourceSpec -> Parser JannoSourceSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ([String] -> JannoSourceSpec
JannoSourceBaseDirs ([String] -> JannoSourceSpec)
-> Parser [String] -> Parser JannoSourceSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser [String]
parseBasePaths)
where
parseJannocoalSingleSource :: Parser JannoSourceSpec
parseJannocoalSingleSource = ReadM JannoSourceSpec
-> Mod OptionFields JannoSourceSpec -> Parser JannoSourceSpec
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> JannoSourceSpec
JannoSourceSingle (String -> JannoSourceSpec)
-> ReadM String -> ReadM JannoSourceSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields JannoSourceSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"sourceFile" Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields JannoSourceSpec
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
's' Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields JannoSourceSpec
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
-> Mod OptionFields JannoSourceSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields JannoSourceSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The source .janno file."
)
parseJannocoalTargetFile :: OP.Parser FilePath
parseJannocoalTargetFile :: Parser String
parseJannocoalTargetFile = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"targetFile" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
't' Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The target .janno file to fill."
)
parseJannocoalOutSpec :: OP.Parser (Maybe FilePath)
parseJannocoalOutSpec :: Parser (Maybe String)
parseJannocoalOutSpec = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"outFile" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'o' Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
OP.metavar String
"FILE" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields (Maybe String)
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"An optional file to write the results to. \
\If not specified, change the target file in place."
)
parseJannocoalJannoColumns :: OP.Parser CoalesceJannoColumnSpec
parseJannocoalJannoColumns :: Parser CoalesceJannoColumnSpec
parseJannocoalJannoColumns = Parser CoalesceJannoColumnSpec
includeJannoColumns Parser CoalesceJannoColumnSpec
-> Parser CoalesceJannoColumnSpec -> Parser CoalesceJannoColumnSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
OP.<|> Parser CoalesceJannoColumnSpec
excludeJannoColumns Parser CoalesceJannoColumnSpec
-> Parser CoalesceJannoColumnSpec -> Parser CoalesceJannoColumnSpec
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
OP.<|> CoalesceJannoColumnSpec -> Parser CoalesceJannoColumnSpec
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure CoalesceJannoColumnSpec
AllJannoColumns
where
includeJannoColumns :: Parser CoalesceJannoColumnSpec
includeJannoColumns = ReadM CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
-> Parser CoalesceJannoColumnSpec
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ([ByteString] -> CoalesceJannoColumnSpec
IncludeJannoColumns ([ByteString] -> CoalesceJannoColumnSpec)
-> (String -> [ByteString]) -> String -> CoalesceJannoColumnSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> ByteString) -> [String] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map String -> ByteString
BSC.pack ([String] -> [ByteString])
-> (String -> [String]) -> String -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"," (String -> CoalesceJannoColumnSpec)
-> ReadM String -> ReadM CoalesceJannoColumnSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields CoalesceJannoColumnSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"includeColumns" Mod OptionFields CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields CoalesceJannoColumnSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A comma-separated list of .janno column names to coalesce. \
\If not specified, all columns that can be found in the source \
\and target will get filled."
)
excludeJannoColumns :: Parser CoalesceJannoColumnSpec
excludeJannoColumns = ReadM CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
-> Parser CoalesceJannoColumnSpec
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option ([ByteString] -> CoalesceJannoColumnSpec
ExcludeJannoColumns ([ByteString] -> CoalesceJannoColumnSpec)
-> (String -> [ByteString]) -> String -> CoalesceJannoColumnSpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> ByteString) -> [String] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map String -> ByteString
BSC.pack ([String] -> [ByteString])
-> (String -> [String]) -> String -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String -> [String]
forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
"," (String -> CoalesceJannoColumnSpec)
-> ReadM String -> ReadM CoalesceJannoColumnSpec
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields CoalesceJannoColumnSpec
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"excludeColumns" Mod OptionFields CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
-> Mod OptionFields CoalesceJannoColumnSpec
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields CoalesceJannoColumnSpec
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"A comma-separated list of .janno column names NOT to coalesce. \
\All columns that can be found in the source and target will get filled, \
\except the ones listed here."
)
parseJannocoalOverride :: OP.Parser Bool
parseJannocoalOverride :: Parser Bool
parseJannocoalOverride = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"force" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'f' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"With this option, potential non-missing content in target columns gets overridden \
\with non-missing content in source columns. By default, only missing data gets filled-in."
)
parseJannocoalSourceKey :: OP.Parser String
parseJannocoalSourceKey :: Parser String
parseJannocoalSourceKey = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"sourceKey" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The .janno column to use as the source key." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value String
"Poseidon_ID" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseJannocoalTargetKey :: OP.Parser String
parseJannocoalTargetKey :: Parser String
parseJannocoalTargetKey = Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
OP.strOption (
String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"targetKey" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"The .janno column to use as the target key." Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields String
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value String
"Poseidon_ID" Mod OptionFields String
-> Mod OptionFields String -> Mod OptionFields String
forall a. Semigroup a => a -> a -> a
<>
Mod OptionFields String
forall a (f :: * -> *). Show a => Mod f a
OP.showDefault
)
parseJannocoalIdStripRegex :: OP.Parser (Maybe String)
parseJannocoalIdStripRegex :: Parser (Maybe String)
parseJannocoalIdStripRegex = ReadM (Maybe String)
-> Mod OptionFields (Maybe String) -> Parser (Maybe String)
forall a. ReadM a -> Mod OptionFields a -> Parser a
OP.option (String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> ReadM String -> ReadM (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ReadM String
forall s. IsString s => ReadM s
OP.str) (
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"stripIdRegex" Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"An optional regular expression to identify parts of the IDs to strip \
\before matching between source and target. Uses POSIX Extended regular expressions." Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
-> Mod OptionFields (Maybe String)
forall a. Semigroup a => a -> a -> a
<>
Maybe String -> Mod OptionFields (Maybe String)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
OP.value Maybe String
forall a. Maybe a
Nothing
)
parseOutputOrdered :: OP.Parser Bool
parseOutputOrdered :: Parser Bool
parseOutputOrdered = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"ordered" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"With this option, the output of forge is ordered according to the entities given."
)
parseZipOut :: OP.Parser Bool
parseZipOut :: Parser Bool
parseZipOut = Mod FlagFields Bool -> Parser Bool
OP.switch (
String -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => String -> Mod f a
OP.long String
"zip" Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
Char -> Mod FlagFields Bool
forall (f :: * -> *) a. HasName f => Char -> Mod f a
OP.short Char
'z' Mod FlagFields Bool -> Mod FlagFields Bool -> Mod FlagFields Bool
forall a. Semigroup a => a -> a -> a
<>
String -> Mod FlagFields Bool
forall (f :: * -> *) a. String -> Mod f a
OP.help String
"Should the resulting genotype- and snp-files be gzipped?"
)