{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}

{-|
Description : Example showing how to remove all comments from an ABIF file
Copyright   : (c) HyraxBio, 2018
License     : BSD3
Maintainer  : andre@hyraxbio.co.za, andre@andrevdm.com

Example showing how to remove all comments from an ABIF file.
See other examples in "Examples"
-}
module Examples.RemoveComments where

import           Protolude

import qualified Hyrax.Abif as H
import qualified Hyrax.Abif.Read as H
import qualified Hyrax.Abif.Write as H

-- | Remove all comments from an existing file
removeComments :: IO ()
removeComments :: IO ()
removeComments = do
  Either Text Abif
abif' <- FilePath -> IO (Either Text Abif)
H.readAbif FilePath
"example.ab1"

  case Either Text Abif
abif' of
    Left Text
e -> Text -> IO ()
forall a (m :: * -> *). (Print a, MonadIO m) => a -> m ()
putStrLn (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"error reading ABIF: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
e
    Right Abif
abif -> do
      let modified :: Abif
modified = Abif
abif { aDirs :: [Directory]
H.aDirs = (Directory -> Bool) -> [Directory] -> [Directory]
forall a. (a -> Bool) -> [a] -> [a]
filter Directory -> Bool
noComments ([Directory] -> [Directory]) -> [Directory] -> [Directory]
forall a b. (a -> b) -> a -> b
$ Abif -> [Directory]
H.aDirs Abif
abif }
      FilePath -> Abif -> IO ()
H.writeAbif FilePath
"example.modified.ab1" Abif
modified

  where
    noComments :: H.Directory -> Bool
    noComments :: Directory -> Bool
noComments Directory
dir = Directory -> Text
H.dTagName Directory
dir Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"CMNT"