summaryrefslogtreecommitdiff
path: root/src/Trivmix
diff options
context:
space:
mode:
Diffstat (limited to 'src/Trivmix')
-rw-r--r--src/Trivmix/Types.hs90
1 files changed, 90 insertions, 0 deletions
diff --git a/src/Trivmix/Types.hs b/src/Trivmix/Types.hs
new file mode 100644
index 0000000..66accdf
--- /dev/null
+++ b/src/Trivmix/Types.hs
@@ -0,0 +1,90 @@
1{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
2
3module Trivmix.Types
4 ( Level
5 , toFloat
6 , Adjustment(..)
7 , doAdjustment
8 , module Data.Default
9 ) where
10
11import Data.Fixed
12import Data.CaseInsensitive ( CI )
13import qualified Data.CaseInsensitive as CI
14
15import Data.Default
16
17import Data.Function (on)
18
19data Level = Lin Float | DB Float
20
21instance Num Level where
22 (+) = asFloat (+)
23 (-) = asFloat (-)
24 (*) = asFloat (*)
25 abs = Lin . abs . toFloat
26 signum = Lin . signum . toFloat
27 fromInteger = Lin . fromInteger
28
29asFloat :: (Float -> Float -> Float) -> Level -> Level -> Level
30asFloat f (Lin x) (Lin y) = Lin $ f x y
31asFloat f x y = DB $ (f `on` toFloat) x y
32
33toFloat :: Level -> Float
34toFloat (Lin x) = x
35toFloat (DB x) = x
36
37withPrec :: (Num a, RealFrac a, HasResolution b) => a -> Fixed b
38withPrec x = withResolution $ \p' -> MkFixed $ toInteger $ round $ x * (fromInteger p')
39
40withType :: (p a -> f a) -> f a
41withType f = f undefined
42
43withResolution :: (HasResolution a) => (Integer -> f a) -> f a
44withResolution f = withType (f . resolution)
45
46instance Show Level where
47 show (Lin x) = show x
48 show (DB x) = (show $ (withPrec x' :: Milli)) ++ "dB"
49 where
50 x' = 20 * (logBase 10 x)
51
52instance Read Level where
53 readsPrec i = map toL . readsPrec i
54 where
55 toL :: (Float, String) -> (Level, String)
56 toL (f, str)
57 | ((==) `on` CI.mk) prec unit = (DB $ 10 ** (0.05 * f), rest)
58 | otherwise = (Lin f, str)
59 where
60 prec = take lU str
61 rest = drop lU str
62 unit = "dB"
63 lU = length unit
64
65instance Eq Level where
66 (Lin a) == (Lin b) = a == b
67 (Lin a) == (DB b) = a == b
68 (DB a) == (Lin b) = a == b
69 (DB a) == (DB b) = a == b
70
71instance Default Level where
72 def = Lin 0
73
74data Adjustment a = Set a
75 | Add a
76 | Sub a
77 deriving (Show, Eq)
78
79class Adjustable a where
80 add :: a -> a -> a
81 sub :: a -> a -> a
82
83instance Num a => Adjustable a where
84 add = (+)
85 sub = (-)
86
87doAdjustment :: Adjustable a => a -> Adjustment a -> a
88doAdjustment _ (Set y) = y
89doAdjustment x (Add y) = add x y
90doAdjustment x (Sub y) = sub x y