{-# LANGUAGE StrictData #-}
module Currycarbon.Types where
import qualified Data.Vector as V
import qualified Data.Vector.Unboxed as VU
data CalibrationMethod =
MatrixMultiplication
| Bchron { CalibrationMethod -> CalibrationDistribution
distribution :: CalibrationDistribution }
deriving (Int -> CalibrationMethod -> ShowS
[CalibrationMethod] -> ShowS
CalibrationMethod -> String
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
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)
data CalibrationDistribution =
NormalDist
| StudentTDist {
CalibrationDistribution -> Double
ndf :: Double
}
deriving (Int -> CalibrationDistribution -> ShowS
[CalibrationDistribution] -> ShowS
CalibrationDistribution -> String
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
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)
type YearBP = Word
type YearBCAD = Int
type YearRange = Word
data UncalC14 = UncalC14 {
UncalC14 -> String
_uncalC14Id :: String
, UncalC14 -> YearBP
_uncalC14UnCal :: YearBP
, UncalC14 -> YearBP
_uncalC14Sigma :: YearRange
} deriving (Int -> UncalC14 -> ShowS
[UncalC14] -> ShowS
UncalC14 -> String
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
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)
data UncalPDF = UncalPDF {
UncalPDF -> String
_uncalPDFid :: String
, UncalPDF -> Vector YearBP
_uncalPDFUnCals :: VU.Vector YearBP
, UncalPDF -> Vector Float
_uncalPDFDens :: VU.Vector Float
} deriving Int -> UncalPDF -> ShowS
[UncalPDF] -> ShowS
UncalPDF -> String
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
data CalCurveBP = CalCurveBP {
CalCurveBP -> Vector YearBP
_calCurveBPCals :: VU.Vector YearBP
, CalCurveBP -> Vector YearBP
_calCurveBPUnCals :: VU.Vector YearBP
, CalCurveBP -> Vector YearBP
_calCurveBPSigmas :: VU.Vector YearRange
} deriving Int -> CalCurveBP -> ShowS
[CalCurveBP] -> ShowS
CalCurveBP -> String
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
data CalCurveBCAD = CalCurveBCAD {
CalCurveBCAD -> Vector Int
_calCurveBCADCals :: VU.Vector YearBCAD
, CalCurveBCAD -> Vector Int
_calCurveBCADUnCals :: VU.Vector YearBCAD
, CalCurveBCAD -> Vector YearBP
_calCurveBCADSigmas :: VU.Vector YearRange
} deriving Int -> CalCurveBCAD -> ShowS
[CalCurveBCAD] -> ShowS
CalCurveBCAD -> String
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
data CalCurveMatrix = CalCurveMatrix {
CalCurveMatrix -> Vector Int
_calCurveMatrixUnCals :: VU.Vector YearBCAD
, CalCurveMatrix -> Vector Int
_calCurveMatrixCals :: VU.Vector YearBCAD
, CalCurveMatrix -> Vector (Vector Float)
_calCurveMatrixDens :: V.Vector (VU.Vector Float)
} deriving Int -> CalCurveMatrix -> ShowS
[CalCurveMatrix] -> ShowS
CalCurveMatrix -> String
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
data CalPDF = CalPDF {
CalPDF -> String
_calPDFid :: String
, CalPDF -> Vector Int
_calPDFCals :: VU.Vector YearBCAD
, CalPDF -> Vector Float
_calPDFDens :: VU.Vector Float
} deriving (Int -> CalPDF -> ShowS
[CalPDF] -> ShowS
CalPDF -> String
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
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)
data NamedCalExpr = NamedCalExpr {
NamedCalExpr -> String
_exprID :: String
, NamedCalExpr -> CalExpr
_expr :: CalExpr
} deriving (Int -> NamedCalExpr -> ShowS
[NamedCalExpr] -> ShowS
NamedCalExpr -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NamedCalExpr] -> ShowS
$cshowList :: [NamedCalExpr] -> ShowS
show :: NamedCalExpr -> String
$cshow :: NamedCalExpr -> String
showsPrec :: Int -> NamedCalExpr -> ShowS
$cshowsPrec :: Int -> NamedCalExpr -> ShowS
Show, NamedCalExpr -> NamedCalExpr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NamedCalExpr -> NamedCalExpr -> Bool
$c/= :: NamedCalExpr -> NamedCalExpr -> Bool
== :: NamedCalExpr -> NamedCalExpr -> Bool
$c== :: NamedCalExpr -> NamedCalExpr -> Bool
Eq)
data CalExpr =
UnCalDate UncalC14
| WindowBP TimeWindowBP
| WindowBCAD TimeWindowBCAD
| CalDate CalPDF
| SumCal CalExpr CalExpr
| ProductCal CalExpr CalExpr
deriving (Int -> CalExpr -> ShowS
[CalExpr] -> ShowS
CalExpr -> String
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, CalExpr -> CalExpr -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CalExpr -> CalExpr -> Bool
$c/= :: CalExpr -> CalExpr -> Bool
== :: CalExpr -> CalExpr -> Bool
$c== :: CalExpr -> CalExpr -> Bool
Eq)
data TimeWindowBP = TimeWindowBP String YearBP YearBP
deriving (Int -> TimeWindowBP -> ShowS
[TimeWindowBP] -> ShowS
TimeWindowBP -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeWindowBP] -> ShowS
$cshowList :: [TimeWindowBP] -> ShowS
show :: TimeWindowBP -> String
$cshow :: TimeWindowBP -> String
showsPrec :: Int -> TimeWindowBP -> ShowS
$cshowsPrec :: Int -> TimeWindowBP -> ShowS
Show, TimeWindowBP -> TimeWindowBP -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeWindowBP -> TimeWindowBP -> Bool
$c/= :: TimeWindowBP -> TimeWindowBP -> Bool
== :: TimeWindowBP -> TimeWindowBP -> Bool
$c== :: TimeWindowBP -> TimeWindowBP -> Bool
Eq)
data TimeWindowBCAD = TimeWindowBCAD String YearBCAD YearBCAD
deriving (Int -> TimeWindowBCAD -> ShowS
[TimeWindowBCAD] -> ShowS
TimeWindowBCAD -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TimeWindowBCAD] -> ShowS
$cshowList :: [TimeWindowBCAD] -> ShowS
show :: TimeWindowBCAD -> String
$cshow :: TimeWindowBCAD -> String
showsPrec :: Int -> TimeWindowBCAD -> ShowS
$cshowsPrec :: Int -> TimeWindowBCAD -> ShowS
Show, TimeWindowBCAD -> TimeWindowBCAD -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TimeWindowBCAD -> TimeWindowBCAD -> Bool
$c/= :: TimeWindowBCAD -> TimeWindowBCAD -> Bool
== :: TimeWindowBCAD -> TimeWindowBCAD -> Bool
$c== :: TimeWindowBCAD -> TimeWindowBCAD -> Bool
Eq)
data CalC14 = CalC14 {
CalC14 -> String
_calC14id :: String
, CalC14 -> CalRangeSummary
_calC14RangeSummary :: CalRangeSummary
, CalC14 -> [HDR]
_calC14HDROneSigma :: [HDR]
, CalC14 -> [HDR]
_calC14HDRTwoSigma :: [HDR]
} deriving Int -> CalC14 -> ShowS
[CalC14] -> ShowS
CalC14 -> String
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
data CalRangeSummary = CalRangeSummary {
CalRangeSummary -> Int
_calRangeStartTwoSigma :: YearBCAD
, CalRangeSummary -> Int
_calRangeStartOneSigma :: YearBCAD
, CalRangeSummary -> Int
_calRangeMedian :: YearBCAD
, CalRangeSummary -> Int
_calRangeStopOneSigma :: YearBCAD
, CalRangeSummary -> Int
_calRangeStopTwoSigma :: YearBCAD
} deriving Int -> CalRangeSummary -> ShowS
[CalRangeSummary] -> ShowS
CalRangeSummary -> String
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
data HDR = HDR {
HDR -> Int
_hdrstart :: YearBCAD
, HDR -> Int
_hdrstop :: YearBCAD
} deriving (Int -> HDR -> ShowS
[HDR] -> ShowS
HDR -> String
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
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)
data RandomAgeSample = RandomAgeSample {
RandomAgeSample -> String
_rasId :: String
, RandomAgeSample -> Vector Int
_rasSamples :: VU.Vector YearBCAD
} deriving Int -> RandomAgeSample -> ShowS
[RandomAgeSample] -> ShowS
RandomAgeSample -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RandomAgeSample] -> ShowS
$cshowList :: [RandomAgeSample] -> ShowS
show :: RandomAgeSample -> String
$cshow :: RandomAgeSample -> String
showsPrec :: Int -> RandomAgeSample -> ShowS
$cshowsPrec :: Int -> RandomAgeSample -> ShowS
Show