summaryrefslogtreecommitdiff
path: root/src/Trivmix/Types.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Trivmix/Types.hs')
-rw-r--r--src/Trivmix/Types.hs79
1 files changed, 42 insertions, 37 deletions
diff --git a/src/Trivmix/Types.hs b/src/Trivmix/Types.hs
index a6a41b9..f01e023 100644
--- a/src/Trivmix/Types.hs
+++ b/src/Trivmix/Types.hs
@@ -1,7 +1,8 @@
1{-# LANGUAGE FlexibleInstances, UndecidableInstances #-} 1{-# LANGUAGE FlexibleInstances, UndecidableInstances, ViewPatterns, TemplateHaskell, PatternGuards #-}
2 2
3module Trivmix.Types 3module Trivmix.Types
4 ( Level 4 ( Level'
5 , Level(Lin), toLin
5 , toFloat 6 , toFloat
6 , asFloat 7 , asFloat
7 , Adjustment(..) 8 , Adjustment(..)
@@ -13,27 +14,37 @@ import Data.Fixed
13import Data.CaseInsensitive ( CI ) 14import Data.CaseInsensitive ( CI )
14import qualified Data.CaseInsensitive as CI 15import qualified Data.CaseInsensitive as CI
15 16
17import Text.ParserCombinators.ReadPrec
18import Control.Applicative
19import Control.Monad
20
16import Data.Default 21import Data.Default
17 22
18import Data.Function (on) 23import Data.Function (on)
19 24
20data Level = Lin Float | DB Float 25import Refined
21 26
22instance Num Level where 27type Level' = Refined NonNegative Float
23 (+) = asFloat (+) 28data Level = Lin { toLin :: Level' } | DB { toLin :: Level' }
24 (-) = asFloat (-)
25 (*) = asFloat (*)
26 abs = Lin . abs . toFloat
27 signum = Lin . signum . toFloat
28 fromInteger = Lin . fromInteger
29 29
30asFloat :: (Float -> Float -> Float) -> Level -> Level -> Level 30instance Num Level where
31asFloat f (Lin x) (Lin y) = Lin $ f x y 31 (+) = fmap (either error id) . asFloat (+)
32asFloat f x y = DB $ (f `on` toFloat) x y 32 (-) = fmap (either error id) . asFloat (-)
33 (*) = fmap (either error id) . asFloat (*)
34 abs = Lin . toLin
35 signum = Lin . either error id . refine . signum . toFloat
36 fromInteger = Lin . either error id . refine . fromInteger
37
38asFloat :: (Float -> Float -> Float) -> Level -> Level -> Either String Level
39asFloat ((`on` toFloat) -> f) x y = toLvl <$> refine (f x y)
40 where
41 toLvl
42 | DB _ <- x = DB
43 | DB _ <- y = DB
44 | otherwise = Lin
33 45
34toFloat :: Level -> Float 46toFloat :: Level -> Float
35toFloat (Lin x) = x 47toFloat = unrefine . toLin
36toFloat (DB x) = x
37 48
38withPrec :: (Num a, RealFrac a, HasResolution b) => a -> Fixed b 49withPrec :: (Num a, RealFrac a, HasResolution b) => a -> Fixed b
39withPrec x = withResolution $ \p' -> MkFixed $ toInteger $ round $ x * (fromInteger p') 50withPrec x = withResolution $ \p' -> MkFixed $ toInteger $ round $ x * (fromInteger p')
@@ -44,39 +55,33 @@ withType f = f undefined
44withResolution :: (HasResolution a) => (Integer -> f a) -> f a 55withResolution :: (HasResolution a) => (Integer -> f a) -> f a
45withResolution f = withType (f . resolution) 56withResolution f = withType (f . resolution)
46 57
47linToDb :: Float -> Float 58linToDb :: Level' -> Float
48linToDb x = 20 * (logBase 10 x) 59linToDb (unrefine -> x) = 20 * (logBase 10 x)
49 60
50dBToLin :: Float -> Float 61dBToLin :: Float -> Level'
51dBToLin x = 10 ** (0.05 * x) 62dBToLin x = either error id . refine $ 10 ** (0.05 * x)
52 63
53instance Show Level where 64instance Show Level where
54 show (Lin x) = show x 65 show (Lin x) = show x
55 show (DB x) = (show $ (withPrec x' :: Milli)) ++ "dB" 66 show (DB (linToDb -> x)) = (show $ (withPrec x :: Milli)) ++ "dB"
56 where
57 x' = linToDb x
58 67
59instance Read Level where 68instance Read Level where
60 readsPrec i = map toL . readsPrec i 69 readsPrec = readPrec_to_S $ parseDb <|> parseLin
61 where 70 where
62 toL :: (Float, String) -> (Level, String) 71 parseDb = do
63 toL (f, str) 72 db <- readS_to_Prec readsPrec
64 | ((==) `on` CI.mk) prec unit = (DB $ dBToLin f, rest) 73 let
65 | otherwise = (Lin f, str) 74 unit@(length -> lU) = "dB"
66 where 75 unit' <- forM [1..lU] $ const get
67 prec = take lU str 76 guard $ ((==) `on` CI.mk) unit unit'
68 rest = drop lU str 77 return . DB $ dBToLin db
69 unit = "dB" 78 parseLin = Lin <$> readS_to_Prec readsPrec
70 lU = length unit
71 79
72instance Eq Level where 80instance Eq Level where
73 (Lin a) == (Lin b) = a == b 81 (==) = (==) `on` toLin
74 (Lin a) == (DB b) = a == b
75 (DB a) == (Lin b) = a == b
76 (DB a) == (DB b) = a == b
77 82
78instance Default Level where 83instance Default Level where
79 def = Lin 0 84 def = Lin $$(refineTH 0)
80 85
81data Adjustment a = Set a 86data Adjustment a = Set a
82 | Add a 87 | Add a