{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

-- |
-- Module      :  SLynx.Tools
-- Description :  Common tools for sequence lynx
-- Copyright   :  (c) Dominik Schrempf 2020
-- License     :  GPL-3.0-or-later
--
-- Maintainer  :  dominik.schrempf@gmail.com
-- Stability   :  unstable
-- Portability :  portable
--
-- Creation date: Sat Sep  7 06:24:22 2019.
module SLynx.Tools
  ( -- * SLynx.Tools
    readSeqs,

    -- * Options
    alphabetOpt,
  )
where

import Control.Monad.IO.Class
import Control.Monad.Logger
import qualified Data.Text as T
import ELynx.Data.Alphabet.Alphabet
import ELynx.Data.Sequence.Sequence
import ELynx.Import.Sequence.Fasta
import ELynx.Tools
import Options.Applicative

-- -- | Read sequences of given alphabet from file or standard input.
-- readSeqs
--   :: (MonadIO m, MonadLogger m) => Alphabet -> Maybe FilePath -> m [Sequence]
-- readSeqs a mfp = do
--   case mfp of
--     Nothing ->
--       $(logInfo)
--         $  T.pack
--         $  "Read sequences from standard input; alphabet "
--         <> show a
--         <> "."
--     Just fp ->
--       $(logInfo)
--         $  T.pack
--         $  "Read sequences from file "
--         <> fp
--         <> "; alphabet "
--         <> show a
--         <> "."
--   liftIO $ parseFileOrIOWith (fasta a) mfp

-- | Read sequences of given alphabet from file or standard input.
readSeqs :: (MonadIO m, MonadLogger m) => Alphabet -> FilePath -> m [Sequence]
readSeqs :: Alphabet -> FilePath -> m [Sequence]
readSeqs Alphabet
a FilePath
fp = do
  $(Int
FilePath
LogLevel
FilePath -> Text
FilePath -> FilePath -> FilePath -> CharPos -> CharPos -> Loc
Text -> Text
Loc -> Text -> LogLevel -> Text -> m ()
(Text -> m ()) -> (Text -> Text) -> Text -> m ()
forall a. a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
pack :: FilePath -> Text
monadLoggerLog :: forall (m :: * -> *) msg.
(MonadLogger m, ToLogStr msg) =>
Loc -> Text -> LogLevel -> msg -> m ()
id :: forall a. a -> a
. :: forall b c a. (b -> c) -> (a -> b) -> a -> c
logInfo) (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$
    FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$
      FilePath
"Read sequences from file "
        FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
fp
        FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"; alphabet "
        FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> Alphabet -> FilePath
forall a. Show a => a -> FilePath
show Alphabet
a
        FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath
"."
  IO [Sequence] -> m [Sequence]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Sequence] -> m [Sequence]) -> IO [Sequence] -> m [Sequence]
forall a b. (a -> b) -> a -> b
$ Parser [Sequence] -> FilePath -> IO [Sequence]
forall a. Parser a -> FilePath -> IO a
parseFileWith (Alphabet -> Parser [Sequence]
fasta Alphabet
a) FilePath
fp

-- | Command line option to specify the alphabet. Used by various commands.
alphabetOpt :: Parser Alphabet
alphabetOpt :: Parser Alphabet
alphabetOpt =
  ReadM Alphabet -> Mod OptionFields Alphabet -> Parser Alphabet
forall a. ReadM a -> Mod OptionFields a -> Parser a
option ReadM Alphabet
forall a. Read a => ReadM a
auto (Mod OptionFields Alphabet -> Parser Alphabet)
-> Mod OptionFields Alphabet -> Parser Alphabet
forall a b. (a -> b) -> a -> b
$
    FilePath -> Mod OptionFields Alphabet
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"alphabet" Mod OptionFields Alphabet
-> Mod OptionFields Alphabet -> Mod OptionFields Alphabet
forall a. Semigroup a => a -> a -> a
<> Char -> Mod OptionFields Alphabet
forall (f :: * -> *) a. HasName f => Char -> Mod f a
short Char
'a' Mod OptionFields Alphabet
-> Mod OptionFields Alphabet -> Mod OptionFields Alphabet
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Alphabet
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"NAME"
      Mod OptionFields Alphabet
-> Mod OptionFields Alphabet -> Mod OptionFields Alphabet
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields Alphabet
forall (f :: * -> *) a. FilePath -> Mod f a
help
        FilePath
"Specify alphabet type NAME"