module Sound.Sc3.Ugen.Constant where
import Sound.Sc3.Ugen.Brackets
data Constant = Constant
{ Constant -> Double
constantValue :: Double
, Constant -> Brackets
constantBrackets :: Brackets
}
deriving (Eq Constant
Eq Constant =>
(Constant -> Constant -> Ordering)
-> (Constant -> Constant -> Bool)
-> (Constant -> Constant -> Bool)
-> (Constant -> Constant -> Bool)
-> (Constant -> Constant -> Bool)
-> (Constant -> Constant -> Constant)
-> (Constant -> Constant -> Constant)
-> Ord Constant
Constant -> Constant -> Bool
Constant -> Constant -> Ordering
Constant -> Constant -> Constant
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Constant -> Constant -> Ordering
compare :: Constant -> Constant -> Ordering
$c< :: Constant -> Constant -> Bool
< :: Constant -> Constant -> Bool
$c<= :: Constant -> Constant -> Bool
<= :: Constant -> Constant -> Bool
$c> :: Constant -> Constant -> Bool
> :: Constant -> Constant -> Bool
$c>= :: Constant -> Constant -> Bool
>= :: Constant -> Constant -> Bool
$cmax :: Constant -> Constant -> Constant
max :: Constant -> Constant -> Constant
$cmin :: Constant -> Constant -> Constant
min :: Constant -> Constant -> Constant
Ord, Constant -> Constant -> Bool
(Constant -> Constant -> Bool)
-> (Constant -> Constant -> Bool) -> Eq Constant
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constant -> Constant -> Bool
== :: Constant -> Constant -> Bool
$c/= :: Constant -> Constant -> Bool
/= :: Constant -> Constant -> Bool
Eq, ReadPrec [Constant]
ReadPrec Constant
Int -> ReadS Constant
ReadS [Constant]
(Int -> ReadS Constant)
-> ReadS [Constant]
-> ReadPrec Constant
-> ReadPrec [Constant]
-> Read Constant
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Constant
readsPrec :: Int -> ReadS Constant
$creadList :: ReadS [Constant]
readList :: ReadS [Constant]
$creadPrec :: ReadPrec Constant
readPrec :: ReadPrec Constant
$creadListPrec :: ReadPrec [Constant]
readListPrec :: ReadPrec [Constant]
Read, Int -> Constant -> ShowS
[Constant] -> ShowS
Constant -> String
(Int -> Constant -> ShowS)
-> (Constant -> String) -> ([Constant] -> ShowS) -> Show Constant
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constant -> ShowS
showsPrec :: Int -> Constant -> ShowS
$cshow :: Constant -> String
show :: Constant -> String
$cshowList :: [Constant] -> ShowS
showList :: [Constant] -> ShowS
Show)
fractionPart :: Double -> Double
fractionPart :: Double -> Double
fractionPart = (Integer, Double) -> Double
forall a b. (a, b) -> b
snd ((Integer, Double) -> Double)
-> (Double -> (Integer, Double)) -> Double -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Double -> (Integer, Double)
forall b. Integral b => Double -> (b, Double)
forall a b. (RealFrac a, Integral b) => a -> (b, a)
properFraction :: Double -> (Integer, Double))
constantIsInteger :: Constant -> Bool
constantIsInteger :: Constant -> Bool
constantIsInteger (Constant Double
n Brackets
_) = Double -> Double
fractionPart Double
n Double -> Double -> Bool
forall a. Eq a => a -> a -> Bool
== Double
0