hmt-0.16: Haskell Music Theory

Safe HaskellSafe
LanguageHaskell98

Music.Theory.Math

Contents

Description

Math functions.

Synopsis

Documentation

type R = Double Source #

Real (alias for Double).

integer_and_fractional_parts :: RealFrac t => t -> (Integer, t) Source #

Type specialised.

fractional_part :: RealFrac a => a -> a Source #

http://reference.wolfram.com/mathematica/ref/FractionalPart.html

import Sound.SC3.Plot {- hsc3-plot -}
plotTable1 (map fractional_part [-2.0,-1.99 .. 2.0])

real_floor_int :: Real r => r -> Int Source #

Type specialised real_floor.

real_round_int :: Real r => r -> Int Source #

Type specialised real_round.

zero_to_precision :: Real r => Int -> r -> Bool Source #

Is r zero to k decimal places.

map (flip zero_to_precision 0.00009) [4,5] == [True,False]
zero_to_precision 4 1.00009 == False

whole_to_precision :: Real r => Int -> r -> Bool Source #

Is r whole to k decimal places.

map (flip whole_to_precision 1.00009) [4,5] == [True,False]

sawtooth_wave :: RealFrac a => a -> a Source #

http://reference.wolfram.com/mathematica/ref/SawtoothWave.html

plotTable1 (map sawtooth_wave [-2.0,-1.99 .. 2.0])

rational_pp :: (Show a, Integral a) => Ratio a -> String Source #

Pretty printer for Rational that elides denominators of 1.

map rational_pp [1,3/2,2] == ["1","3/2","2"]

ratio_pp :: Rational -> String Source #

Pretty print ratio as : separated integers.

map ratio_pp [1,3/2,2] == ["1:1","3:2","2:1"]

rational_simplifies :: Integral a => (a, a) -> Bool Source #

Predicate that is true if n/d can be simplified, ie. where gcd of n and d is not 1.

let r = [False,True,False]
in map rational_simplifies [(2,3),(4,6),(5,7)] == r

rational_nd :: Ratio t -> (t, t) Source #

numerator and denominator of rational.

rational_whole :: Integral a => Ratio a -> Maybe a Source #

Rational as a whole number, or Nothing.

rational_whole_err :: Integral a => Ratio a -> a Source #

Erroring variant.

show_rational_decimal :: Int -> Rational -> String Source #

Show rational to n decimal places.

let r = approxRational pi 1e-100
r == 884279719003555 / 281474976710656
show_rational_decimal 12 r == "3.141592653590"

realfloat_pp :: RealFloat a => Int -> a -> String Source #

Variant of showFFloat. The Show instance for floats resorts to exponential notation very readily.

[show 0.01,realfloat_pp 2 0.01] == ["1.0e-2","0.01"]

real_pp :: Real t => Int -> t -> String Source #

Show r as float to k places.

float_pp :: Int -> Float -> String Source #

Type specialised realfloat_pp.

double_pp :: Int -> Double -> String Source #

Type specialised realfloat_pp.

num_diff_str :: (Num a, Ord a, Show a) => a -> String Source #

Show only positive and negative values, always with sign.

map num_diff_str [-2,-1,0,1,2] == ["-2","-1","","+1","+2"]
map show [-2,-1,0,1,2] == ["-2","-1","0","1","2"]

floor_f :: (RealFrac a, Num b) => a -> b Source #

round_to :: RealFrac n => n -> n -> n Source #

Round b to nearest multiple of a.

map (round_to 0.25) [0,0.1 .. 1] == [0.0,0.0,0.25,0.25,0.5,0.5,0.5,0.75,0.75,1.0,1.0]
map (round_to 25) [0,10 .. 100] == [0,0,25,25,50,50,50,75,75,100,100]

One-indexed

oi_mod :: Integral a => a -> a -> a Source #

One-indexed mod function.

map (`oi_mod` 5) [1..10] == [1,2,3,4,5,1,2,3,4,5]

oi_divMod :: Integral t => t -> t -> (t, t) Source #

One-indexed divMod function.

map (`oi_divMod` 5) [1,3 .. 9] == [(0,1),(0,3),(0,5),(1,2),(1,4)]

I = integral

i_square_root :: Integral t => t -> t Source #

Integral square root function.

map i_square_root [0,1,4,9,16,25,36,49,64,81,100] == [0 .. 10]
map i_square_root [4 .. 16] == [2,2,2,2,2,3,3,3,3,3,3,3,4]

Interval

in_open_interval :: Ord a => (a, a) -> a -> Bool Source #

(0,1) = {x | 0 < x < 1}

in_closed_interval :: Ord a => (a, a) -> a -> Bool Source #

0,1
= {x | 0 ≤ x ≤ 1}

in_left_half_open_interval :: Ord a => (a, a) -> a -> Bool Source #

(p,q] (0,1] = {x | 0 < x ≤ 1}

in_right_half_open_interval :: Ord a => (a, a) -> a -> Bool Source #

[p,q) [0,1) = {x | 0 ≤ x < 1}