{-# LANGUAGE OverloadedStrings #-} import Currycarbon.CLI.RunCalibrate (runCalibrate, CalibrateOptions (..)) import Currycarbon.Parsers import Currycarbon.Types import Currycarbon.Utils import Paths_currycarbon (version) import Control.Exception (catch) import Data.Version (showVersion) import qualified Options.Applicative as OP import System.Exit (exitFailure) import System.IO (hPutStrLn, stderr) -- * CLI interface configuration -- -- $cliInterface -- -- This module contains the necessary code to configure the currycarbon CLI interface -- data types data Options = CmdCalibrate CalibrateOptions -- CLI interface configuration main :: IO () main = do cmdOpts <- OP.customExecParser p optParserInfo catch (runCmd cmdOpts) handler where p = OP.prefs OP.showHelpOnEmpty handler :: CurrycarbonException -> IO () handler e = do hPutStrLn stderr $ renderCurrycarbonException e exitFailure runCmd :: Options -> IO () runCmd o = case o of CmdCalibrate opts -> runCalibrate opts optParserInfo :: OP.ParserInfo Options optParserInfo = OP.info (OP.helper <*> versionOption <*> optParser) ( OP.briefDesc <> OP.progDesc "Intercept calibration of radiocarbon dates" ) versionOption :: OP.Parser (a -> a) versionOption = OP.infoOption (showVersion version) (OP.long "version" <> OP.help "Show version") optParser :: OP.Parser Options optParser = CmdCalibrate <$> calibrateOptParser calibrateOptParser :: OP.Parser CalibrateOptions calibrateOptParser = CalibrateOptions <$> optParseUncalC14String <*> optParseUncalC14FromFile <*> optParseCalCurveFromFile <*> optParseCalibrationMethod <*> optParseAllowOutside <*> optParseDontInterpolateCalCurve <*> optParseQuiet <*> optParseDensityFile <*> optParseHDRFile <*> optParseCalCurveSegmentFile <*> optParseCalCurveMatrixFile -- ** Input parsing functions -- -- $inputParsing -- -- These functions define and handle the CLI input arguments optParseUncalC14String :: OP.Parser [UncalC14] optParseUncalC14String = concat <$> OP.many (OP.argument (OP.eitherReader readUncalC14) ( OP.metavar "DATES" <> OP.help "A string with one or multiple uncalibrated dates of \ \the form \",,;...\" \ \where is optional. \ \So for example \"S1,4000,50;3000,25;S3,1000,20\"." )) optParseUncalC14FromFile :: OP.Parser [FilePath] optParseUncalC14FromFile = OP.many (OP.strOption ( OP.long "inputFile" <> OP.short 'i' <> OP.help "A file with a list of uncalibrated dates. \ \Formated just as DATES, but with a new line for each input date. \ \DATES and --inputFile can be combined and you can provide multiple instances of --inputFile" )) optParseCalCurveFromFile :: OP.Parser (Maybe FilePath) optParseCalCurveFromFile = OP.option (Just <$> OP.str) ( OP.long "calibrationCurveFile" <> OP.help "Path to an calibration curve file in .14c format. \ \The calibration curve will be read and used for calibration. \ \If no file is provided, currycarbon will use the intcal20 curve." <> OP.value Nothing ) optParseCalibrationMethod :: OP.Parser CalibrationMethod optParseCalibrationMethod = OP.option (OP.eitherReader readCalibrationMethod) ( OP.long "method" <> OP.help "The calibration algorithm that should be used: \ \\",,\". \ \The default setting is equivalent to \"Bchron,StudentT,100\" \ \which copies the algorithm implemented in the Bchron R package. \ \Alternatively we implemented \"MatrixMult\", which comes without further arguments. \ \For the Bchron algorithm with a normal distribution (\"Bchron,Normal\") \ \the degrees of freedom argument is not relevant" <> OP.value (Bchron $ StudentTDist 100) ) optParseAllowOutside :: OP.Parser (Bool) optParseAllowOutside = OP.switch ( OP.long "allowOutside" <> OP.help "Allow calibrations to run outside the range of the calibration curve" ) optParseDontInterpolateCalCurve :: OP.Parser (Bool) optParseDontInterpolateCalCurve = OP.switch ( OP.long "noInterpolation" <> OP.help "Don't interpolate the calibration curve" ) optParseQuiet :: OP.Parser (Bool) optParseQuiet = OP.switch ( OP.long "quiet" <> OP.short 'q' <> OP.help "Suppress the printing of calibration results to the command line" ) optParseDensityFile :: OP.Parser (Maybe FilePath) optParseDensityFile = OP.option (Just <$> OP.str) ( OP.long "densityFile" <> OP.help "Path to an output file which stores output densities per sample and calender year" <> OP.value Nothing ) optParseHDRFile :: OP.Parser (Maybe FilePath) optParseHDRFile = OP.option (Just <$> OP.str) ( OP.long "hdrFile" <> OP.help "Path to an output file which stores the high probability density regions for each \ \sample" <> OP.value Nothing ) optParseCalCurveSegmentFile :: OP.Parser (Maybe FilePath) optParseCalCurveSegmentFile = OP.option (Just <$> OP.str) ( OP.long "calCurveSegmentFile" <> OP.help "Path to an output file which stores the relevant, interpolated calibration curve \ \segment for the first (!) input date in a long format. \ \This option as well as --calCurveMatrixFile are mostly meant for debugging" <> OP.value Nothing ) optParseCalCurveMatrixFile :: OP.Parser (Maybe FilePath) optParseCalCurveMatrixFile = OP.option (Just <$> OP.str) ( OP.long "calCurveMatrixFile" <> OP.help "Path to an output file which stores the relevant, interpolated calibration curve \ \segment for the first (!) input date in a wide matrix format" <> OP.value Nothing )