module TPDB.Input.File where

import TPDB.Data
import TPDB.Convert

import qualified TPDB.Input.Memory as TIM

import qualified Data.Text.Lazy as T
import qualified Data.Text.Lazy.IO as T
import System.FilePath.Posix ( takeExtension )

-- | read input from file with given name.
-- can have extension .srs, .trs, .xml.
-- unknown extension is considered as .xml, because of 
-- http://starexec.forumotion.com/t60-restore-file-extension-for-renamed-benchmarks

get :: FilePath 
         -> IO ( Either (TRS Identifier Identifier) 
                        ( SRS Identifier ) )
get :: FilePath
-> IO (Either (TRS Identifier Identifier) (SRS Identifier))
get FilePath
f = do
    Either
  FilePath (Either (TRS Identifier Identifier) (SRS Identifier))
m <- FilePath
-> IO
     (Either
        FilePath (Either (TRS Identifier Identifier) (SRS Identifier)))
getE FilePath
f
    case Either
  FilePath (Either (TRS Identifier Identifier) (SRS Identifier))
m of
        Right Either (TRS Identifier Identifier) (SRS Identifier)
x -> Either (TRS Identifier Identifier) (SRS Identifier)
-> IO (Either (TRS Identifier Identifier) (SRS Identifier))
forall (m :: * -> *) a. Monad m => a -> m a
return Either (TRS Identifier Identifier) (SRS Identifier)
x 
        Left FilePath
err -> FilePath
-> IO (Either (TRS Identifier Identifier) (SRS Identifier))
forall a. HasCallStack => FilePath -> a
error FilePath
err

getE :: FilePath
-> IO
     (Either
        FilePath (Either (TRS Identifier Identifier) (SRS Identifier)))
getE FilePath
f = do
  Text
s <- FilePath -> IO Text
T.readFile FilePath
f
  FilePath
-> Text
-> IO
     (Either
        FilePath (Either (TRS Identifier Identifier) (SRS Identifier)))
TIM.get FilePath
f Text
s

get_trs :: FilePath -> IO (TRS Identifier Identifier)
get_trs FilePath
f = do
    Either (TRS Identifier Identifier) (SRS Identifier)
x <- FilePath
-> IO (Either (TRS Identifier Identifier) (SRS Identifier))
get FilePath
f
    TRS Identifier Identifier -> IO (TRS Identifier Identifier)
forall (m :: * -> *) a. Monad m => a -> m a
return (TRS Identifier Identifier -> IO (TRS Identifier Identifier))
-> TRS Identifier Identifier -> IO (TRS Identifier Identifier)
forall a b. (a -> b) -> a -> b
$ case Either (TRS Identifier Identifier) (SRS Identifier)
x of
        Right SRS Identifier
x -> SRS Identifier -> TRS Identifier Identifier
srs2trs SRS Identifier
x
        Left  TRS Identifier Identifier
x -> TRS Identifier Identifier
x

getE_trs :: FilePath -> IO (Either FilePath (TRS Identifier Identifier))
getE_trs FilePath
f = do
    Either
  FilePath (Either (TRS Identifier Identifier) (SRS Identifier))
e <- FilePath
-> IO
     (Either
        FilePath (Either (TRS Identifier Identifier) (SRS Identifier)))
getE FilePath
f
    Either FilePath (TRS Identifier Identifier)
-> IO (Either FilePath (TRS Identifier Identifier))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either FilePath (TRS Identifier Identifier)
 -> IO (Either FilePath (TRS Identifier Identifier)))
-> Either FilePath (TRS Identifier Identifier)
-> IO (Either FilePath (TRS Identifier Identifier))
forall a b. (a -> b) -> a -> b
$ case Either
  FilePath (Either (TRS Identifier Identifier) (SRS Identifier))
e of
        Right Either (TRS Identifier Identifier) (SRS Identifier)
x -> TRS Identifier Identifier
-> Either FilePath (TRS Identifier Identifier)
forall a b. b -> Either a b
Right (TRS Identifier Identifier
 -> Either FilePath (TRS Identifier Identifier))
-> TRS Identifier Identifier
-> Either FilePath (TRS Identifier Identifier)
forall a b. (a -> b) -> a -> b
$ case Either (TRS Identifier Identifier) (SRS Identifier)
x of
            Right SRS Identifier
x -> SRS Identifier -> TRS Identifier Identifier
srs2trs SRS Identifier
x
            Left  TRS Identifier Identifier
x -> TRS Identifier Identifier
x
        Left FilePath
e -> FilePath -> Either FilePath (TRS Identifier Identifier)
forall a b. a -> Either a b
Left FilePath
e

get_srs :: FilePath -> IO (SRS Identifier)
get_srs FilePath
f = do
    Either (TRS Identifier Identifier) (SRS Identifier)
x <- FilePath
-> IO (Either (TRS Identifier Identifier) (SRS Identifier))
get FilePath
f
    SRS Identifier -> IO (SRS Identifier)
forall (m :: * -> *) a. Monad m => a -> m a
return (SRS Identifier -> IO (SRS Identifier))
-> SRS Identifier -> IO (SRS Identifier)
forall a b. (a -> b) -> a -> b
$ case Either (TRS Identifier Identifier) (SRS Identifier)
x of
        Right SRS Identifier
x -> SRS Identifier
x
        Left  TRS Identifier Identifier
x -> case TRS Identifier Identifier -> Maybe (SRS Identifier)
forall v s. Eq v => TRS v s -> Maybe (SRS s)
trs2srs TRS Identifier Identifier
x of
            Maybe (SRS Identifier)
Nothing -> FilePath -> SRS Identifier
forall a. HasCallStack => FilePath -> a
error FilePath
"not an SRS"
            Just SRS Identifier
x -> SRS Identifier
x