module Music.Theory.Clef where
import Music.Theory.Pitch
import Music.Theory.Pitch.Name
data Clef_Type = Bass | Tenor | Alto | Treble | Percussion
deriving (Clef_Type -> Clef_Type -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Clef_Type -> Clef_Type -> Bool
$c/= :: Clef_Type -> Clef_Type -> Bool
== :: Clef_Type -> Clef_Type -> Bool
$c== :: Clef_Type -> Clef_Type -> Bool
Eq,Eq Clef_Type
Clef_Type -> Clef_Type -> Bool
Clef_Type -> Clef_Type -> Ordering
Clef_Type -> Clef_Type -> Clef_Type
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
min :: Clef_Type -> Clef_Type -> Clef_Type
$cmin :: Clef_Type -> Clef_Type -> Clef_Type
max :: Clef_Type -> Clef_Type -> Clef_Type
$cmax :: Clef_Type -> Clef_Type -> Clef_Type
>= :: Clef_Type -> Clef_Type -> Bool
$c>= :: Clef_Type -> Clef_Type -> Bool
> :: Clef_Type -> Clef_Type -> Bool
$c> :: Clef_Type -> Clef_Type -> Bool
<= :: Clef_Type -> Clef_Type -> Bool
$c<= :: Clef_Type -> Clef_Type -> Bool
< :: Clef_Type -> Clef_Type -> Bool
$c< :: Clef_Type -> Clef_Type -> Bool
compare :: Clef_Type -> Clef_Type -> Ordering
$ccompare :: Clef_Type -> Clef_Type -> Ordering
Ord,Int -> Clef_Type -> ShowS
[Clef_Type] -> ShowS
Clef_Type -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Clef_Type] -> ShowS
$cshowList :: [Clef_Type] -> ShowS
show :: Clef_Type -> String
$cshow :: Clef_Type -> String
showsPrec :: Int -> Clef_Type -> ShowS
$cshowsPrec :: Int -> Clef_Type -> ShowS
Show)
data Clef i = Clef {forall i. Clef i -> Clef_Type
clef_t :: Clef_Type
,forall i. Clef i -> i
clef_octave :: i}
deriving (Clef i -> Clef i -> Bool
forall i. Eq i => Clef i -> Clef i -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Clef i -> Clef i -> Bool
$c/= :: forall i. Eq i => Clef i -> Clef i -> Bool
== :: Clef i -> Clef i -> Bool
$c== :: forall i. Eq i => Clef i -> Clef i -> Bool
Eq,Clef i -> Clef i -> Bool
Clef i -> Clef i -> Ordering
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
forall {i}. Ord i => Eq (Clef i)
forall i. Ord i => Clef i -> Clef i -> Bool
forall i. Ord i => Clef i -> Clef i -> Ordering
forall i. Ord i => Clef i -> Clef i -> Clef i
min :: Clef i -> Clef i -> Clef i
$cmin :: forall i. Ord i => Clef i -> Clef i -> Clef i
max :: Clef i -> Clef i -> Clef i
$cmax :: forall i. Ord i => Clef i -> Clef i -> Clef i
>= :: Clef i -> Clef i -> Bool
$c>= :: forall i. Ord i => Clef i -> Clef i -> Bool
> :: Clef i -> Clef i -> Bool
$c> :: forall i. Ord i => Clef i -> Clef i -> Bool
<= :: Clef i -> Clef i -> Bool
$c<= :: forall i. Ord i => Clef i -> Clef i -> Bool
< :: Clef i -> Clef i -> Bool
$c< :: forall i. Ord i => Clef i -> Clef i -> Bool
compare :: Clef i -> Clef i -> Ordering
$ccompare :: forall i. Ord i => Clef i -> Clef i -> Ordering
Ord,Int -> Clef i -> ShowS
forall i. Show i => Int -> Clef i -> ShowS
forall i. Show i => [Clef i] -> ShowS
forall i. Show i => Clef i -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Clef i] -> ShowS
$cshowList :: forall i. Show i => [Clef i] -> ShowS
show :: Clef i -> String
$cshow :: forall i. Show i => Clef i -> String
showsPrec :: Int -> Clef i -> ShowS
$cshowsPrec :: forall i. Show i => Int -> Clef i -> ShowS
Show)
clef_range :: Clef_Type -> Maybe (Pitch,Pitch)
clef_range :: Clef_Type -> Maybe (Pitch, Pitch)
clef_range Clef_Type
c =
case Clef_Type
c of
Clef_Type
Bass -> forall a. a -> Maybe a
Just (Pitch
f2,Pitch
b3)
Clef_Type
Tenor -> forall a. a -> Maybe a
Just (Pitch
c3,Pitch
f4)
Clef_Type
Alto -> forall a. a -> Maybe a
Just (Pitch
e3,Pitch
a4)
Clef_Type
Treble -> forall a. a -> Maybe a
Just (Pitch
d4,Pitch
g5)
Clef_Type
Percussion -> forall a. Maybe a
Nothing
clef_suggest :: Integral i => Pitch -> Clef i
clef_suggest :: forall i. Integral i => Pitch -> Clef i
clef_suggest Pitch
p | Pitch
p forall a. Ord a => a -> a -> Bool
< Pitch
f1 = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Bass (-i
2)
| Pitch
p forall a. Ord a => a -> a -> Bool
< Pitch
f2 = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Bass (-i
1)
| Pitch
p forall a. Ord a => a -> a -> Bool
< Pitch
b3 = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Bass i
0
| Pitch
p forall a. Ord a => a -> a -> Bool
< Pitch
g5 = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Treble i
0
| Pitch
p forall a. Ord a => a -> a -> Bool
< Pitch
g6 = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Treble i
1
| Bool
otherwise = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
Treble i
2
clef_zero :: Integral i => Clef i -> Clef i
clef_zero :: forall i. Integral i => Clef i -> Clef i
clef_zero (Clef Clef_Type
c_t i
_) = forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
c_t i
0
clef_restrict :: Integral i => i -> Clef i -> Clef i
clef_restrict :: forall i. Integral i => i -> Clef i -> Clef i
clef_restrict i
r (Clef Clef_Type
c_t i
n) =
let n' :: i
n' = if forall a. Num a => a -> a
abs i
n forall a. Ord a => a -> a -> Bool
> i
r then forall a. Num a => a -> a
signum i
n forall a. Num a => a -> a -> a
* i
r else i
n
in forall i. Clef_Type -> i -> Clef i
Clef Clef_Type
c_t i
n'