summaryrefslogtreecommitdiff
path: root/lib/Postdelay/TimeSpec/Units.hs
diff options
context:
space:
mode:
authorGregor Kleen <aethoago@141.li>2017-02-15 15:10:51 +0100
committerGregor Kleen <aethoago@141.li>2017-02-15 15:10:51 +0100
commitee09f262f9b8c7c6a4042071cdfff3e22adbef86 (patch)
treebaeb1d9ee726881d25e0762c21f750850efb37f2 /lib/Postdelay/TimeSpec/Units.hs
parent8a24b41b333bce25e698d2e4b87f4b4f6548772c (diff)
downloadpostdelay-ee09f262f9b8c7c6a4042071cdfff3e22adbef86.tar
postdelay-ee09f262f9b8c7c6a4042071cdfff3e22adbef86.tar.gz
postdelay-ee09f262f9b8c7c6a4042071cdfff3e22adbef86.tar.bz2
postdelay-ee09f262f9b8c7c6a4042071cdfff3e22adbef86.tar.xz
postdelay-ee09f262f9b8c7c6a4042071cdfff3e22adbef86.zip
Establish framework
Diffstat (limited to 'lib/Postdelay/TimeSpec/Units.hs')
-rw-r--r--lib/Postdelay/TimeSpec/Units.hs111
1 files changed, 111 insertions, 0 deletions
diff --git a/lib/Postdelay/TimeSpec/Units.hs b/lib/Postdelay/TimeSpec/Units.hs
new file mode 100644
index 0000000..330997a
--- /dev/null
+++ b/lib/Postdelay/TimeSpec/Units.hs
@@ -0,0 +1,111 @@
1{-# LANGUAGE TemplateHaskell, TypeFamilies, GADTs, RankNTypes, DataKinds, ViewPatterns, ScopedTypeVariables #-}
2
3module Postdelay.TimeSpec.Units
4 ( Time
5
6 , Second, Minute, Hour
7 , Day, Week, Month, Year
8
9 , timeLength
10
11 , module Data.Units.SI.Prefixes
12 ) where
13
14import Postdelay.TimeSpec.Utils
15
16import Control.Applicative
17
18import Data.Metrology
19import Data.Metrology.TH
20import Data.Metrology.SI.Mono ()
21
22import Data.Units.SI
23import Data.Units.SI.Prefixes
24import Data.Units.SI.Parser
25import qualified Data.Dimensions.SI as D
26
27import Data.Foldable
28import Data.Function
29import Data.VectorSpace
30
31import Data.Fixed (Fixed, HasResolution)
32import qualified Data.Fixed as Fixed
33
34
35import Text.Megaparsec
36
37
38declareDerivedUnit "Day" [t| Hour |] 24 Nothing
39declareDerivedUnit "Week" [t| Day |] 7 Nothing
40declareDerivedUnit "Month" [t| Day |] 30 Nothing
41declareDerivedUnit "Year" [t| Day |] 365.25 Nothing
42
43type Time = MkQu_DLN D.Time DefaultLCSU Fixed.Pico
44
45data Prefix where
46 Prefix :: forall p. (UnitPrefix p, Show p) => p -> Prefix
47
48instance HasResolution p => AdditiveGroup (Fixed p) where
49 zeroV = 0
50 (^+^) = (+)
51 negateV = negate
52 (^-^) = (-)
53
54instance HasResolution p => VectorSpace (Fixed p) where
55 type Scalar (Fixed p) = Fixed p
56 (*^) = (*)
57
58
59timeLength :: StringParser s m => m Time
60timeLength = (*^) <$> lexeme rational <*> timeUnit
61
62rational :: forall s m n. (StringParser s m, Fractional n, Num n) => m n
63rational = combine <$> some digitChar <*> option [] (char '.' *> many digitChar)
64 where
65 combine :: [Char] -> [Char] -> n
66 combine (map asN -> whole) (map asN -> fractional)
67 = foldl' (\i l -> i * 10 + l) 0 whole + (foldr' (\h t -> h + t / 10) 0 fractional) / 10
68 asN :: Char -> n
69 asN c = fromIntegral $ ((-) `on` fromEnum) c '0'
70
71timeUnit :: StringParser s m => m Time
72timeUnit = label "Unit of time" . choice $
73 [ 1 % Second <$ choice [ string' "seconds"
74 , string' "second"
75 , string' "secs"
76 , string' "sec"
77 ]
78 , 1 % Minute <$ choice [ string' "minutes"
79 , string' "minute"
80 , string' "mins"
81 , string' "min"
82 ]
83 , 1 % Hour <$ choice [ string' "hours"
84 , string' "hour"
85 ]
86 , 1 % Day <$ choice [ string' "days"
87 , string' "day"
88 ]
89 , 1 % Week <$ choice [ string' "weeks"
90 , string' "week"
91 ]
92 , 1 % Month <$ choice [ string' "months"
93 , string' "month"
94 ]
95 , 1 % Year <$ choice [ string' "years"
96 , string' "year"
97 ]
98 ] ++
99 [ (% Second) <$> option 1 siPrefix <* string "s"
100 , (% Hour) <$> option 1 siPrefix <* string "h"
101 , (% Day) <$> option 1 siPrefix <* string "d"
102 , (% Year) <$> option 1 siPrefix <* choice [ string "a", string "yr", string "yrs" ]
103 ]
104
105siPrefix :: (StringParser s m, Fractional n) => m n
106siPrefix = label "SI prefix" . choice $ map (\(Prefix p) -> multiplier p <$ string (show p))
107 [ Prefix Deca, Prefix Hecto, Prefix Kilo, Prefix Mega, Prefix Giga
108 , Prefix Tera, Prefix Peta, Prefix Exa, Prefix Zetta, Prefix Yotta
109 , Prefix Deci, Prefix Centi, Prefix Milli, Prefix Micro, Prefix Nano
110 , Prefix Pico, Prefix Femto, Prefix Atto, Prefix Zepto, Prefix Yocto
111 ]