{-# LANGUAGE DeriveGeneric #-}

-- |
-- Module      :  TLynx.Shuffle.Options
-- Description :  Options for the connect subcommand
-- Copyright   :  (c) Dominik Schrempf 2021
-- License     :  GPL-3.0-or-later
--
-- Maintainer  :  dominik.schrempf@gmail.com
-- Stability   :  unstable
-- Portability :  portable
--
-- Creation date: Thu Sep 19 15:02:21 2019.
module TLynx.Shuffle.Options
  ( ShuffleArguments (..),
    shuffleArguments,
  )
where

import Data.Aeson
import ELynx.Tools.Options
import ELynx.Tools.Reproduction
import GHC.Generics
import Options.Applicative
import TLynx.Parsers

-- | Arguments of shuffle command.
data ShuffleArguments = ShuffleArguments
  { ShuffleArguments -> NewickFormat
nwFormat :: NewickFormat,
    ShuffleArguments -> Int
nReplicates :: Int,
    ShuffleArguments -> FilePath
inFile :: FilePath,
    ShuffleArguments -> SeedOpt
argsSeed :: SeedOpt
  }
  deriving (ShuffleArguments -> ShuffleArguments -> Bool
(ShuffleArguments -> ShuffleArguments -> Bool)
-> (ShuffleArguments -> ShuffleArguments -> Bool)
-> Eq ShuffleArguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ShuffleArguments -> ShuffleArguments -> Bool
$c/= :: ShuffleArguments -> ShuffleArguments -> Bool
== :: ShuffleArguments -> ShuffleArguments -> Bool
$c== :: ShuffleArguments -> ShuffleArguments -> Bool
Eq, Int -> ShuffleArguments -> ShowS
[ShuffleArguments] -> ShowS
ShuffleArguments -> FilePath
(Int -> ShuffleArguments -> ShowS)
-> (ShuffleArguments -> FilePath)
-> ([ShuffleArguments] -> ShowS)
-> Show ShuffleArguments
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
showList :: [ShuffleArguments] -> ShowS
$cshowList :: [ShuffleArguments] -> ShowS
show :: ShuffleArguments -> FilePath
$cshow :: ShuffleArguments -> FilePath
showsPrec :: Int -> ShuffleArguments -> ShowS
$cshowsPrec :: Int -> ShuffleArguments -> ShowS
Show, (forall x. ShuffleArguments -> Rep ShuffleArguments x)
-> (forall x. Rep ShuffleArguments x -> ShuffleArguments)
-> Generic ShuffleArguments
forall x. Rep ShuffleArguments x -> ShuffleArguments
forall x. ShuffleArguments -> Rep ShuffleArguments x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ShuffleArguments x -> ShuffleArguments
$cfrom :: forall x. ShuffleArguments -> Rep ShuffleArguments x
Generic)

instance Reproducible ShuffleArguments where
  inFiles :: ShuffleArguments -> [FilePath]
inFiles = FilePath -> [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (FilePath -> [FilePath])
-> (ShuffleArguments -> FilePath) -> ShuffleArguments -> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShuffleArguments -> FilePath
inFile
  outSuffixes :: ShuffleArguments -> [FilePath]
outSuffixes ShuffleArguments
_ = [FilePath
".tree"]
  getSeed :: ShuffleArguments -> Maybe SeedOpt
getSeed = SeedOpt -> Maybe SeedOpt
forall a. a -> Maybe a
Just (SeedOpt -> Maybe SeedOpt)
-> (ShuffleArguments -> SeedOpt)
-> ShuffleArguments
-> Maybe SeedOpt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShuffleArguments -> SeedOpt
argsSeed
  setSeed :: ShuffleArguments -> SeedOpt -> ShuffleArguments
setSeed ShuffleArguments
a SeedOpt
s = ShuffleArguments
a {argsSeed :: SeedOpt
argsSeed = SeedOpt
s}
  parser :: Parser ShuffleArguments
parser = Parser ShuffleArguments
shuffleArguments
  cmdName :: FilePath
cmdName = FilePath
"shuffle"
  cmdDsc :: [FilePath]
cmdDsc =
    [ FilePath
"Shuffle a phylogenetic tree (keep coalescent times, but shuffle topology and leaves)."
    ]

instance FromJSON ShuffleArguments

instance ToJSON ShuffleArguments

-- | Parse arguments of shuffle command.
shuffleArguments :: Parser ShuffleArguments
shuffleArguments :: Parser ShuffleArguments
shuffleArguments = NewickFormat -> Int -> FilePath -> SeedOpt -> ShuffleArguments
ShuffleArguments (NewickFormat -> Int -> FilePath -> SeedOpt -> ShuffleArguments)
-> Parser NewickFormat
-> Parser (Int -> FilePath -> SeedOpt -> ShuffleArguments)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser NewickFormat
newickFormat Parser (Int -> FilePath -> SeedOpt -> ShuffleArguments)
-> Parser Int -> Parser (FilePath -> SeedOpt -> ShuffleArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Int
n Parser (FilePath -> SeedOpt -> ShuffleArguments)
-> Parser FilePath -> Parser (SeedOpt -> ShuffleArguments)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser FilePath
file Parser (SeedOpt -> ShuffleArguments)
-> Parser SeedOpt -> Parser ShuffleArguments
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser SeedOpt
seedOpt

n :: Parser Int
n :: Parser Int
n =
  ReadM Int -> Mod OptionFields Int -> Parser Int
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Int
forall a. Read a => ReadM a
auto (Mod OptionFields Int -> Parser Int)
-> Mod OptionFields Int -> Parser Int
forall a b. (a -> b) -> a -> b
$
    FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"replicates" 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
short Char
'n' Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"N" 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
value Int
1
      Mod OptionFields Int
-> Mod OptionFields Int -> Mod OptionFields Int
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Int
forall (f :: * -> *) a. FilePath -> Mod f a
help
        FilePath
"Number of trees to generate"

file :: Parser FilePath
file :: Parser FilePath
file =
  Mod ArgumentFields FilePath -> Parser FilePath
forall s. IsString s => Mod ArgumentFields s -> Parser s
strArgument (Mod ArgumentFields FilePath -> Parser FilePath)
-> Mod ArgumentFields FilePath -> Parser FilePath
forall a b. (a -> b) -> a -> b
$ FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"TREE-FILE" Mod ArgumentFields FilePath
-> Mod ArgumentFields FilePath -> Mod ArgumentFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod ArgumentFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"File containing a Newick tree"