{-# LANGUAGE DoAndIfThenElse #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE DeriveGeneric  #-}
{-# OPTIONS_GHC -w #-}
module Uniform.WritePDF
  ( module Uniform.WritePDF
  ) where
import qualified System.Exit as Sys
import qualified System.Process as SysP
import System.IO.Silently (silence)
import UniformBase
writePDF2 :: NoticeLevel -> Path Abs File -> Path Abs File -> Path Abs Dir -> ErrIO ()
writePDF2 :: NoticeLevel
-> Path Abs File -> Path Abs File -> Path Abs Dir -> ErrIO ()
writePDF2 NoticeLevel
debug Path Abs File
fn Path Abs File
fnres Path Abs Dir
refDir = do
    
    
    
    
    
    
    let infn :: FilePath
infn =   forall fp. Filenames1 fp => fp -> FilePath
getNakedFileName forall a b. (a -> b) -> a -> b
$ Path Abs File
fn :: FilePath 
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (NoticeLevel -> Bool
inform NoticeLevel
debug) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => [Text] -> m ()
putIOwords
        [ Text
"writePDF2 1 infn"
        , forall {a}. Show a => a -> Text
showT FilePath
infn
        , Text
"\n\t fnres"
        , forall {a}. Show a => a -> Text
showT Path Abs File
fnres
        , Text
"\n\t refDir (will be current working dir but seem not to work)"
        , forall {a}. Show a => a -> Text
showT Path Abs Dir
refDir
        ]
    let dir1 :: FilePath
dir1 = forall fp. Filenames1 fp => fp -> FilePath
getParentDir Path Abs File
fnres :: FilePath 
    let out1 :: FilePath
out1 = FilePath
"--output-directory=" forall a. Semigroup a => a -> a -> a
<> FilePath
dir1
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (NoticeLevel -> Bool
inform NoticeLevel
debug) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => [Text] -> m ()
putIOwords [Text
"writePDF2 2 out1", forall {a}. Show a => a -> Text
showT FilePath
out1]
    ExitCode
exit_code1 <- Bool -> FilePath -> [FilePath] -> Path Abs Dir -> ErrIO ExitCode
callProcessWithCWD Bool
True 
        FilePath
"lualatex"
        [FilePath
out1, FilePath
"-interaction=nonstopmode",  FilePath
infn]
        Path Abs Dir
refDir
    ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling ExitCode
exit_code1 FilePath
infn Int
1
    ExitCode
exit_code2 <- Bool -> FilePath -> [FilePath] -> Path Abs Dir -> ErrIO ExitCode
callProcessWithCWD Bool
True 
        FilePath
"biber"
        [ FilePath
infn]
        Path Abs Dir
refDir
    ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling ExitCode
exit_code2 FilePath
infn Int
2
    ExitCode
exit_code3 <- Bool -> FilePath -> [FilePath] -> Path Abs Dir -> ErrIO ExitCode
callProcessWithCWD Bool
True 
        FilePath
"makeindex"
        [FilePath
"-q", FilePath
infn]
        Path Abs Dir
refDir
    ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling ExitCode
exit_code3 FilePath
infn Int
3
    ExitCode
exit_code3 <- Bool -> FilePath -> [FilePath] -> Path Abs Dir -> ErrIO ExitCode
callProcessWithCWD Bool
True 
        FilePath
"lualatex"
        [FilePath
out1, FilePath
"-interaction=nonstopmode",  FilePath
infn]
        Path Abs Dir
refDir
    ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling ExitCode
exit_code3 FilePath
infn Int
4
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (NoticeLevel -> Bool
inform NoticeLevel
debug) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => [Text] -> m ()
putIOwords [Text
"writePDF2 end for", forall {a}. Show a => a -> Text
showT FilePath
out1]
exitHandling :: Sys.ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling :: ExitCode -> FilePath -> Int -> ErrIO ()
exitHandling ExitCode
exit_code FilePath
filename Int
step = do
    
    case ExitCode
exit_code of
        ExitCode
Sys.ExitSuccess -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Sys.ExitFailure Int
r -> do 
                forall (m :: * -> *). MonadIO m => [Text] -> m ()
putIOwords [Text
"callProcessWithCWD - failed - check for 1 log, for 2 blg " 
                            , Text
"show exit code", forall {a}. Show a => a -> Text
showT Int
r, Text
"step", forall {a}. Show a => a -> Text
showT Int
step
                            
                            
                            
                            ]
                
                forall (m :: * -> *) a. Monad m => a -> m a
return ()  
    forall (m :: * -> *) a. Monad m => a -> m a
return ()
callProcessWithCWD :: Bool ->  FilePath -> [String] -> Path Abs Dir -> ErrIO Sys.ExitCode
callProcessWithCWD :: Bool -> FilePath -> [FilePath] -> Path Abs Dir -> ErrIO ExitCode
callProcessWithCWD Bool
silenced FilePath
cmd [FilePath]
args Path Abs Dir
cwd1 = forall a. IO a -> ErrIO a
callIO 
        forall b c a. (b -> c) -> (a -> b) -> a -> c
. (if Bool
silenced then (forall a. IO a -> IO a
silence) else (forall a. a -> a
id)) forall a b. (a -> b) -> a -> b
$ do 
    ExitCode
exit_code <-
        forall a.
CreateProcess
-> (Maybe Handle
    -> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a)
-> IO a
SysP.withCreateProcess 
            (FilePath -> [FilePath] -> CreateProcess
SysP.proc FilePath
cmd   [FilePath]
args)
                { delegate_ctlc :: Bool
SysP.delegate_ctlc = Bool
True
                , cwd :: Maybe FilePath
SysP.cwd = forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b t. Path b t -> FilePath
toFilePath forall a b. (a -> b) -> a -> b
$ Path Abs Dir
cwd1
                }
            forall a b. (a -> b) -> a -> b
$ \Maybe Handle
_ Maybe Handle
_ Maybe Handle
_ ProcessHandle
p ->
                ProcessHandle -> IO ExitCode
SysP.waitForProcess ProcessHandle
p
    forall (m :: * -> *) a. Monad m => a -> m a
return ExitCode
exit_code