| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Music.Theory.Duration.Annotation
Description
Duration annotations.
- data D_Annotation
- type Duration_A = (Duration, [D_Annotation])
- begin_tuplet :: D_Annotation -> Maybe (Integer, Integer, Duration)
- da_begin_tuplet :: Duration_A -> Maybe (Integer, Integer, Duration)
- begins_tuplet :: D_Annotation -> Bool
- da_begins_tuplet :: Duration_A -> Bool
- da_ends_tuplet :: Duration_A -> Bool
- da_tied_right :: Duration_A -> Bool
- da_tuplet :: (Integer, Integer) -> [Duration_A] -> [Duration_A]
- begin_end_cmp :: (t -> Bool) -> (t -> Bool) -> t -> Ordering
- begin_end_cmp_eq :: Eq t => t -> t -> t -> Ordering
- group_tree :: (a -> Ordering) -> [a] -> Tree (Maybe a)
- da_group_tuplets :: [Duration_A] -> Tree (Maybe Duration_A)
- break_left :: (a -> Bool) -> [a] -> ([a], [a])
- sep_balanced :: Bool -> (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a])
- da_group_tuplets_nn :: [Duration_A] -> [Either Duration_A [Duration_A]]
- zip_with_kr :: (a -> b -> c) -> [a] -> [b] -> ([c], [b])
- zip_kr :: [a] -> [b] -> ([(a, b)], [b])
- nn_reshape :: (a -> b -> c) -> [Either a [a]] -> [b] -> [Either c [c]]
- adopt_shape :: Traversable t => (a -> b -> c) -> [b] -> t a -> t c
- adopt_shape_m :: Traversable t => (a -> b -> c) -> [b] -> t (Maybe a) -> t (Maybe c)
- d_annotated_tied_lr :: [D_Annotation] -> (Bool, Bool)
- duration_a_tied_lr :: Duration_A -> (Bool, Bool)
Documentation
data D_Annotation Source
Standard music notation durational model annotations
Constructors
| Tie_Right | |
| Tie_Left | |
| Begin_Tuplet (Integer, Integer, Duration) | |
| End_Tuplet |
Instances
type Duration_A = (Duration, [D_Annotation]) Source
Annotated Duration.
begin_tuplet :: D_Annotation -> Maybe (Integer, Integer, Duration) Source
da_begin_tuplet :: Duration_A -> Maybe (Integer, Integer, Duration) Source
begins_tuplet :: D_Annotation -> Bool Source
da_begins_tuplet :: Duration_A -> Bool Source
Does Duration_A begin a tuplet?
da_ends_tuplet :: Duration_A -> Bool Source
Does Duration_A end a tuplet?
da_tied_right :: Duration_A -> Bool Source
Is Duration_A tied to the the right?
da_tuplet :: (Integer, Integer) -> [Duration_A] -> [Duration_A] Source
Annotate a sequence of Duration_A as a tuplet.
import Music.Theory.Duration.Name da_tuplet (3,2) [(quarter_note,[Tie_Left]),(eighth_note,[Tie_Right])]
begin_end_cmp :: (t -> Bool) -> (t -> Bool) -> t -> Ordering Source
begin_end_cmp_eq :: Eq t => t -> t -> t -> Ordering Source
Variant of begin_end_cmp, predicates are constructed by ==.
map (begin_end_cmp_eq '{' '}') "{a}" == [LT,EQ,GT]group_tree :: (a -> Ordering) -> [a] -> Tree (Maybe a) Source
Given an Ordering predicate where LT opens a group, GT
closes a group, and EQ continues current group, construct tree
from list.
let {l = "a {b {c d} e f} g h i"
;t = group_tree (begin_end_cmp_eq '{' '}') l}
in catMaybes (flatten t) == llet d = putStrLn . drawTree . fmap show
in d (group_tree (begin_end_cmp_eq '(' ')') "a(b(cd)ef)ghi")da_group_tuplets :: [Duration_A] -> Tree (Maybe Duration_A) Source
Group tuplets into a Tree. Branch nodes have label Nothing,
leaf nodes label Just Duration_A.
import Music.Theory.Duration.Name.Abbreviation
let d = [(q,[])
,(e,[Begin_Tuplet (3,2,e)])
,(s,[Begin_Tuplet (3,2,s)]),(s,[]),(s,[End_Tuplet])
,(e,[End_Tuplet])
,(q,[])]
in catMaybes (flatten (da_group_tuplets d)) == dbreak_left :: (a -> Bool) -> [a] -> ([a], [a]) Source
Variant of break that places separator at left.
break_left (== 3) [1..6] == ([1..3],[4..6]) break_left (== 3) [1..3] == ([1..3],[])
sep_balanced :: Bool -> (a -> Bool) -> (a -> Bool) -> [a] -> ([a], [a]) Source
Variant of break_left that balances begin & end predicates.
break_left (== ')') "test (sep) _) balanced"
sep_balanced True (== '(') (== ')') "test (sep) _) balanced"
sep_balanced False (== '(') (== ')') "(test (sep) _) balanced"da_group_tuplets_nn :: [Duration_A] -> [Either Duration_A [Duration_A]] Source
Group non-nested tuplets, ie. groups nested tuplets at one level.
zip_with_kr :: (a -> b -> c) -> [a] -> [b] -> ([c], [b]) Source
Keep right variant of zipWith, unused rhs values are returned.
zip_with_kr (,) [1..3] ['a'..'e'] == ([(1,'a'),(2,'b'),(3,'c')],"de")
zip_kr :: [a] -> [b] -> ([(a, b)], [b]) Source
Keep right variant of zip, unused rhs values are returned.
zip_kr [1..4] ['a'..'f'] == ([(1,'a'),(2,'b'),(3,'c'),(4,'d')],"ef")
nn_reshape :: (a -> b -> c) -> [Either a [a]] -> [b] -> [Either c [c]] Source
zipWith variant that adopts the shape of the lhs.
let {p = [Left 1,Right [2,3],Left 4]
;q = "abcd"}
in nn_reshape (,) p q == [Left (1,'a'),Right [(2,'b'),(3,'c')],Left (4,'d')]adopt_shape :: Traversable t => (a -> b -> c) -> [b] -> t a -> t c Source
Replace elements at Traversable with result of joining with
elements from list.
adopt_shape_m :: Traversable t => (a -> b -> c) -> [b] -> t (Maybe a) -> t (Maybe c) Source
Variant of adopt_shape that considers only Just elements at
Traversable.
let {s = "a(b(cd)ef)ghi"
;t = group_tree (begin_end_cmp_eq '(' ')') s}
in adopt_shape_m (,) [1..13] td_annotated_tied_lr :: [D_Annotation] -> (Bool, Bool) Source
duration_a_tied_lr :: Duration_A -> (Bool, Bool) Source