summaryrefslogtreecommitdiff
path: root/lib/Postdelay/TimeSpec/Units.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Postdelay/TimeSpec/Units.hs')
-rw-r--r--lib/Postdelay/TimeSpec/Units.hs42
1 files changed, 27 insertions, 15 deletions
diff --git a/lib/Postdelay/TimeSpec/Units.hs b/lib/Postdelay/TimeSpec/Units.hs
index 330997a..0062460 100644
--- a/lib/Postdelay/TimeSpec/Units.hs
+++ b/lib/Postdelay/TimeSpec/Units.hs
@@ -1,19 +1,21 @@
1{-# LANGUAGE TemplateHaskell, TypeFamilies, GADTs, RankNTypes, DataKinds, ViewPatterns, ScopedTypeVariables #-} 1{-# LANGUAGE TemplateHaskell, GADTs, RankNTypes, DataKinds, ViewPatterns, ScopedTypeVariables, FlexibleContexts, FlexibleInstances, UndecidableInstances, TypeFamilies #-}
2 2
3module Postdelay.TimeSpec.Units 3module Postdelay.TimeSpec.Units
4 ( Time 4 ( Time
5 5
6 , Second, Minute, Hour 6 , Second(..), Minute(..), Hour(..)
7 , Day, Week, Month, Year 7 , Day(..), Week(..), Month(..), Year(..)
8 8
9 , timeLength 9 , timeLength
10 10
11 , module Data.Metrology
11 , module Data.Units.SI.Prefixes 12 , module Data.Units.SI.Prefixes
12 ) where 13 ) where
13 14
14import Postdelay.TimeSpec.Utils 15import Postdelay.TimeSpec.Utils
15 16
16import Control.Applicative 17import Control.Applicative
18import Control.Monad
17 19
18import Data.Metrology 20import Data.Metrology
19import Data.Metrology.TH 21import Data.Metrology.TH
@@ -42,9 +44,6 @@ declareDerivedUnit "Year" [t| Day |] 365.25 Nothing
42 44
43type Time = MkQu_DLN D.Time DefaultLCSU Fixed.Pico 45type Time = MkQu_DLN D.Time DefaultLCSU Fixed.Pico
44 46
45data Prefix where
46 Prefix :: forall p. (UnitPrefix p, Show p) => p -> Prefix
47
48instance HasResolution p => AdditiveGroup (Fixed p) where 47instance HasResolution p => AdditiveGroup (Fixed p) where
49 zeroV = 0 48 zeroV = 0
50 (^+^) = (+) 49 (^+^) = (+)
@@ -57,16 +56,16 @@ instance HasResolution p => VectorSpace (Fixed p) where
57 56
58 57
59timeLength :: StringParser s m => m Time 58timeLength :: StringParser s m => m Time
60timeLength = (*^) <$> lexeme rational <*> timeUnit 59timeLength = (*^) <$> lexeme rational <*> timeUnit <?> "Length of time"
61 60
62rational :: forall s m n. (StringParser s m, Fractional n, Num n) => m n 61rational :: forall s m n. (StringParser s m, Fractional n, Num n) => m n
63rational = combine <$> some digitChar <*> option [] (char '.' *> many digitChar) 62rational = combine <$> some digitChar <*> option [] (char '.' *> many digitChar) <?> "Decimal number"
64 where 63 where
65 combine :: [Char] -> [Char] -> n 64 combine :: [Char] -> [Char] -> n
66 combine (map asN -> whole) (map asN -> fractional) 65 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 66 = foldl' (\i l -> i * 10 + l) 0 whole + (foldr' (\h t -> h + t / 10) 0 fractional) / 10
68 asN :: Char -> n 67 asN :: Char -> n
69 asN c = fromIntegral $ ((-) `on` fromEnum) c '0' 68 asN c = fromIntegral $ fromEnum c - fromEnum '0'
70 69
71timeUnit :: StringParser s m => m Time 70timeUnit :: StringParser s m => m Time
72timeUnit = label "Unit of time" . choice $ 71timeUnit = label "Unit of time" . choice $
@@ -95,15 +94,28 @@ timeUnit = label "Unit of time" . choice $
95 , 1 % Year <$ choice [ string' "years" 94 , 1 % Year <$ choice [ string' "years"
96 , string' "year" 95 , string' "year"
97 ] 96 ]
98 ] ++ 97 , option 1 siPrefix <**> choice [ (% Second) <$ string "s"
99 [ (% Second) <$> option 1 siPrefix <* string "s" 98 , (% Hour ) <$ string "h"
100 , (% Hour) <$> option 1 siPrefix <* string "h" 99 , (% Day ) <$ string "d"
101 , (% Day) <$> option 1 siPrefix <* string "d" 100 , (% Year ) <$ choice [ string "a", string' "yr", string' "yrs" ]
102 , (% Year) <$> option 1 siPrefix <* choice [ string "a", string "yr", string "yrs" ] 101 ]
103 ] 102 ]
104 103
104
105data Prefix where
106 Prefix :: forall p. ParseablePrefix p => p -> Prefix
107
108class UnitPrefix a => ParseablePrefix a where
109 parser :: StringParser s m => a -> m ()
110
111instance {-# OVERLAPPABLE #-} (UnitPrefix a, Show a) => ParseablePrefix a where
112 parser = void . string . show
113
114instance ParseablePrefix Micro where
115 parser _ = void $ choice [ string "ยต", string "u" ]
116
105siPrefix :: (StringParser s m, Fractional n) => m n 117siPrefix :: (StringParser s m, Fractional n) => m n
106siPrefix = label "SI prefix" . choice $ map (\(Prefix p) -> multiplier p <$ string (show p)) 118siPrefix = label "SI prefix" . choice $ map (\(Prefix p) -> multiplier p <$ parser p)
107 [ Prefix Deca, Prefix Hecto, Prefix Kilo, Prefix Mega, Prefix Giga 119 [ Prefix Deca, Prefix Hecto, Prefix Kilo, Prefix Mega, Prefix Giga
108 , Prefix Tera, Prefix Peta, Prefix Exa, Prefix Zetta, Prefix Yotta 120 , Prefix Tera, Prefix Peta, Prefix Exa, Prefix Zetta, Prefix Yotta
109 , Prefix Deci, Prefix Centi, Prefix Milli, Prefix Micro, Prefix Nano 121 , Prefix Deci, Prefix Centi, Prefix Milli, Prefix Micro, Prefix Nano