{-# LANGUAGE StrictData #-}

module Currycarbon.Types where

import qualified Data.Vector.Unboxed as VU
import qualified Data.Vector as V

-- * Data types
--
-- $dataTypes
--
-- This module defines the relevant data types for handling radiocarbon dates

-- | Different calibration algorithms implemented in currycarbon. Currently two distinct 
-- implementations are available, although both of them are similar [Intercept calibration](https://en.wikipedia.org/wiki/Radiocarbon_calibration#Intercept)
-- algorithms. Maybe more algorithms will be added in the future
data CalibrationMethod =
  -- | A matrix multiplication method generally following [this blog post by Martin Hinz](https://www.martinhinz.info/jekyll/update/blog/2016/06/03/simple_calibration.html).
  -- This method is slower and the underlying code more verbose than 'Bchron', but it 
  -- has some advantages regarding didactics and the inspection of intermediate data
  -- products for debugging.
  -- Using this method is thus generally not advisable, except for specific applications,
  -- where a more technical insight into C14 calibration is needed
    MatrixMultiplication
  -- | A fast and reliable calibration algorithm very similar to the implementation in the 
  -- [R package Bchron by Andrew Parnell](https://github.com/andrewcparnell/Bchron/blob/master/R/BchronCalibrate.R).
  -- This algorithm can be run with a simple normal distribution ('NormalDist') or
  -- Student's t-distribution ('StudentTDist'), which is recommended
  | Bchron { CalibrationMethod -> CalibrationDistribution
distribution :: CalibrationDistribution }
  deriving (Int -> CalibrationMethod -> ShowS
[CalibrationMethod] -> ShowS
CalibrationMethod -> String
(Int -> CalibrationMethod -> ShowS)
-> (CalibrationMethod -> String)
-> ([CalibrationMethod] -> ShowS)
-> Show CalibrationMethod
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalibrationMethod] -> ShowS
$cshowList :: [CalibrationMethod] -> ShowS
show :: CalibrationMethod -> String
$cshow :: CalibrationMethod -> String
showsPrec :: Int -> CalibrationMethod -> ShowS
$cshowsPrec :: Int -> CalibrationMethod -> ShowS
Show, CalibrationMethod -> CalibrationMethod -> Bool
(CalibrationMethod -> CalibrationMethod -> Bool)
-> (CalibrationMethod -> CalibrationMethod -> Bool)
-> Eq CalibrationMethod
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalibrationMethod -> CalibrationMethod -> Bool
$c/= :: CalibrationMethod -> CalibrationMethod -> Bool
== :: CalibrationMethod -> CalibrationMethod -> Bool
$c== :: CalibrationMethod -> CalibrationMethod -> Bool
Eq)

-- | Statistical distributions to be used with the 'CalibrationMethod' 'Bchron'
data CalibrationDistribution = 
  -- | Normal distribution
    NormalDist
  -- | Student's t-distribution.
  | StudentTDist {
      CalibrationDistribution -> Double
ndf :: Double -- ^ number of degrees of freedom 
    }
  deriving (Int -> CalibrationDistribution -> ShowS
[CalibrationDistribution] -> ShowS
CalibrationDistribution -> String
(Int -> CalibrationDistribution -> ShowS)
-> (CalibrationDistribution -> String)
-> ([CalibrationDistribution] -> ShowS)
-> Show CalibrationDistribution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalibrationDistribution] -> ShowS
$cshowList :: [CalibrationDistribution] -> ShowS
show :: CalibrationDistribution -> String
$cshow :: CalibrationDistribution -> String
showsPrec :: Int -> CalibrationDistribution -> ShowS
$cshowsPrec :: Int -> CalibrationDistribution -> ShowS
Show, CalibrationDistribution -> CalibrationDistribution -> Bool
(CalibrationDistribution -> CalibrationDistribution -> Bool)
-> (CalibrationDistribution -> CalibrationDistribution -> Bool)
-> Eq CalibrationDistribution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalibrationDistribution -> CalibrationDistribution -> Bool
$c/= :: CalibrationDistribution -> CalibrationDistribution -> Bool
== :: CalibrationDistribution -> CalibrationDistribution -> Bool
$c== :: CalibrationDistribution -> CalibrationDistribution -> Bool
Eq)

-- | A type to represent years BP. All numbers are positive and describe the distance in years
-- to 1950AD: 3000 = 3000BP = 1050BC
type YearBP = Word
-- | A type to represent years BC or AD. Negative values describe years BC, positive values
-- years AD: -5000 = 5000BC and 1300 = 1300AD
type YearBCAD = Int
-- | A type to represent a range of years
type YearRange = Word

-- | A data type to represent an uncalibrated radiocarbon date
data UncalC14 = UncalC14 { 
    -- | Sample identifier, e.g. a lab number  
      UncalC14 -> String
_uncalC14Id :: String
    -- | C14 age in years BP
    , UncalC14 -> YearBP
_uncalC14UnCal :: YearBP
    -- | C14 standard deviation (one sigma in years)
    , UncalC14 -> YearBP
_uncalC14Sigma :: YearRange
    } deriving (Int -> UncalC14 -> ShowS
[UncalC14] -> ShowS
UncalC14 -> String
(Int -> UncalC14 -> ShowS)
-> (UncalC14 -> String) -> ([UncalC14] -> ShowS) -> Show UncalC14
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UncalC14] -> ShowS
$cshowList :: [UncalC14] -> ShowS
show :: UncalC14 -> String
$cshow :: UncalC14 -> String
showsPrec :: Int -> UncalC14 -> ShowS
$cshowsPrec :: Int -> UncalC14 -> ShowS
Show, UncalC14 -> UncalC14 -> Bool
(UncalC14 -> UncalC14 -> Bool)
-> (UncalC14 -> UncalC14 -> Bool) -> Eq UncalC14
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UncalC14 -> UncalC14 -> Bool
$c/= :: UncalC14 -> UncalC14 -> Bool
== :: UncalC14 -> UncalC14 -> Bool
$c== :: UncalC14 -> UncalC14 -> Bool
Eq)

-- | A data type to represent a year-wise probability density for uncalibrated dates
-- Although technically not correct, we still call this a probability density function (PDF)
data UncalPDF = UncalPDF {
    -- | Sample identifier, e.g. a lab number
      UncalPDF -> String
_uncalPDFid :: String
    -- | Years BP
    , UncalPDF -> Vector YearBP
_uncalPDFUnCals :: VU.Vector YearBP
    -- | Probability densities
    , UncalPDF -> Vector Float
_uncalPDFDens :: VU.Vector Float
    } deriving Int -> UncalPDF -> ShowS
[UncalPDF] -> ShowS
UncalPDF -> String
(Int -> UncalPDF -> ShowS)
-> (UncalPDF -> String) -> ([UncalPDF] -> ShowS) -> Show UncalPDF
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UncalPDF] -> ShowS
$cshowList :: [UncalPDF] -> ShowS
show :: UncalPDF -> String
$cshow :: UncalPDF -> String
showsPrec :: Int -> UncalPDF -> ShowS
$cshowsPrec :: Int -> UncalPDF -> ShowS
Show

-- | A data type to represent a calibration curve with 'YearBP'
data CalCurveBP = CalCurveBP {
    -- | Years calBP
      CalCurveBP -> Vector YearBP
_calCurveBPCals :: VU.Vector YearBP
    -- | Years BP
    , CalCurveBP -> Vector YearBP
_calCurveBPUnCals :: VU.Vector YearBP
    -- | Standard deviation (one sigma in years)
    , CalCurveBP -> Vector YearBP
_calCurveBPSigmas :: VU.Vector YearRange
    } deriving Int -> CalCurveBP -> ShowS
[CalCurveBP] -> ShowS
CalCurveBP -> String
(Int -> CalCurveBP -> ShowS)
-> (CalCurveBP -> String)
-> ([CalCurveBP] -> ShowS)
-> Show CalCurveBP
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalCurveBP] -> ShowS
$cshowList :: [CalCurveBP] -> ShowS
show :: CalCurveBP -> String
$cshow :: CalCurveBP -> String
showsPrec :: Int -> CalCurveBP -> ShowS
$cshowsPrec :: Int -> CalCurveBP -> ShowS
Show

-- | A second data type to represent a calibration curve, here now with 'YearBCAD'
data CalCurveBCAD = CalCurveBCAD {
    -- | Years calBCAD
      CalCurveBCAD -> Vector Int
_calCurveBCADCals :: VU.Vector YearBCAD
    -- | Years BCAD
    , CalCurveBCAD -> Vector Int
_calCurveBCADUnCals :: VU.Vector YearBCAD
    -- | Standard deviation (one sigma in years)
    , CalCurveBCAD -> Vector YearBP
_calCurveBCADSigmas :: VU.Vector YearRange
    } deriving Int -> CalCurveBCAD -> ShowS
[CalCurveBCAD] -> ShowS
CalCurveBCAD -> String
(Int -> CalCurveBCAD -> ShowS)
-> (CalCurveBCAD -> String)
-> ([CalCurveBCAD] -> ShowS)
-> Show CalCurveBCAD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalCurveBCAD] -> ShowS
$cshowList :: [CalCurveBCAD] -> ShowS
show :: CalCurveBCAD -> String
$cshow :: CalCurveBCAD -> String
showsPrec :: Int -> CalCurveBCAD -> ShowS
$cshowsPrec :: Int -> CalCurveBCAD -> ShowS
Show

-- | A data type to represent a calibration curve in a /wide/ matrix form
data CalCurveMatrix = CalCurveMatrix {
    -- | Row names of the calibration curve matrix: Years BCAD
      CalCurveMatrix -> Vector Int
_calCurveMatrixUnCals :: VU.Vector YearBCAD
    -- | Column names of the calibration curve matrix: Years calBCAD
    , CalCurveMatrix -> Vector Int
_calCurveMatrixCals :: VU.Vector YearBCAD
    -- | Matrix (as a list of columns) with the probability densities
    , CalCurveMatrix -> Vector (Vector Float)
_calCurveMatrixDens :: V.Vector (VU.Vector Float)
    } deriving Int -> CalCurveMatrix -> ShowS
[CalCurveMatrix] -> ShowS
CalCurveMatrix -> String
(Int -> CalCurveMatrix -> ShowS)
-> (CalCurveMatrix -> String)
-> ([CalCurveMatrix] -> ShowS)
-> Show CalCurveMatrix
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalCurveMatrix] -> ShowS
$cshowList :: [CalCurveMatrix] -> ShowS
show :: CalCurveMatrix -> String
$cshow :: CalCurveMatrix -> String
showsPrec :: Int -> CalCurveMatrix -> ShowS
$cshowsPrec :: Int -> CalCurveMatrix -> ShowS
Show

-- | A data type to represent a year-wise probability density for calibrated dates.
-- Although technically not correct, we still call this a probability density function (PDF)
data CalPDF = CalPDF {
    -- | Sample identifier, e.g. a lab number
      CalPDF -> String
_calPDFid :: String
    -- | Years calBCAD
    , CalPDF -> Vector Int
_calPDFCals :: VU.Vector YearBCAD
    -- | Probability densities for each year in '_calPDFCals'
    , CalPDF -> Vector Float
_calPDFDens :: VU.Vector Float
    } deriving (Int -> CalPDF -> ShowS
[CalPDF] -> ShowS
CalPDF -> String
(Int -> CalPDF -> ShowS)
-> (CalPDF -> String) -> ([CalPDF] -> ShowS) -> Show CalPDF
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalPDF] -> ShowS
$cshowList :: [CalPDF] -> ShowS
show :: CalPDF -> String
$cshow :: CalPDF -> String
showsPrec :: Int -> CalPDF -> ShowS
$cshowsPrec :: Int -> CalPDF -> ShowS
Show, CalPDF -> CalPDF -> Bool
(CalPDF -> CalPDF -> Bool)
-> (CalPDF -> CalPDF -> Bool) -> Eq CalPDF
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalPDF -> CalPDF -> Bool
$c/= :: CalPDF -> CalPDF -> Bool
== :: CalPDF -> CalPDF -> Bool
$c== :: CalPDF -> CalPDF -> Bool
Eq)

-- | A data type to represent an expression for sum- or product calibration
data CalExpr =
      UnCalDate UncalC14
    | CalDate CalPDF
    | SumCal CalExpr CalExpr
    | ProductCal CalExpr CalExpr
    deriving Int -> CalExpr -> ShowS
[CalExpr] -> ShowS
CalExpr -> String
(Int -> CalExpr -> ShowS)
-> (CalExpr -> String) -> ([CalExpr] -> ShowS) -> Show CalExpr
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalExpr] -> ShowS
$cshowList :: [CalExpr] -> ShowS
show :: CalExpr -> String
$cshow :: CalExpr -> String
showsPrec :: Int -> CalExpr -> ShowS
$cshowsPrec :: Int -> CalExpr -> ShowS
Show
-- http://www.cse.chalmers.se/edu/year/2018/course/TDA452/lectures/RecursiveDataTypes.html

-- | A data type to represent a human readable summary of a calibrated radiocarbon date
data CalC14 = CalC14 {
    -- | Identifier, e.g. a lab number
      CalC14 -> String
_calC14id :: String
    -- | Summary of the range of the calibrated date
    , CalC14 -> CalRangeSummary
_calC14RangeSummary :: CalRangeSummary
    -- | One-sigma high density regions
    , CalC14 -> [HDR]
_calC14HDROneSigma :: [HDR]
    -- | Two-sigma high density regions
    , CalC14 -> [HDR]
_calC14HDRTwoSigma :: [HDR]
    } deriving Int -> CalC14 -> ShowS
[CalC14] -> ShowS
CalC14 -> String
(Int -> CalC14 -> ShowS)
-> (CalC14 -> String) -> ([CalC14] -> ShowS) -> Show CalC14
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalC14] -> ShowS
$cshowList :: [CalC14] -> ShowS
show :: CalC14 -> String
$cshow :: CalC14 -> String
showsPrec :: Int -> CalC14 -> ShowS
$cshowsPrec :: Int -> CalC14 -> ShowS
Show

-- | A data type to store a simple range summary of the calibrated date, including 
-- the median age
data CalRangeSummary = CalRangeSummary {
    -- | Start of the two-sigma age range
      CalRangeSummary -> Int
_calRangeStartTwoSigma :: YearBCAD
    -- | Start of the one-sigma age range
    , CalRangeSummary -> Int
_calRangeStartOneSigma :: YearBCAD
    -- | Median age
    , CalRangeSummary -> Int
_calRangeMedian        :: YearBCAD
    -- | End of the one-sigma age range
    , CalRangeSummary -> Int
_calRangeStopOneSigma  :: YearBCAD
    -- | End of the two-sigma age range
    , CalRangeSummary -> Int
_calRangeStopTwoSigma  :: YearBCAD
} deriving Int -> CalRangeSummary -> ShowS
[CalRangeSummary] -> ShowS
CalRangeSummary -> String
(Int -> CalRangeSummary -> ShowS)
-> (CalRangeSummary -> String)
-> ([CalRangeSummary] -> ShowS)
-> Show CalRangeSummary
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CalRangeSummary] -> ShowS
$cshowList :: [CalRangeSummary] -> ShowS
show :: CalRangeSummary -> String
$cshow :: CalRangeSummary -> String
showsPrec :: Int -> CalRangeSummary -> ShowS
$cshowsPrec :: Int -> CalRangeSummary -> ShowS
Show

-- | A data type to represent a high density region of a probability distribution.
-- A high density region is here defined as an age range, within which the respective 
-- cummulative probability (e.g. of an calibrated radiocarbon date density curve) 
-- is above a certain threshold
data HDR = HDR {
    -- | Start of the high density region in years calBCAD
      HDR -> Int
_hdrstart :: YearBCAD
    -- | End of the high density region in years calBCAD
    , HDR -> Int
_hdrstop :: YearBCAD
    } deriving (Int -> HDR -> ShowS
[HDR] -> ShowS
HDR -> String
(Int -> HDR -> ShowS)
-> (HDR -> String) -> ([HDR] -> ShowS) -> Show HDR
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HDR] -> ShowS
$cshowList :: [HDR] -> ShowS
show :: HDR -> String
$cshow :: HDR -> String
showsPrec :: Int -> HDR -> ShowS
$cshowsPrec :: Int -> HDR -> ShowS
Show, HDR -> HDR -> Bool
(HDR -> HDR -> Bool) -> (HDR -> HDR -> Bool) -> Eq HDR
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HDR -> HDR -> Bool
$c/= :: HDR -> HDR -> Bool
== :: HDR -> HDR -> Bool
$c== :: HDR -> HDR -> Bool
Eq)