module Music.Theory.Math where
import Data.Maybe
import Data.Ratio
import Numeric
type R = Double
integral_and_fractional_parts :: (Integral i, RealFrac t) => t -> (i,t)
integral_and_fractional_parts n =
if n >= 0
then let n' = floor n in (n',n fromIntegral n')
else let n' = ceiling n in (n',n fromIntegral n')
integer_and_fractional_parts :: RealFrac t => t -> (Integer,t)
integer_and_fractional_parts = integral_and_fractional_parts
fractional_part :: RealFrac a => a -> a
fractional_part = snd . integer_and_fractional_parts
sawtooth_wave :: RealFrac a => a -> a
sawtooth_wave n = n fromInteger (floor n)
rational_pp :: (Show a,Integral a) => Ratio a -> String
rational_pp r =
let n = numerator r
d = denominator r
in if d == 1
then show n
else concat [show n,"/",show d]
ratio_pp :: Rational -> String
ratio_pp r =
let (n,d) = rational_nd r
in concat [show n,":",show d]
rational_simplifies :: Integral a => (a,a) -> Bool
rational_simplifies (n,d) = gcd n d /= 1
rational_nd :: Integral t => Ratio t -> (t,t)
rational_nd r = (numerator r,denominator r)
rational_whole :: Integral a => Ratio a -> Maybe a
rational_whole r = if denominator r == 1 then Just (numerator r) else Nothing
rational_whole_err :: Integral a => Ratio a -> a
rational_whole_err = fromMaybe (error "rational_whole") . rational_whole
realfloat_pp :: RealFloat a => Int -> a -> String
realfloat_pp k n = showFFloat (Just k) n ""
float_pp :: Int -> Float -> String
float_pp = realfloat_pp
double_pp :: Int -> Double -> String
double_pp = realfloat_pp
num_diff_str :: (Num a, Ord a, Show a) => a -> String
num_diff_str n =
case compare n 0 of
LT -> '-' : show (abs n)
EQ -> ""
GT -> '+' : show n