hmt-0.20: Haskell Music Theory
Safe HaskellSafe-Inferred
LanguageHaskell2010

Music.Theory.Gamelan

Description

Gamelan instruments and pitch structures.

Synopsis

Documentation

fromJust_err :: String -> Maybe a -> a Source #

fromJust with error message.

Gamelan

data Instrument_Family Source #

Enumeration of gamelan instrument families.

Constructors

Bonang 
Gambang 
Gender 
Gong 
Saron 

Instances

Instances details
Bounded Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

Enum Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

Read Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

Show Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

Eq Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

Ord Instrument_Family Source # 
Instance details

Defined in Music.Theory.Gamelan

data Instrument_Name Source #

Enumeration of Gamelan instruments.

Constructors

Bonang_Barung

Bonang Barung (horizontal gong, middle)

Bonang_Panerus

Bonang Panerus (horizontal gong, high)

Gambang_Kayu

Gambang Kayu (wooden key&resonator)

Gender_Barung

Gender Barung (key&resonator, middle)

Gender_Panerus

Gender Panembung (key&resonator, high)

Gender_Panembung

Gender Panembung, Slenthem (key&resonator, low)

Gong_Ageng

Gong Ageng (hanging gong, low)

Gong_Suwukan

Gong Suwukan (hanging gong, middle)

Kempul

Kempul (hanging gong, middle)

Kempyang

Kempyang (horizontal gong, high)

Kenong

Kenong (horizontal gong, low)

Ketuk

Ketuk, Kethuk (horizontal gong, middle)

Saron_Barung

Saron Barung, Saron (key, middle)

Saron_Demung

Saron Demung, Demung (key, low)

Saron_Panerus

Saron Panerus, Peking (key, high)

Instances

Instances details
Bounded Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

Enum Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

Read Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

Show Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

Eq Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

Ord Instrument_Name Source # 
Instance details

Defined in Music.Theory.Gamelan

data Scale Source #

Enumeration of Gamelan scales.

Constructors

Pelog 
Slendro 

Instances

Instances details
Enum Scale Source # 
Instance details

Defined in Music.Theory.Gamelan

Read Scale Source # 
Instance details

Defined in Music.Theory.Gamelan

Show Scale Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

showsPrec :: Int -> Scale -> ShowS #

show :: Scale -> String #

showList :: [Scale] -> ShowS #

Eq Scale Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

(==) :: Scale -> Scale -> Bool #

(/=) :: Scale -> Scale -> Bool #

Ord Scale Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

compare :: Scale -> Scale -> Ordering #

(<) :: Scale -> Scale -> Bool #

(<=) :: Scale -> Scale -> Bool #

(>) :: Scale -> Scale -> Bool #

(>=) :: Scale -> Scale -> Bool #

max :: Scale -> Scale -> Scale #

min :: Scale -> Scale -> Scale #

type Octave = Integer Source #

Octaves are zero-indexed and may be negative.

type Degree = Integer Source #

Degrees are one-indexed.

type Frequency = Double Source #

Frequency in hertz.

type Annotation = String Source #

A text annotation.

data Pitch Source #

Constructors

Pitch 

Instances

Instances details
Show Pitch Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

Eq Pitch Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

(==) :: Pitch -> Pitch -> Bool #

(/=) :: Pitch -> Pitch -> Bool #

Ord Pitch Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

compare :: Pitch -> Pitch -> Ordering #

(<) :: Pitch -> Pitch -> Bool #

(<=) :: Pitch -> Pitch -> Bool #

(>) :: Pitch -> Pitch -> Bool #

(>=) :: Pitch -> Pitch -> Bool #

max :: Pitch -> Pitch -> Pitch #

min :: Pitch -> Pitch -> Pitch #

pitch_pp_ascii :: Pitch -> String Source #

Octaves are written as repeated - or +, degrees are printed ordinarily.

map pitch_pp_ascii (zipWith Pitch [-2 .. 2] [1 .. 5]) == ["--1","-2","3","+4","++5"]

data Note Source #

Constructors

Note 

Instances

Instances details
Show Note Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Eq Note Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

(==) :: Note -> Note -> Bool #

(/=) :: Note -> Note -> Bool #

Ord Note Source #

Orderable if scales are equal.

Instance details

Defined in Music.Theory.Gamelan

Methods

compare :: Note -> Note -> Ordering #

(<) :: Note -> Note -> Bool #

(<=) :: Note -> Note -> Bool #

(>) :: Note -> Note -> Bool #

(>=) :: Note -> Note -> Bool #

max :: Note -> Note -> Note #

min :: Note -> Note -> Note #

note_compare :: Note -> Note -> Ordering Source #

It is an error to compare notes from different scales.

note_range_elem :: Scale -> Pitch -> Pitch -> [Note] Source #

Ascending sequence of Note for Scale from p1 to p2 inclusive.

note_gamut_elem :: Note -> Note -> [Note] Source #

Ascending sequence of Note from n1 to n2 inclusive.

note_gamut_elem (Note Slendro (Pitch 0 5)) (Note Slendro (Pitch 1 2))

data Tone t Source #

Instances

Instances details
Show t => Show (Tone t) Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

showsPrec :: Int -> Tone t -> ShowS #

show :: Tone t -> String #

showList :: [Tone t] -> ShowS #

Eq t => Eq (Tone t) Source # 
Instance details

Defined in Music.Theory.Gamelan

Methods

(==) :: Tone t -> Tone t -> Bool #

(/=) :: Tone t -> Tone t -> Bool #

Eq t => Ord (Tone t) Source #

Orderable if frequency is given.

Instance details

Defined in Music.Theory.Gamelan

Methods

compare :: Tone t -> Tone t -> Ordering #

(<) :: Tone t -> Tone t -> Bool #

(<=) :: Tone t -> Tone t -> Bool #

(>) :: Tone t -> Tone t -> Bool #

(>=) :: Tone t -> Tone t -> Bool #

max :: Tone t -> Tone t -> Tone t #

min :: Tone t -> Tone t -> Tone t #

plain_tone :: Instrument_Name -> Scale -> Octave -> Degree -> Tone t Source #

Constructor for Tone without frequency or annotation.

tone_equivalent :: Tone t -> Tone t -> Bool Source #

Tones are considered equivalent if they have the same Instrument_Name and Note.

tone_24et_fmidi :: Tone t -> Rational Source #

Fractional (rational) 24-et midi note number of Tone.

tone_12et_fmidi :: Tone t -> Rational Source #

Fractional (rational) 24-et midi note number of Tone.

type Tone_Subset = ([Instrument_Family], [Scale]) Source #

Specify subset as list of families and scales.

tone_subset :: Tone_Subset -> Tone_Set t -> Tone_Set t Source #

Extract subset of Tone_Set.

type Tone_Set t = [Tone t] Source #

tone_set_near_frequency :: Tone_Set t -> Cents -> Frequency -> Tone_Set t Source #

Given a Tone_Set, find those Tones that are within Cents of Frequency.

tone_compare_frequency :: Tone t -> Tone t -> Ordering Source #

Compare Tones by frequency. Tones without frequency compare as if at frequency 0.

map_maybe_uniform :: (a -> Maybe b) -> [a] -> Maybe [b] Source #

If all f of a are Just b, then Just [b], else Nothing.

scale_degrees :: Scale -> [Degree] Source #

Pelog has seven degrees, numbered one to seven. Slendro has five degrees, numbered one to six excluding four.

map scale_degrees [Pelog,Slendro] == [[1,2,3,4,5,6,7],[1,2,3,5,6]]

degree_index :: Scale -> Degree -> Maybe Int Source #

Zero based index of scale degree, or Nothing.

degree_index Slendro 4 == Nothing
degree_index Pelog 4 == Just 3

Tone set