{-# LANGUAGE OverloadedStrings #-}

module Currycarbon.Parsers where

import Currycarbon.Types
import Currycarbon.Utils

import           Control.Exception              (throwIO)
import           Data.List                      (intercalate, transpose)
import qualified Text.Parsec                    as P
import qualified Text.Parsec.String             as P
import qualified Data.Vector.Unboxed            as VU
import qualified Data.Vector                    as V

-- * Parsing, rendering and writing functions
--
-- $importExport
--
-- This module contains a number of functions to manage data input and 
-- output plumbing for different datatypes

-- | Combine 'UncalC14', 'CalPDF' and 'CalC14' to render pretty command line output
-- like this:
-- 
-- @
-- Sample: 1 ~\> [5000±30BP]
-- 1-sigma: 3894-3880BC, 3797-3709BC
-- 2-sigma: 3941-3864BC, 3810-3700BC, 3680-3655BC
--                                     ***                      
--                                    *'''**   *****            
--                   ***             *'''''''***''''''*           
--             ******'''*            ''''''''''''''''      **   
--            *''''''''''**        **''''''''''''''''*   **''*  
--         ***''''''''''''''********'''''''''''''''''''''***''''''**
--  -3960 \<~~~~~~~~~|~~~~~~~~~~~~~~~~|~~~~~~~~~~~~~~~|~~~~~~~~~~\> -3640
-- @
--
renderCalDatesPretty :: [(UncalC14, CalPDF, CalC14)] -> String
renderCalDatesPretty :: [(UncalC14, CalPDF, CalC14)] -> String
renderCalDatesPretty [(UncalC14, CalPDF, CalC14)]
xs =
    String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ ((UncalC14, CalPDF, CalC14) -> String)
-> [(UncalC14, CalPDF, CalC14)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (UncalC14, CalPDF, CalC14) -> String
renderCalDatePretty [(UncalC14, CalPDF, CalC14)]
xs

renderCalDatePretty :: (UncalC14, CalPDF, CalC14) -> String
renderCalDatePretty :: (UncalC14, CalPDF, CalC14) -> String
renderCalDatePretty (UncalC14
uncalC14, CalPDF
calPDF, CalC14
calC14) =
    String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [
          UncalC14 -> String
renderUncalC14 UncalC14
uncalC14
        , CalC14 -> String
renderCalC14 CalC14
calC14
        , Int -> Int -> CalPDF -> String
renderCLIPlotCalPDF Int
5 Int
50 CalPDF
calPDF
        ]

-- CalibrationMethod
readCalibrationMethod :: String -> Either String CalibrationMethod
readCalibrationMethod :: String -> Either String CalibrationMethod
readCalibrationMethod String
s =
    case Parsec String () CalibrationMethod
-> () -> String -> String -> Either ParseError CalibrationMethod
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () CalibrationMethod
parseCalibrationMethod () String
"" String
s of
        Left ParseError
err -> String -> Either String CalibrationMethod
forall a b. a -> Either a b
Left (String -> Either String CalibrationMethod)
-> String -> Either String CalibrationMethod
forall a b. (a -> b) -> a -> b
$ CurrycarbonException -> String
renderCurrycarbonException (CurrycarbonException -> String) -> CurrycarbonException -> String
forall a b. (a -> b) -> a -> b
$ String -> CurrycarbonException
CurrycarbonCLIParsingException (String -> CurrycarbonException) -> String -> CurrycarbonException
forall a b. (a -> b) -> a -> b
$ ParseError -> String
forall a. Show a => a -> String
show ParseError
err
        Right CalibrationMethod
x -> CalibrationMethod -> Either String CalibrationMethod
forall a b. b -> Either a b
Right CalibrationMethod
x

parseCalibrationMethod :: P.Parser CalibrationMethod
parseCalibrationMethod :: Parsec String () CalibrationMethod
parseCalibrationMethod = do
    Parsec String () CalibrationMethod
-> Parsec String () CalibrationMethod
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try Parsec String () CalibrationMethod
forall u. ParsecT String u Identity CalibrationMethod
bchron Parsec String () CalibrationMethod
-> Parsec String () CalibrationMethod
-> Parsec String () CalibrationMethod
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
P.<|> Parsec String () CalibrationMethod
forall u. ParsecT String u Identity CalibrationMethod
matrixMultiplication
    where
        bchron :: ParsecT String u Identity CalibrationMethod
bchron = do
            String
_ <- String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"Bchron,"
            ParsecT String u Identity CalibrationMethod
-> ParsecT String u Identity CalibrationMethod
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try ParsecT String u Identity CalibrationMethod
forall u. ParsecT String u Identity CalibrationMethod
studentT ParsecT String u Identity CalibrationMethod
-> ParsecT String u Identity CalibrationMethod
-> ParsecT String u Identity CalibrationMethod
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
P.<|> ParsecT String u Identity CalibrationMethod
forall u. ParsecT String u Identity CalibrationMethod
normal
        studentT :: ParsecT String u Identity CalibrationMethod
studentT = do
            String
_ <- String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"StudentT,"
            Double
dof <- String -> Double
forall a. Read a => String -> a
read (String -> Double)
-> ParsecT String u Identity String
-> ParsecT String u Identity Double
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
            CalibrationMethod -> ParsecT String u Identity CalibrationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (CalibrationDistribution -> CalibrationMethod
Bchron (CalibrationDistribution -> CalibrationMethod)
-> CalibrationDistribution -> CalibrationMethod
forall a b. (a -> b) -> a -> b
$ Double -> CalibrationDistribution
StudentTDist Double
dof)
        normal :: ParsecT String u Identity CalibrationMethod
normal = do
            String
_ <- String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"Normal"
            CalibrationMethod -> ParsecT String u Identity CalibrationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return (CalibrationDistribution -> CalibrationMethod
Bchron CalibrationDistribution
NormalDist)
        matrixMultiplication :: ParsecT String u Identity CalibrationMethod
matrixMultiplication = do
            String
_ <- String -> ParsecT String u Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"MatrixMult"
            CalibrationMethod -> ParsecT String u Identity CalibrationMethod
forall (m :: * -> *) a. Monad m => a -> m a
return CalibrationMethod
MatrixMultiplication

-- CalC14
-- | Write 'CalC14's to the file system. The output file is a long .csv file with the following structure:
-- 
-- @
-- sample,hdrSigma,hdrStartBCAD,hdrStopBCAD
-- Sample1,1,-3797,-3709
-- Sample1,1,-3894,-3880
-- Sample1,2,-3680,-3655
-- Sample1,2,-3810,-3700
-- Sample1,2,-3941,-3864
-- Sample2,1,-1142,-1130
-- Sample2,1,-1173,-1161
-- Sample2,1,-1293,-1194
-- Sample2,1,-1368,-1356
-- Sample2,2,-1061,-1059
-- Sample2,2,-1323,-1112
-- Sample2,2,-1393,-1334
-- @
-- 
writeCalC14s :: FilePath -> [CalC14] -> IO ()
writeCalC14s :: String -> [CalC14] -> IO ()
writeCalC14s String
path [CalC14]
calC14s = String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ 
    String
"sample,hdrSigma,hdrStartBCAD,hdrStopBCAD\n" 
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ((CalC14 -> String) -> [CalC14] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map CalC14 -> String
renderCalC14ForFile [CalC14]
calC14s)

writeCalC14 :: FilePath -> CalC14 -> IO ()
writeCalC14 :: String -> CalC14 -> IO ()
writeCalC14 String
path CalC14
calC14 = String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ 
    String
"sample,hdrSigma,hdrStartBCAD,hdrStopBCAD\n" 
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ CalC14 -> String
renderCalC14ForFile CalC14
calC14

appendCalC14 :: FilePath -> CalC14 -> IO ()
appendCalC14 :: String -> CalC14 -> IO ()
appendCalC14 String
path CalC14
calC14 =
    String -> String -> IO ()
appendFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ CalC14 -> String
renderCalC14ForFile CalC14
calC14

renderCalC14ForFile :: CalC14 -> String
renderCalC14ForFile :: CalC14 -> String
renderCalC14ForFile (CalC14 String
name [HDR]
hdrs68 [HDR]
hdrs95) =
    String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ 
        ((String, String, (String, String)) -> String)
-> [(String, String, (String, String))] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String, String, (String, String)) -> String
renderRow ([(String, String, (String, String))] -> [String])
-> [(String, String, (String, String))] -> [String]
forall a b. (a -> b) -> a -> b
$
        [String]
-> [String]
-> [(String, String)]
-> [(String, String, (String, String))]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (String -> [String]
forall a. a -> [a]
repeat String
name) (String -> [String]
forall a. a -> [a]
repeat String
"1") ([HDR] -> [(String, String)]
renderHDRsForFile [HDR]
hdrs68) [(String, String, (String, String))]
-> [(String, String, (String, String))]
-> [(String, String, (String, String))]
forall a. [a] -> [a] -> [a]
++
        [String]
-> [String]
-> [(String, String)]
-> [(String, String, (String, String))]
forall a b c. [a] -> [b] -> [c] -> [(a, b, c)]
zip3 (String -> [String]
forall a. a -> [a]
repeat String
name) (String -> [String]
forall a. a -> [a]
repeat String
"2") ([HDR] -> [(String, String)]
renderHDRsForFile [HDR]
hdrs95)
    where
        renderRow :: (String, String, (String, String)) -> String
        renderRow :: (String, String, (String, String)) -> String
renderRow (String
a, String
b, (String
c, String
d)) = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," [String
a,String
b,String
c,String
d]

renderCalC14s :: [CalC14] -> String
renderCalC14s :: [CalC14] -> String
renderCalC14s [CalC14]
xs = 
    String
"Calibrated high density ranges (HDR):\n" 
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" ((CalC14 -> String) -> [CalC14] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map CalC14 -> String
renderCalC14 [CalC14]
xs)

renderCalC14 :: CalC14 -> String
renderCalC14 :: CalC14 -> String
renderCalC14 (CalC14 String
_ [HDR]
hdrs68 [HDR]
hdrs95) =
       String
"1-sigma: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [HDR] -> String
renderHDRs ([HDR] -> [HDR]
forall a. [a] -> [a]
reverse [HDR]
hdrs68) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
    String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"2-sigma: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ [HDR] -> String
renderHDRs ([HDR] -> [HDR]
forall a. [a] -> [a]
reverse [HDR]
hdrs95)

-- HDR
renderHDRsForFile :: [HDR] -> [(String, String)]
renderHDRsForFile :: [HDR] -> [(String, String)]
renderHDRsForFile = (HDR -> (String, String)) -> [HDR] -> [(String, String)]
forall a b. (a -> b) -> [a] -> [b]
map HDR -> (String, String)
renderHDRForFile

renderHDRForFile :: HDR -> (String, String)
renderHDRForFile :: HDR -> (String, String)
renderHDRForFile (HDR Int
start Int
stop) = (Int -> String
forall a. Show a => a -> String
show Int
stop, Int -> String
forall a. Show a => a -> String
show Int
start)

renderHDRs :: [HDR] -> String
renderHDRs :: [HDR] -> String
renderHDRs [HDR]
xs = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
", " ((HDR -> String) -> [HDR] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map HDR -> String
renderHDR [HDR]
xs)

renderHDR :: HDR -> String
renderHDR :: HDR -> String
renderHDR (HDR Int
stop Int
start)
    | Int
start Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
stop Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0  = Int -> String
forall a. Show a => a -> String
show (-Int
start) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show (-Int
stop) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"BC"
    | Int
start Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
&& Int
stop Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0   = Int -> String
forall a. Show a => a -> String
show (-Int
start) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"BC-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
stop String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"AD"
    | Int
start Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
stop Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = Int -> String
forall a. Show a => a -> String
show Int
start String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
stop String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"AD"
    | Bool
otherwise = String -> String
forall a. HasCallStack => String -> a
error (String -> String) -> String -> String
forall a b. (a -> b) -> a -> b
$ String
"This should never happen: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
start String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
show Int
stop

-- CalCurveMatrix
writeCalCurveMatrix :: FilePath -> CalCurveMatrix -> IO ()
writeCalCurveMatrix :: String -> CalCurveMatrix -> IO ()
writeCalCurveMatrix String
path CalCurveMatrix
calCurveMatrix = 
    String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ CalCurveMatrix -> String
renderCalCurveMatrix CalCurveMatrix
calCurveMatrix

renderCalCurveMatrix :: CalCurveMatrix -> String
renderCalCurveMatrix :: CalCurveMatrix -> String
renderCalCurveMatrix (CalCurveMatrix Vector Int
uncals Vector Int
cals Vector (Vector Float)
curveDensities) =
    let header :: String
header = String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ((Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Int -> String
forall a. Show a => a -> String
show ([Int] -> [String]) -> [Int] -> [String]
forall a b. (a -> b) -> a -> b
$ Vector Int -> [Int]
forall a. Unbox a => Vector a -> [a]
VU.toList Vector Int
cals) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"
        body :: [String]
body = (Int -> [Float] -> String) -> [Int] -> [[Float]] -> [String]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Int -> [Float] -> String
forall a a. (Show a, Show a) => a -> [a] -> String
makeRow (Vector Int -> [Int]
forall a. Unbox a => Vector a -> [a]
VU.toList Vector Int
uncals) ([[Float]] -> [[Float]]
forall a. [[a]] -> [[a]]
transpose ([[Float]] -> [[Float]]) -> [[Float]] -> [[Float]]
forall a b. (a -> b) -> a -> b
$ Vector [Float] -> [[Float]]
forall a. Vector a -> [a]
V.toList ((Vector Float -> [Float])
-> Vector (Vector Float) -> Vector [Float]
forall a b. (a -> b) -> Vector a -> Vector b
V.map Vector Float -> [Float]
forall a. Unbox a => Vector a -> [a]
VU.toList Vector (Vector Float)
curveDensities))
    in String
header String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
body
    where 
      makeRow :: a -> [a] -> String
makeRow a
uncal [a]
dens = a -> String
forall a. Show a => a -> String
show a
uncal String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"," ((a -> String) -> [a] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map a -> String
forall a. Show a => a -> String
show [a]
dens)

-- CalPDF
-- | Write 'CalPDF's to the file system. The output file is a long .csv file with the following structure:
-- 
-- @
-- sample,calBCAD,density
-- ...
-- Sample1,-1391,2.8917924e-4
-- Sample1,-1390,3.3285577e-4
-- Sample1,-1389,3.5674628e-4
-- Sample1,-1388,3.750703e-4
-- ...
-- Sample2,-3678,1.8128564e-3
-- Sample2,-3677,1.9512239e-3
-- Sample2,-3676,2.0227064e-3
-- Sample2,-3675,2.095691e-3
-- ...
-- @
-- 
writeCalPDFs :: FilePath -> [CalPDF] -> IO ()
writeCalPDFs :: String -> [CalPDF] -> IO ()
writeCalPDFs String
path [CalPDF]
calPDFs =
    String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
        String
"sample,calBCAD,density\n"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ [CalPDF] -> String
renderCalPDFs [CalPDF]
calPDFs

writeCalPDF :: FilePath -> CalPDF -> IO ()
writeCalPDF :: String -> CalPDF -> IO ()
writeCalPDF String
path CalPDF
calPDF =
    String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
        String
"sample,calBCAD,density\n"
        String -> String -> String
forall a. [a] -> [a] -> [a]
++ CalPDF -> String
renderCalPDF CalPDF
calPDF

appendCalPDF :: FilePath -> CalPDF -> IO ()
appendCalPDF :: String -> CalPDF -> IO ()
appendCalPDF String
path CalPDF
calPDF =
    String -> String -> IO ()
appendFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ CalPDF -> String
renderCalPDF CalPDF
calPDF

renderCalPDFs :: [CalPDF] -> String
renderCalPDFs :: [CalPDF] -> String
renderCalPDFs = (CalPDF -> String) -> [CalPDF] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CalPDF -> String
renderCalPDF

renderCalPDF :: CalPDF -> String
renderCalPDF :: CalPDF -> String
renderCalPDF (CalPDF String
name Vector Int
cals Vector Float
dens) =
    ((Int, Float) -> String) -> [(Int, Float)] -> String
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Int, Float) -> String
forall a a. (Show a, Show a) => (a, a) -> String
makeRow ([(Int, Float)] -> String) -> [(Int, Float)] -> String
forall a b. (a -> b) -> a -> b
$ Vector (Int, Float) -> [(Int, Float)]
forall a. Unbox a => Vector a -> [a]
VU.toList (Vector (Int, Float) -> [(Int, Float)])
-> Vector (Int, Float) -> [(Int, Float)]
forall a b. (a -> b) -> a -> b
$ Vector Int -> Vector Float -> Vector (Int, Float)
forall a b.
(Unbox a, Unbox b) =>
Vector a -> Vector b -> Vector (a, b)
VU.zip Vector Int
cals Vector Float
dens
    where
      makeRow :: (a, a) -> String
makeRow (a
x,a
y) = String -> String
forall a. Show a => a -> String
show String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n"

renderCLIPlotCalPDF :: Int -> Int -> CalPDF -> String
renderCLIPlotCalPDF :: Int -> Int -> CalPDF -> String
renderCLIPlotCalPDF Int
rows Int
cols (CalPDF String
_ Vector Int
cals Vector Float
dens) =
     let binWidth :: Int
binWidth = Int -> Int -> Int
forall a. Integral a => a -> a -> a
quot (Vector Float -> Int
forall a. Unbox a => Vector a -> Int
VU.length Vector Float
dens) Int
cols
        -- last bin will often be shorter, which renders the whole plot 
        -- slightly incorrect for the last column
         binDens :: [Int]
binDens = Float -> Int -> Vector Float -> [Int]
meanBinDens (Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
rows) Int
binWidth Vector Float
dens
         plotRows :: [String]
plotRows = (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char -> String
forall a. Int -> a -> [a]
replicate Int
8 Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++) ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (Int -> String) -> [Int] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (\Int
x -> (Int -> Char) -> [Int] -> String
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Char
getSymbol Int
x) [Int]
binDens) ([Int] -> [String]) -> [Int] -> [String]
forall a b. (a -> b) -> a -> b
$ [Int] -> [Int]
forall a. [a] -> [a]
reverse [Int
0..Int
rows]
         xAxis :: String
xAxis = Int -> Int -> Int -> Int -> String
constructXAxis (Vector Int -> Int
forall a. Unbox a => Vector a -> a
VU.head Vector Int
cals) (Vector Int -> Int
forall a. Unbox a => Vector a -> a
VU.last Vector Int
cals) ([Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Int]
binDens) Int
binWidth
     in String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
plotRows String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
xAxis
     where
        meanBinDens :: Float -> Int -> VU.Vector Float -> [Int]
        meanBinDens :: Float -> Int -> Vector Float -> [Int]
meanBinDens Float
scaling Int
binWidth Vector Float
dens_ =
            let meanDens :: [Float]
meanDens = ([Float] -> Float) -> [[Float]] -> [Float]
forall a b. (a -> b) -> [a] -> [b]
map (\[Float]
x -> [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [Float]
x Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral ([Float] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Float]
x)) ([[Float]] -> [Float]) -> [[Float]] -> [Float]
forall a b. (a -> b) -> a -> b
$ Int -> [Float] -> [[Float]]
forall a. Int -> [a] -> [[a]]
splitEvery Int
binWidth ([Float] -> [[Float]]) -> [Float] -> [[Float]]
forall a b. (a -> b) -> a -> b
$ Vector Float -> [Float]
forall a. Unbox a => Vector a -> [a]
VU.toList Vector Float
dens_
                maxDens :: Float
maxDens = [Float] -> Float
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Float]
meanDens
            in (Float -> Int) -> [Float] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\Float
x -> Float -> Int
forall a b. (RealFrac a, Integral b) => a -> b
round (Float -> Int) -> Float -> Int
forall a b. (a -> b) -> a -> b
$ (Float
x Float -> Float -> Float
forall a. Fractional a => a -> a -> a
/ Float
maxDens) Float -> Float -> Float
forall a. Num a => a -> a -> a
* Float
scaling) [Float]
meanDens
        splitEvery :: Int -> [a] -> [[a]] -- https://stackoverflow.com/a/8681226/3216883
        splitEvery :: Int -> [a] -> [[a]]
splitEvery Int
_ [] = []
        splitEvery Int
n [a]
list = [a]
first [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: Int -> [a] -> [[a]]
forall a. Int -> [a] -> [[a]]
splitEvery Int
n [a]
rest
            where ([a]
first,[a]
rest) = Int -> [a] -> ([a], [a])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
n [a]
list
        padString :: Int -> String -> String
        padString :: Int -> String -> String
padString Int
l String
x = Int -> Char -> String
forall a. Int -> a -> [a]
replicate (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- String -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
x) Char
' ' String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
x
        getSymbol :: Int -> Int -> Char
        getSymbol :: Int -> Int -> Char
getSymbol Int
x Int
y
            | Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
y = Char
'*'
            | Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
y = Char
'\''
            | Bool
otherwise = Char
' '
        constructXAxis :: Int -> Int -> Int -> Int -> String
        constructXAxis :: Int -> Int -> Int -> Int -> String
constructXAxis Int
start Int
stop Int
l Int
binWidth =
            let startS :: String
startS = Int -> String -> String
padString Int
6 (Int -> String
forall a. Show a => a -> String
show (Int -> String) -> Int -> String
forall a b. (a -> b) -> a -> b
$ Int -> Int
roundTo10 Int
start)
                stopS :: String
stopS = Int -> String
forall a. Show a => a -> String
show (Int -> Int
roundTo10 Int
stop)
                tickFreq :: Int
tickFreq = if Int -> Int
forall a. Num a => a -> a
abs (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
stop) Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1500 then Int
100 else Int
1000
                axis :: String
axis = (Int -> Int -> Char) -> [Int] -> [Int] -> String
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int -> Int -> Int -> Int -> Char
axisSymbol Int
binWidth Int
tickFreq) [Int
0 .. (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)] [Int
1 .. Int
l]
            in  String
startS String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" <" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
axis String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
stopS
            where 
                axisSymbol :: Int -> Int -> Int -> Int -> Char
axisSymbol Int
axisL Int
tickFreq Int
a Int
b = if Int -> Int -> Int -> Bool
forall a. Integral a => a -> a -> a -> Bool
hasTick Int
tickFreq (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
axisL Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
a Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Int
start Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
axisL Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
b) then Char
'|' else Char
'~'
                hasTick :: a -> a -> a -> Bool
hasTick a
tickFreq a
a a
b = (a -> Bool) -> [a] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (\a
x -> a -> a -> a
forall a. Integral a => a -> a -> a
rem (a -> a
forall a. Num a => a -> a
abs a
x) a
tickFreq a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0) [a
a..a
b]
        roundTo10 :: Int -> Int
        roundTo10 :: Int -> Int
roundTo10 Int
x = 
            let (Int
dec,Int
rest) = Int -> Int -> (Int, Int)
forall a. Integral a => a -> a -> (a, a)
quotRem (Int -> Int
forall a. Num a => a -> a
abs Int
x) Int
10
                roundedDec :: Int
roundedDec = if Int
rest Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
5 then Int
dec Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
dec
            in Int
roundedDec Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
10 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int -> Int
forall a. Num a => a -> a
signum Int
x

-- UncalC14
renderUncalC14 :: UncalC14 -> String
renderUncalC14 :: UncalC14 -> String
renderUncalC14 (UncalC14 String
name YearBP
bp YearBP
sigma) = String
"Sample: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" ~> [" String -> String -> String
forall a. [a] -> [a] -> [a]
++ YearBP -> String
forall a. Show a => a -> String
show YearBP
bp String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"±" String -> String -> String
forall a. [a] -> [a] -> [a]
++ YearBP -> String
forall a. Show a => a -> String
show YearBP
sigma String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"BP]"

-- | Read uncalibrated radiocarbon dates from a file. The file should feature one radiocarbon date
-- per line in the form "\<sample name\>,\<mean age BP\>,\<one sigma standard deviation\>", where 
-- \<sample name\> is optional. A valid file could look like this:
-- 
-- @
-- Sample1,5000,30
-- 6000,50
-- Sample3,4000,25
-- @
-- 
readUncalC14FromFile :: FilePath -> IO [UncalC14]
readUncalC14FromFile :: String -> IO [UncalC14]
readUncalC14FromFile String
uncalFile = do
    String
s <- String -> IO String
readFile String
uncalFile
    case Parsec String () [UncalC14]
-> () -> String -> String -> Either ParseError [UncalC14]
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () [UncalC14]
uncalC14SepByNewline () String
"" String
s of
        Left ParseError
err -> CurrycarbonException -> IO [UncalC14]
forall e a. Exception e => e -> IO a
throwIO (CurrycarbonException -> IO [UncalC14])
-> CurrycarbonException -> IO [UncalC14]
forall a b. (a -> b) -> a -> b
$ String -> CurrycarbonException
CurrycarbonCLIParsingException (String -> CurrycarbonException) -> String -> CurrycarbonException
forall a b. (a -> b) -> a -> b
$ ParseError -> String
forall a. Show a => a -> String
show ParseError
err
        Right [UncalC14]
x -> [UncalC14] -> IO [UncalC14]
forall (m :: * -> *) a. Monad m => a -> m a
return [UncalC14]
x
    where
        uncalC14SepByNewline :: P.Parser [UncalC14]
        uncalC14SepByNewline :: Parsec String () [UncalC14]
uncalC14SepByNewline = ParsecT String () Identity UncalC14
-> ParsecT String () Identity Char -> Parsec String () [UncalC14]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.endBy ParsecT String () Identity UncalC14
parseUncalC14 (ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.newline ParsecT String () Identity Char
-> ParsecT String () Identity () -> ParsecT String () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces) Parsec String () [UncalC14]
-> ParsecT String () Identity () -> Parsec String () [UncalC14]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT String () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof

readUncalC14 :: String -> Either String [UncalC14]
readUncalC14 :: String -> Either String [UncalC14]
readUncalC14 String
s = 
    case Parsec String () [UncalC14]
-> () -> String -> String -> Either ParseError [UncalC14]
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () [UncalC14]
uncalC14SepBySemicolon () String
"" String
s of
        Left ParseError
err -> String -> Either String [UncalC14]
forall a b. a -> Either a b
Left (String -> Either String [UncalC14])
-> String -> Either String [UncalC14]
forall a b. (a -> b) -> a -> b
$ CurrycarbonException -> String
renderCurrycarbonException (CurrycarbonException -> String) -> CurrycarbonException -> String
forall a b. (a -> b) -> a -> b
$ String -> CurrycarbonException
CurrycarbonCLIParsingException (String -> CurrycarbonException) -> String -> CurrycarbonException
forall a b. (a -> b) -> a -> b
$ ParseError -> String
forall a. Show a => a -> String
show ParseError
err
        Right [UncalC14]
x -> [UncalC14] -> Either String [UncalC14]
forall a b. b -> Either a b
Right [UncalC14]
x
    where 
        uncalC14SepBySemicolon :: P.Parser [UncalC14]
        uncalC14SepBySemicolon :: Parsec String () [UncalC14]
uncalC14SepBySemicolon = ParsecT String () Identity UncalC14
-> ParsecT String () Identity Char -> Parsec String () [UncalC14]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.sepBy ParsecT String () Identity UncalC14
parseUncalC14 (Char -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
P.char Char
';' ParsecT String () Identity Char
-> ParsecT String () Identity () -> ParsecT String () Identity Char
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT String () Identity ()
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m ()
P.spaces) Parsec String () [UncalC14]
-> ParsecT String () Identity () -> Parsec String () [UncalC14]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT String () Identity ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
P.eof

parseUncalC14 :: P.Parser UncalC14
parseUncalC14 :: ParsecT String () Identity UncalC14
parseUncalC14 = do
    ParsecT String () Identity UncalC14
-> ParsecT String () Identity UncalC14
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try ParsecT String () Identity UncalC14
forall u. ParsecT String u Identity UncalC14
long ParsecT String () Identity UncalC14
-> ParsecT String () Identity UncalC14
-> ParsecT String () Identity UncalC14
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
P.<|> ParsecT String () Identity UncalC14
forall u. ParsecT String u Identity UncalC14
short
    where
        long :: ParsecT String u Identity UncalC14
long = do
            String
name <- ParsecT String u Identity Char -> ParsecT String u Identity String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
P.many (String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.noneOf String
",")
            Char
_ <- String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.oneOf String
","
            YearBP
mean <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String u Identity String
-> ParsecT String u Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
            Char
_ <- String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.oneOf String
","
            YearBP
std <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String u Identity String
-> ParsecT String u Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
            UncalC14 -> ParsecT String u Identity UncalC14
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> YearBP -> YearBP -> UncalC14
UncalC14 String
name YearBP
mean YearBP
std)
        short :: ParsecT String u Identity UncalC14
short = do
            YearBP
mean <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String u Identity String
-> ParsecT String u Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
            Char
_ <- String -> ParsecT String u Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.oneOf String
","
            YearBP
std <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String u Identity String
-> ParsecT String u Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String u Identity Char -> ParsecT String u Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String u Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
            UncalC14 -> ParsecT String u Identity UncalC14
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> YearBP -> YearBP -> UncalC14
UncalC14 String
"unknownSampleName" YearBP
mean YearBP
std)

-- CalCurve
writeCalCurve :: FilePath -> CalCurveBCAD -> IO ()
writeCalCurve :: String -> CalCurveBCAD -> IO ()
writeCalCurve String
path CalCurveBCAD
calCurve = 
    String -> String -> IO ()
writeFile String
path (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ CalCurveBCAD -> String
renderCalCurve CalCurveBCAD
calCurve

renderCalCurve :: CalCurveBCAD -> String
renderCalCurve :: CalCurveBCAD -> String
renderCalCurve (CalCurveBCAD Vector Int
cals Vector Int
uncals Vector YearBP
sigmas) =
    let header :: String
header = String
"calBCAD,uncalBCAD,Sigma\n"
        body :: [String]
body = ((Int, Int, YearBP) -> String) -> [(Int, Int, YearBP)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Int, Int, YearBP) -> String
forall a a a. (Show a, Show a, Show a) => (a, a, a) -> String
makeRow ([(Int, Int, YearBP)] -> [String])
-> [(Int, Int, YearBP)] -> [String]
forall a b. (a -> b) -> a -> b
$ Vector (Int, Int, YearBP) -> [(Int, Int, YearBP)]
forall a. Unbox a => Vector a -> [a]
VU.toList (Vector (Int, Int, YearBP) -> [(Int, Int, YearBP)])
-> Vector (Int, Int, YearBP) -> [(Int, Int, YearBP)]
forall a b. (a -> b) -> a -> b
$ Vector Int
-> Vector Int -> Vector YearBP -> Vector (Int, Int, YearBP)
forall a b c.
(Unbox a, Unbox b, Unbox c) =>
Vector a -> Vector b -> Vector c -> Vector (a, b, c)
VU.zip3 Vector Int
cals Vector Int
uncals Vector YearBP
sigmas
    in String
header String -> String -> String
forall a. [a] -> [a] -> [a]
++ String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"\n" [String]
body
    where
      makeRow :: (a, a, a) -> String
makeRow (a
x,a
y,a
z) = a -> String
forall a. Show a => a -> String
show a
x String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
y String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"," String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
z

-- | Read a calibration curve file. The file must adhere to the current version of the 
-- .c14 file format (e.g. [here](http://intcal.org/curves/intcal20.14c)). Look
-- [here](http://intcal.org/blurb.html) for other calibration curves
readCalCurveFromFile :: FilePath -> IO CalCurveBP
readCalCurveFromFile :: String -> IO CalCurveBP
readCalCurveFromFile String
calCurveFile = do
    String
calCurve <- String -> IO String
readFile String
calCurveFile
    CalCurveBP -> IO CalCurveBP
forall (m :: * -> *) a. Monad m => a -> m a
return (CalCurveBP -> IO CalCurveBP) -> CalCurveBP -> IO CalCurveBP
forall a b. (a -> b) -> a -> b
$ String -> CalCurveBP
readCalCurve String
calCurve

readCalCurve :: String -> CalCurveBP
readCalCurve :: String -> CalCurveBP
readCalCurve String
calCurveString = do
    case Parsec String () [(YearBP, YearBP, YearBP)]
-> ()
-> String
-> String
-> Either ParseError [(YearBP, YearBP, YearBP)]
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> String -> s -> Either ParseError a
P.runParser Parsec String () [(YearBP, YearBP, YearBP)]
parseCalCurve () String
"" String
calCurveString of
        Left ParseError
p  -> String -> CalCurveBP
forall a. HasCallStack => String -> a
error (String -> CalCurveBP) -> String -> CalCurveBP
forall a b. (a -> b) -> a -> b
$ String
"This should never happen." String -> String -> String
forall a. [a] -> [a] -> [a]
++ ParseError -> String
forall a. Show a => a -> String
show ParseError
p
        Right [(YearBP, YearBP, YearBP)]
x -> Vector YearBP -> Vector YearBP -> Vector YearBP -> CalCurveBP
CalCurveBP 
            ([YearBP] -> Vector YearBP
forall a. Unbox a => [a] -> Vector a
VU.fromList ([YearBP] -> Vector YearBP) -> [YearBP] -> Vector YearBP
forall a b. (a -> b) -> a -> b
$ ((YearBP, YearBP, YearBP) -> YearBP)
-> [(YearBP, YearBP, YearBP)] -> [YearBP]
forall a b. (a -> b) -> [a] -> [b]
map (\(YearBP
a,YearBP
_,YearBP
_) -> YearBP
a) [(YearBP, YearBP, YearBP)]
x)
            ([YearBP] -> Vector YearBP
forall a. Unbox a => [a] -> Vector a
VU.fromList ([YearBP] -> Vector YearBP) -> [YearBP] -> Vector YearBP
forall a b. (a -> b) -> a -> b
$ ((YearBP, YearBP, YearBP) -> YearBP)
-> [(YearBP, YearBP, YearBP)] -> [YearBP]
forall a b. (a -> b) -> [a] -> [b]
map (\(YearBP
_,YearBP
b,YearBP
_) -> YearBP
b) [(YearBP, YearBP, YearBP)]
x)
            ([YearBP] -> Vector YearBP
forall a. Unbox a => [a] -> Vector a
VU.fromList ([YearBP] -> Vector YearBP) -> [YearBP] -> Vector YearBP
forall a b. (a -> b) -> a -> b
$ ((YearBP, YearBP, YearBP) -> YearBP)
-> [(YearBP, YearBP, YearBP)] -> [YearBP]
forall a b. (a -> b) -> [a] -> [b]
map (\(YearBP
_,YearBP
_,YearBP
c) -> YearBP
c) [(YearBP, YearBP, YearBP)]
x)

parseCalCurve :: P.Parser [(YearBP, YearBP, YearRange)]
parseCalCurve :: Parsec String () [(YearBP, YearBP, YearBP)]
parseCalCurve = do
    ParsecT String () Identity String -> ParsecT String () Identity ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
P.skipMany ParsecT String () Identity String
comments
    ParsecT String () Identity (YearBP, YearBP, YearBP)
-> ParsecT String () Identity String
-> Parsec String () [(YearBP, YearBP, YearBP)]
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.sepEndBy ParsecT String () Identity (YearBP, YearBP, YearBP)
parseCalCurveLine (ParsecT String () Identity Char
-> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.manyTill ParsecT String () Identity Char
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m t
P.anyToken (ParsecT String () Identity Char -> ParsecT String () Identity Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
P.try ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.newline))

parseCalCurveLine :: P.Parser (YearBP, YearBP, YearRange) 
parseCalCurveLine :: ParsecT String () Identity (YearBP, YearBP, YearBP)
parseCalCurveLine = do
  YearBP
calBP <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String () Identity String
-> ParsecT String () Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
  Char
_ <- String -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.oneOf String
","
  YearBP
bp <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String () Identity String
-> ParsecT String () Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
  Char
_ <- String -> ParsecT String () Identity Char
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m Char
P.oneOf String
","
  YearBP
sigma <- String -> YearBP
forall a. Read a => String -> a
read (String -> YearBP)
-> ParsecT String () Identity String
-> ParsecT String () Identity YearBP
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m [a]
P.many1 ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.digit
  (YearBP, YearBP, YearBP)
-> ParsecT String () Identity (YearBP, YearBP, YearBP)
forall (m :: * -> *) a. Monad m => a -> m a
return (YearBP
calBP, YearBP
bp, YearBP
sigma)

comments :: P.Parser String
comments :: ParsecT String () Identity String
comments = do 
    String
_ <- String -> ParsecT String () Identity String
forall s (m :: * -> *) u.
Stream s m Char =>
String -> ParsecT s u m String
P.string String
"#"
    String
_ <- ParsecT String () Identity Char
-> ParsecT String () Identity Char
-> ParsecT String () Identity String
forall s (m :: * -> *) t u a sep.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m sep -> ParsecT s u m [a]
P.manyTill ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.anyChar ParsecT String () Identity Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
P.newline
    String -> ParsecT String () Identity String
forall (m :: * -> *) a. Monad m => a -> m a
return String
""