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

Music.Theory.Time.Bel1990.R

Description

Bel(R) is a simplified form of the Bel notation described in:

For details see http://rohandrape.net/?t=hmt-texts.

Synopsis

Bel

data Par_Mode Source #

Types of Par nodes.

Instances

Instances details
Show Par_Mode Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

Eq Par_Mode Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

par_mode_brackets :: Par_Mode -> (String, String) Source #

The different Par modes are indicated by bracket types.

par_mode_kind :: (String, String) -> Par_Mode Source #

Inverse of par_mode_brackets

type Tempo = Rational Source #

Tempo is rational. The duration of a Term is the reciprocal of the Tempo that is in place at the Term.

data Term a Source #

Terms are the leaf nodes of the temporal structure.

Constructors

Value a 
Rest 
Continue 

Instances

Instances details
Show a => Show (Term a) Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

Methods

showsPrec :: Int -> Term a -> ShowS #

show :: Term a -> String #

showList :: [Term a] -> ShowS #

Eq a => Eq (Term a) Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

Methods

(==) :: Term a -> Term a -> Bool #

(/=) :: Term a -> Term a -> Bool #

term_value :: Term t -> Maybe t Source #

Value of Term, else Nothing

data Bel a Source #

Recursive temporal structure.

Constructors

Node (Term a)

Leaf node

Iso (Bel a)

Isolate

Seq (Bel a) (Bel a)

Sequence

Par Par_Mode (Bel a) (Bel a)

Parallel

Mul Tempo

Tempo multiplier

Instances

Instances details
Show a => Show (Bel a) Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

Methods

showsPrec :: Int -> Bel a -> ShowS #

show :: Bel a -> String #

showList :: [Bel a] -> ShowS #

Eq a => Eq (Bel a) Source # 
Instance details

Defined in Music.Theory.Time.Bel1990.R

Methods

(==) :: Bel a -> Bel a -> Bool #

(/=) :: Bel a -> Bel a -> Bool #

par_of :: Par_Mode -> [Bel a] -> Bel a Source #

Given a Par mode, generate either: 1. an Iso, 2. a Par, 3. a series of nested Par.

bel_pp :: (a -> String) -> Bel a -> String Source #

Pretty printer for Bel, given pretty printer for the term type. Note this does not write nested Par nodes in their simplified form.

par_analyse :: Tempo -> Par_Mode -> Bel a -> Bel a -> (Rational, Rational, Rational) Source #

Analyse a Par node giving (duration,LHS-tempo-*,RHS-tempo-*).

par_analyse 1 Par_Left (nseq "cd") (nseq "efg") == (2,1,3/2)
par_analyse 1 Par_Right (nseq "cd") (nseq "efg") == (3,2/3,1)
par_analyse 1 Par_Min (nseq "cd") (nseq "efg") == (2,1,3/2)
par_analyse 1 Par_Max (nseq "cd") (nseq "efg") == (3,2/3,1)
par_analyse 1 Par_None (nseq "cd") (nseq "efg") == (3,1,1)

par_dur :: Tempo -> Par_Mode -> Bel a -> Bel a -> Rational Source #

Duration element of par_analyse.

bel_tdur :: Tempo -> Bel a -> (Tempo, Rational) Source #

Calculate final tempo and duration of Bel.

Linearisation

type Time = Rational Source #

Time point.

type Voice = [Char] Source #

Voices are named as a sequence of left and right directions within nested Par structures. l is left and r is right.

type L_St = (Time, Tempo, Voice) Source #

Linear state. Time is the start time of the term. Tempo is the active tempo & therefore the reciprocal of the duration. Voice is the part label.

type L_Term a = (L_St, Term a) Source #

Linear term.

lterm_time :: L_Term a -> Time Source #

Start time of L_Term.

lterm_duration :: L_Term a -> Time Source #

Duration of L_Term (reciprocal of tempo).

lterm_end_time :: L_Term a -> Time Source #

End time of L_Term.

lterm_term :: L_Term t -> Term t Source #

Term of L_Term

lterm_value :: L_Term t -> Maybe t Source #

Value of Term of L_Term

type L_Bel a = [L_Term a] Source #

Linear form of Bel, an ascending sequence of L_Term.

bel_linearise :: L_St -> Bel a -> (L_Bel a, L_St) Source #

Linearise Bel given initial L_St, ascending by construction.

lbel_merge :: L_Bel a -> L_Bel a -> L_Bel a Source #

Merge two ascending L_Bel.

lbel_tempi :: L_Bel a -> [Tempo] Source #

Set of unique Tempo at L_Bel.

lbel_tempo_mul :: Rational -> L_Bel a -> L_Bel a Source #

Multiply Tempo by n, and divide Time by n.

lbel_normalise_multiplier :: L_Bel t -> Rational Source #

The multiplier that will normalise an L_Bel value. After normalisation all start times and durations are integral.

lbel_normalise :: L_Bel a -> L_Bel a Source #

Calculate and apply L_Bel normalisation multiplier.

voice_normalise :: Voice -> Voice Source #

All leftmost voices are re-written to the last non-left turning point.

map voice_normalise ["","l","ll","lll"] == replicate 4 ""
voice_normalise "lllrlrl" == "rlrl"

lbel_voices :: L_Bel a -> [Voice] Source #

Unique Voices at L_Bel.

lbel_duration :: L_Bel a -> Time Source #

The duration of L_Bel.

lbel_lookup :: (Time, Voice) -> L_Bel a -> Maybe (L_Term a) Source #

Locate an L_Term that is active at the indicated Time and in the indicated Voice.

lbel_grid :: L_Bel a -> [[Maybe (Term a)]] Source #

Calculate grid (phase diagram) for L_Bel.

bel_ascii :: Bool -> Bel Char -> String Source #

Bel type phase diagram for Bel of Char. Optionally print whitespace between columns.

Combinators

(~>) :: Bel a -> Bel a -> Bel a Source #

Infix form for Seq.

lseq :: [Bel a] -> Bel a Source #

foldl1 of Seq.

lseq [Node Rest] == Node Rest
lseq [Node Rest,Node Continue] == Seq (Node Rest) (Node Continue)

node :: a -> Bel a Source #

nseq :: [a] -> Bel a Source #

cseq :: String -> Bel Char Source #

Variant of nseq where _ is read as Continue and - as Rest.

par :: Bel a -> Bel a -> Bel a Source #

Par of Par_Max, this is the default Par_Mode.

nrests :: Integral n => n -> Bel a Source #

bel_ascii_pp :: String -> IO () Source #

Run bel_char_parse, and print both bel_char_pp and bel_ascii.

bel_ascii_pp "{i{ab,c[d,oh]e,sr{p,qr}},{jk,ghjkj}}"

Parsing

p_rest :: P (Term a) Source #

Parse Rest Term.

P.parse p_rest "" "-"

p_nrests :: P (Bel a) Source #

Parse Rest Term.

P.parse p_nrests "" "3"

p_continue :: P (Term a) Source #

Parse Continue Term.

P.parse p_continue "" "_"

p_char_value :: P (Term Char) Source #

Parse Char Value Term.

P.parse p_char_value "" "a"

p_char_term :: P (Term Char) Source #

Parse Char Term.

P.parse (P.many1 p_char_term) "" "-_a"

p_char_node :: P (Bel Char) Source #

Parse Char Node.

P.parse (P.many1 p_char_node) "" "-_a"

p_non_negative_integer :: P Integer Source #

Parse non-negative Integer.

P.parse p_non_negative_integer "" "3"

p_non_negative_rational :: P Rational Source #

Parse non-negative Rational.

P.parse (p_non_negative_rational `P.sepBy` (P.char ',')) "" "3%5,2/3"

p_non_negative_double :: P Double Source #

Parse non-negative Double.

P.parse p_non_negative_double "" "3.5"
P.parse (p_non_negative_double `P.sepBy` (P.char ',')) "" "3.5,7.2,1.0"

p_non_negative_number :: P Rational Source #

Parse non-negative number as Rational.

P.parse (p_non_negative_number `P.sepBy` (P.char ',')) "" "7%2,3.5,3"

p_mul :: P (Bel a) Source #

Parse Mul.

P.parse (P.many1 p_mul) "" "/3*3/2"

p_iso :: P (Bel a) -> P (Bel a) Source #

Given parser for Bel a, generate Iso parser.

p_char_iso :: P (Bel Char) Source #

p_iso of p_char_bel.

P.parse p_char_iso "" "{abcde}"

p_par :: P (Bel a) -> P (Bel a) Source #

Given parser for Bel a, generate Par parser.

p_char_par :: P (Bel Char) Source #

p_par of p_char_bel.

p = P.parse p_char_par ""
p "{ab,{c,de}}" == p "{ab,c,de}"
p "{ab,~(c,de)}"

p_char_bel :: P (Bel Char) Source #

Parse Bel Char.

P.parse (P.many1 p_char_bel) "" "-_a*3"

bel_char_parse :: String -> Bel Char Source #

Run parser for Bel of Char.