summaryrefslogtreecommitdiff
path: root/CosmicCalendar.hs
blob: 38a8c86651e1380b020b68a950a6932353df351a (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
{-# OPTIONS_GHC
  -Wall
  -Wno-unused-imports
  -Wno-unused-top-binds
  -Wno-name-shadowing
#-}
{-# language NoImplicitPrelude #-}
{-# language RecordWildCards #-}
{-# language FlexibleContexts #-}
{-# language TemplateHaskell #-}
{-# language ViewPatterns #-}
{-# language OverloadedStrings #-}
{-# language QuasiQuotes #-}

module CosmicCalendar where

import Rebase.Prelude
import qualified Rebase.Prelude as Prelude
import Control.Lens hiding ((<|))
import Data.Foldable (toList)
import Data.Ratio
import Text.Printf
import Data.Time.Calendar.OrdinalDate
import Data.Time.LocalTime
import Control.Monad.RWS
import Data.Time.Calendar.OrdinalDate
import Data.Text.Format.Numbers
import NeatInterpolation
import Data.Text (Text)

import Rebase.Data.Map.Strict (Map)
import qualified Rebase.Data.Map.Strict as Map

-- 13.787±0.020 billion years.  Source: https://en.wikipedia.org/wiki/Age_of_the_universe#cite_note-Planck_2018-2
ageOfUniverseInYears :: Integer
ageOfUniverseInYears = 13787 * 1000 * 1000

daysPerYear :: NominalDiffTime
daysPerYear = 365.2422

lengthOfDay :: NominalDiffTime
lengthOfDay = 24 * 60 * 60

lengthOfYear :: NominalDiffTime
lengthOfYear = daysPerYear * lengthOfDay

ageOfUniverse :: NominalDiffTime
ageOfUniverse = fromIntegral ageOfUniverseInYears * lengthOfYear

data CalendarEntry = CalendarEntry {
  calBeginTime :: NominalDiffTime,
  calEndTime :: Maybe NominalDiffTime,
  calTitle :: Text,
  calSubtitle :: Text,
  calDescription :: Text,
  calReferences :: Text
} deriving (Show)

theCalendar :: Map NominalDiffTime CalendarEntry
theCalendar = Map.fromList $ map (\x -> (calBeginTime x, x)) theCalendarList

thousandYears :: Rational -> NominalDiffTime
thousandYears = (* (lengthOfYear * 1000)) . fromRational 

millionYears :: Rational -> NominalDiffTime
millionYears = (* (lengthOfYear * 1000 * 1000)) . fromRational 

billionYears :: Rational -> NominalDiffTime
billionYears = (* (lengthOfYear * 1000 * 1000 * 1000)) . fromRational 

yearsAgo :: Rational -> NominalDiffTime
yearsAgo n = (ageOfUniverse - lengthOfYear * fromRational n) / ageOfUniverse * lengthOfYear

thousandYearsAgo :: Rational -> NominalDiffTime
thousandYearsAgo = yearsAgo . (* 1000)

millionYearsAgo :: Rational -> NominalDiffTime
millionYearsAgo = thousandYearsAgo . (* 1000)

billionYearsAgo :: Rational -> NominalDiffTime
billionYearsAgo = millionYearsAgo . (* 1000)

afterBigBang :: NominalDiffTime -> NominalDiffTime
afterBigBang = (/ ageOfUniverse) . (* lengthOfYear)

yearStart :: LocalTime -> LocalTime
yearStart (LocalTime d _) = LocalTime d' t'
  where
    d' = fromGregorian y 1 1
    t' = TimeOfDay 0 0 0
    (y, _, _) = toGregorian d

localTimeToYearElapsed :: LocalTime -> NominalDiffTime
localTimeToYearElapsed t = t `diffLocalTime` yearStart t

getPreviousCalendarEntry :: LocalTime -> Maybe CalendarEntry
getPreviousCalendarEntry (localTimeToYearElapsed -> t) = snd <$> Map.lookupLT t theCalendar

getCurrentCalendarEntry :: LocalTime -> Maybe CalendarEntry
getCurrentCalendarEntry (localTimeToYearElapsed -> t) = snd <$> Map.lookupLE t theCalendar

getNextCalendarEntry :: LocalTime -> Maybe CalendarEntry
getNextCalendarEntry (localTimeToYearElapsed -> t) = snd <$> Map.lookupGT t theCalendar

theCalendarList :: [CalendarEntry]
theCalendarList =
  [
    CalendarEntry 0 Nothing "The Big Bang" "The universe begins" "" "",
    CalendarEntry (370 & thousandYears & afterBigBang)
                  Nothing
                  "Recombination"
                  "The universe becomes transparent"
                  recombinationDescription
                  recombinationReferences,
    CalendarEntry (13.4 & billionYearsAgo) Nothing
    "The first observed star"
    ""
    "First Light Viewed Through the Rich Cluster Abell 2218"
    "https://sites.astro.caltech.edu/~rse/firstlight/",
    CalendarEntry (4.6 & billionYearsAgo) Nothing
    "Formation of the Sun"
    "The formation of the solar system begins"
    "The formation of the Solar System began about 4.6 billion years ago with the gravitational collapse of a small part of a giant molecular cloud.[1] Most of the collapsing mass collected in the center, forming the Sun, while the rest flattened into a protoplanetary disk out of which the planets, moons, asteroids, and other small Solar System bodies formed."
    "https://en.wikipedia.org/wiki/Formation_and_evolution_of_the_Solar_System",
    CalendarEntry (4.54 & billionYearsAgo) Nothing
    "Formation of Earth"
    ""
    earthDescription
    "https://en.wikipedia.org/wiki/History_of_Earth#Solar_System_formation",

    CalendarEntry (3.4 & millionYearsAgo) Nothing
    "First Stone Tools"
    "Mode I: The Oldowan Industry"
    [text|
    (Stones with sharp edges.)

    The earliest known Oldowan tools yet found date from 2.6 million years ago, during the Lower Palaeolithic period, and have been uncovered at Gona in Ethiopia.[16] After this date, the Oldowan Industry subsequently spread throughout much of Africa, although archaeologists are currently unsure which Hominan species first developed them, with some speculating that it was Australopithecus garhi, and others believing that it was in fact Homo habilis.[17]

    Homo habilis was the hominin who used the tools for most of the Oldowan in Africa, but at about 1.9-1.8 million years ago Homo erectus inherited them. The Industry flourished in southern and eastern Africa between 2.6 and 1.7 million years ago, but was also spread out of Africa and into Eurasia by travelling bands of H. erectus, who took it as far east as Java by 1.8 million years ago and Northern China by 1.6 million years ago.
    |]
    "",

    CalendarEntry (1.8 & millionYearsAgo) Nothing
    "First major transition in stone tool technology"
    "Mode II: The Acheulean Industry"
    "From the Konso Formation of Ethiopia, Acheulean hand-axes are dated to about 1.5 million years ago using radiometric dating of deposits containing volcanic ashes.[6] Acheulean tools in South Asia have also been found to be dated as far as 1.5 million years ago.[7] However, the earliest accepted examples of the Acheulean currently known come from the West Turkana region of Kenya and were first described by a French-led archaeology team.[8] These particular Acheulean tools were recently dated through the method of magnetostratigraphy to about 1.76 million years ago, making them the oldest not only in Africa but the world.[9] The earliest user of Acheulean tools was Homo ergaster, who first appeared about 1.8 million years ago. Not all researchers use this formal name, and instead prefer to call these users early Homo erectus.[3]"
    "",

    CalendarEntry (160 & thousandYearsAgo) Nothing
    "Second major transition in stone tool technology"
    "Mode III: The Levallois technique; The Mousterian Industry"
    [text|
    (Stone scrapers, knives, and projectile points)

    The technique is first found in the Lower Palaeolithic but is most commonly associated with the Neanderthal Mousterian industries of the Middle Palaeolithic. In the Levant, the Levallois technique was also used by anatomically modern humans during the Middle Stone Age. In North Africa, the Levallois technique was used in the Middle Stone Age, most notably in the Aterian industry to produce very small projectile points. While Levallois cores do display some variability in their platforms, their flake production surfaces show remarkable uniformity. As the Levallois technique is counterintuitive, teaching the process is necessary and thus language is a prerequisite for such technology.[2]

    The Mousterian (or Mode III) is a techno-complex (archaeological industry) of stone tools, associated primarily with the Neanderthals in Europe, and to a lesser extent the earliest anatomically modern humans in North Africa and West Asia. The Mousterian largely defines the latter part of the Middle Paleolithic, the middle of the West Eurasian Old Stone Age. It lasted roughly from 160,000 to 40,000 BP. If its predecessor, known as Levallois or Levallois-Mousterian, is included, the range is extended to as early as c. 300,000–200,000 BP.[2] The main following period is the Aurignacian (c. 43,000–28,000 BP) of Homo sapiens.
    |]
    "",

    CalendarEntry (50 & thousandYearsAgo) Nothing
    "Third major transition in stone tool technology"
    "Mode IV: The Aurignacian Industry"
    "The widespread use of long blades (rather than flakes) of the Upper Palaeolithic Mode 4 industries appeared during the Upper Palaeolithic between 50,000 and 10,000 years ago, although blades were produced in small quantities much earlier by Neanderthals.[20] The Aurignacian culture seems to have been the first to rely largely on blades.[21] The use of blades exponentially increases the efficiency of core usage compared to the Levallois flake technique, which had a similar advantage over Acheulean technology which was worked from cores."
    "https://en.wikipedia.org/wiki/Stone_tool#Mode_IV:_The_Aurignacian_Industry",

    CalendarEntry (35 & thousandYearsAgo) Nothing
    "Last major transition in stone tool technology"
    "Mode V: The Microlithic Industries"
    "Mode 5 stone tools involve the production of microliths, which were used in composite tools, mainly fastened to a shaft.[22] Examples include the Magdalenian culture. Such a technology makes much more efficient use of available materials like flint, although required greater skill in manufacturing the small flakes. Mounting sharp flint edges in a wood or bone handle is the key innovation in microliths, essentially because the handle gives the user protection against the flint and also improves leverage of the device."
    "https://en.wikipedia.org/wiki/Stone_tool#Mode_V:_The_Microlithic_Industries"
    ]

  where
    earthDescription = [text|
      The standard model for the formation of the Solar System (including the Earth) is the solar nebula hypothesis.[23] In this model, the Solar System formed from a large, rotating cloud of interstellar dust and gas called the solar nebula. It was composed of hydrogen and helium created shortly after the Big Bang 13.8 Ga (billion years ago) and heavier elements ejected by supernovae. About 4.5 Ga, the nebula began a contraction that may have been triggered by the shock wave from a nearby supernova.[24] A shock wave would have also made the nebula rotate. As the cloud began to accelerate, its angular momentum, gravity, and inertia flattened it into a protoplanetary disk perpendicular to its axis of rotation. Small perturbations due to collisions and the angular momentum of other large debris created the means by which kilometer-sized protoplanets began to form, orbiting the nebular center.[25]

      The center of the nebula, not having much angular momentum, collapsed rapidly, the compression heating it until nuclear fusion of hydrogen into helium began. After more contraction, a T Tauri star ignited and evolved into the Sun. Meanwhile, in the outer part of the nebula gravity caused matter to condense around density perturbations and dust particles, and the rest of the protoplanetary disk began separating into rings. In a process known as runaway accretion, successively larger fragments of dust and debris clumped together to form planets.[25] Earth formed in this manner about 4.54 billion years ago (with an uncertainty of 1%)[26][27][4] and was largely completed within 10–20 million years.[28] The solar wind of the newly formed T Tauri star cleared out most of the material in the disk that had not already condensed into larger bodies. The same process is expected to produce accretion disks around virtually all newly forming stars in the universe, some of which yield planets.[29]
    |]
    recombinationDescription = [text|
      At about 370,000 years,[3][4][5][6] neutral hydrogen atoms finish forming ("recombination"), and as a result the universe also became transparent for the first time. The newly formed atoms—mainly hydrogen and helium with traces of lithium—quickly reach their lowest energy state (ground state) by releasing photons ("photon decoupling"), and these photons can still be detected today as the cosmic microwave background (CMB). This is the oldest direct observation we currently have of the universe.
    |]
    recombinationReferences = [text|
      https://en.wikipedia.org/wiki/Chronology_of_the_universe#The_very_early_universe

      3. Tanabashi, M. 2018, p. 358, chpt. 21.4.1: "Big-Bang Cosmology" (Revised
      September 2017) by Keith A. Olive and John A. Peacock.

      4. Notes: Edward L. Wright's Javascript Cosmology Calculator (last
      modified 23 July 2018). With a default H 0 {\displaystyle H_{0}} H_{0} =
      69.6 (based on WMAP9+SPT+ACT+6dFGS+BOSS/DR11+H0/Riess) parameters, the
      calculated age of the universe with a redshift of z = 1100 is in agreement
      with Olive and Peacock (about 370,000 years).

      5. Hinshaw, Weiland & Hill 2009. See PDF: page 45, Table 7, Age at
      decoupling, last column. Based on WMAP+BAO+SN parameters, the age of
      decoupling occurred 376971+3162−3167 years after the Big Bang.

      6. Ryden 2006, pp. 194–195. "Without going into the details of the
      non-equilibrium physics, let's content ourselves by saying, in round
      numbers, zdec ≈ 1100, corresponding to a temperature Tdec ≈ 3000 K, when
      the age of the universe was tdec ≈ 350,000 yr in the Benchmark Model.
      (...) The relevant times of various events around the time of
      recombination are shown in Table 9.1. (...) Note that all these times are
      approximate, and are dependent on the cosmological model you choose. (I
      have chosen the Benchmark Model in calculating these numbers.)"

      https://en.wikipedia.org/wiki/Recombination_(cosmology)#cite_note-2

    |]