module Music.Theory.Duration.Sequence.Notate where
import Data.List
import Data.List.Split
import Data.Maybe
import Data.Ratio
import Music.Theory.Either
import Music.Theory.Function
import Music.Theory.List
import Music.Theory.Duration
import Music.Theory.Duration.Annotation
import Music.Theory.Duration.Rq
import Music.Theory.Duration.Rq.Tied
import Music.Theory.Time_Signature
coalesce :: (a -> a -> Maybe a) -> [a] -> [a]
coalesce :: forall a. (a -> a -> Maybe a) -> [a] -> [a]
coalesce a -> a -> Maybe a
f [a]
x =
case [a]
x of
(a
p:a
q:[a]
x') ->
case a -> a -> Maybe a
f a
p a
q of
Maybe a
Nothing -> a
p forall a. a -> [a] -> [a]
: forall a. (a -> a -> Maybe a) -> [a] -> [a]
coalesce a -> a -> Maybe a
f (a
q forall a. a -> [a] -> [a]
: [a]
x')
Just a
r -> forall a. (a -> a -> Maybe a) -> [a] -> [a]
coalesce a -> a -> Maybe a
f (a
r forall a. a -> [a] -> [a]
: [a]
x')
[a]
_ -> [a]
x
coalesce_accum :: (b -> a -> a -> Either a b) -> b -> [a] -> [(b,a)]
coalesce_accum :: forall b a. (b -> a -> a -> Either a b) -> b -> [a] -> [(b, a)]
coalesce_accum b -> a -> a -> Either a b
f b
i [a]
x =
case [a]
x of
[] -> []
[a
p] -> [(b
i,a
p)]
(a
p:a
q:[a]
x') ->
case b -> a -> a -> Either a b
f b
i a
p a
q of
Right b
j -> (b
i,a
p) forall a. a -> [a] -> [a]
: forall b a. (b -> a -> a -> Either a b) -> b -> [a] -> [(b, a)]
coalesce_accum b -> a -> a -> Either a b
f b
j (a
q forall a. a -> [a] -> [a]
: [a]
x')
Left a
r -> forall b a. (b -> a -> a -> Either a b) -> b -> [a] -> [(b, a)]
coalesce_accum b -> a -> a -> Either a b
f b
i (a
r forall a. a -> [a] -> [a]
: [a]
x')
coalesce_sum :: (b -> a -> b) -> b -> (b -> a -> a -> Maybe a) -> [a] -> [a]
coalesce_sum :: forall b a.
(b -> a -> b) -> b -> (b -> a -> a -> Maybe a) -> [a] -> [a]
coalesce_sum b -> a -> b
add b
zero b -> a -> a -> Maybe a
f =
let g :: b -> a -> a -> Either a b
g b
i a
p a
q = case b -> a -> a -> Maybe a
f b
i a
p a
q of
Just a
r -> forall a b. a -> Either a b
Left a
r
Maybe a
Nothing -> forall a b. b -> Either a b
Right (b
i b -> a -> b
`add` a
p)
in forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a. (b -> a -> a -> Either a b) -> b -> [a] -> [(b, a)]
coalesce_accum b -> a -> a -> Either a b
g b
zero
take_sum_by :: (Ord n, Num n) => (a -> n) -> n -> [a] -> ([a], n, [a])
take_sum_by :: forall n a. (Ord n, Num n) => (a -> n) -> n -> [a] -> ([a], n, [a])
take_sum_by a -> n
f n
m =
let go :: [a] -> n -> [a] -> ([a], n, [a])
go [a]
r n
n [a]
l =
let z :: ([a], n, [a])
z = (forall a. [a] -> [a]
reverse [a]
r,n
mforall a. Num a => a -> a -> a
-n
n,[a]
l)
in case [a]
l of
[] -> ([a], n, [a])
z
a
i:[a]
l' -> let n' :: n
n' = a -> n
f a
i forall a. Num a => a -> a -> a
+ n
n
in if n
n' forall a. Ord a => a -> a -> Bool
> n
m
then ([a], n, [a])
z
else [a] -> n -> [a] -> ([a], n, [a])
go (a
iforall a. a -> [a] -> [a]
:[a]
r) n
n' [a]
l'
in [a] -> n -> [a] -> ([a], n, [a])
go [] n
0
take_sum :: (Ord a, Num a) => a -> [a] -> ([a],a,[a])
take_sum :: forall a. (Ord a, Num a) => a -> [a] -> ([a], a, [a])
take_sum = forall n a. (Ord n, Num n) => (a -> n) -> n -> [a] -> ([a], n, [a])
take_sum_by forall a. a -> a
id
take_sum_by_eq :: (Ord n, Num n) => (a -> n) -> n -> [a] -> Maybe ([a], [a])
take_sum_by_eq :: forall n a.
(Ord n, Num n) =>
(a -> n) -> n -> [a] -> Maybe ([a], [a])
take_sum_by_eq a -> n
f n
m [a]
l =
case forall n a. (Ord n, Num n) => (a -> n) -> n -> [a] -> ([a], n, [a])
take_sum_by a -> n
f n
m [a]
l of
([a]
p,n
0,[a]
q) -> forall a. a -> Maybe a
Just ([a]
p,[a]
q)
([a], n, [a])
_ -> forall a. Maybe a
Nothing
split_sum_by_eq :: (Ord n, Num n) => (a -> n) -> [n] -> [a] -> Maybe [[a]]
split_sum_by_eq :: forall n a. (Ord n, Num n) => (a -> n) -> [n] -> [a] -> Maybe [[a]]
split_sum_by_eq a -> n
f [n]
mm [a]
l =
case ([n]
mm,[a]
l) of
([],[]) -> forall a. a -> Maybe a
Just []
(n
m:[n]
mm',[a]
_) -> case forall n a.
(Ord n, Num n) =>
(a -> n) -> n -> [a] -> Maybe ([a], [a])
take_sum_by_eq a -> n
f n
m [a]
l of
Just ([a]
p,[a]
l') -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([a]
p forall a. a -> [a] -> [a]
:) (forall n a. (Ord n, Num n) => (a -> n) -> [n] -> [a] -> Maybe [[a]]
split_sum_by_eq a -> n
f [n]
mm' [a]
l')
Maybe ([a], [a])
Nothing -> forall a. Maybe a
Nothing
([n], [a])
_ -> forall a. Maybe a
Nothing
split_sum :: (Ord a, Num a) => a -> [a] -> Maybe ([a],[a],Maybe (a,a))
split_sum :: forall a.
(Ord a, Num a) =>
a -> [a] -> Maybe ([a], [a], Maybe (a, a))
split_sum a
m [a]
l =
let ([a]
p,a
n,[a]
q) = forall a. (Ord a, Num a) => a -> [a] -> ([a], a, [a])
take_sum a
m [a]
l
in if a
n forall a. Eq a => a -> a -> Bool
== a
0
then if forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
p
then forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just ([a]
p,[a]
q,forall a. Maybe a
Nothing)
else case [a]
q of
[] -> forall a. Maybe a
Nothing
a
z:[a]
q' -> forall a. a -> Maybe a
Just ([a]
pforall a. [a] -> [a] -> [a]
++[a
n],a
zforall a. Num a => a -> a -> a
-a
nforall a. a -> [a] -> [a]
:[a]
q',forall a. a -> Maybe a
Just (a
n,a
zforall a. Num a => a -> a -> a
-a
n))
rqt_split_sum :: Rq -> [Rq_Tied] -> Maybe ([Rq_Tied],[Rq_Tied])
rqt_split_sum :: Rq -> [Rq_Tied] -> Maybe ([Rq_Tied], [Rq_Tied])
rqt_split_sum Rq
d [Rq_Tied]
x =
case forall a.
(Ord a, Num a) =>
a -> [a] -> Maybe ([a], [a], Maybe (a, a))
split_sum Rq
d (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq [Rq_Tied]
x) of
Just ([Rq]
i,[Rq]
_,Maybe (Rq, Rq)
k) ->
case Maybe (Rq, Rq)
k of
Maybe (Rq, Rq)
Nothing -> forall a. a -> Maybe a
Just (forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rq]
i) [Rq_Tied]
x)
Just (Rq
p,Rq
q) -> let ([Rq_Tied]
s,(Rq
_,Bool
z):[Rq_Tied]
t) = forall a. Int -> [a] -> ([a], [a])
splitAt (forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rq]
i forall a. Num a => a -> a -> a
- Int
1) [Rq_Tied]
x
in forall a. a -> Maybe a
Just ([Rq_Tied]
s forall a. [a] -> [a] -> [a]
++ [(Rq
p,Bool
True)]
,(Rq
q,Bool
z) forall a. a -> [a] -> [a]
: [Rq_Tied]
t)
Maybe ([Rq], [Rq], Maybe (Rq, Rq))
Nothing -> forall a. Maybe a
Nothing
rqt_separate :: [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate :: [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq]
m [Rq_Tied]
x =
case ([Rq]
m,[Rq_Tied]
x) of
([],[]) -> forall a b. b -> Either a b
Right []
([],[Rq_Tied]
_) -> forall a b. a -> Either a b
Left (forall a. Show a => a -> String
show (String
"rqt_separate: lhs empty, rhs non-empty",[Rq_Tied]
x))
(Rq
i:[Rq]
m',[Rq_Tied]
_) ->
case Rq -> [Rq_Tied] -> Maybe ([Rq_Tied], [Rq_Tied])
rqt_split_sum Rq
i [Rq_Tied]
x of
Just ([Rq_Tied]
r,[Rq_Tied]
x') -> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([Rq_Tied]
r forall a. a -> [a] -> [a]
:) ([Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq]
m' [Rq_Tied]
x')
Maybe ([Rq_Tied], [Rq_Tied])
Nothing -> forall a b. a -> Either a b
Left (forall a. Show a => a -> String
show (String
"rqt_separate: rqt_split_sum failed",(Rq
i,[Rq_Tied]
x),[Rq]
m'))
rqt_separate_m :: [Rq] -> [Rq_Tied] -> Maybe [[Rq_Tied]]
rqt_separate_m :: [Rq] -> [Rq_Tied] -> Maybe [[Rq_Tied]]
rqt_separate_m [Rq]
m = forall a b. Either a b -> Maybe b
either_to_maybe forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq]
m
rqt_separate_tuplet :: Rq -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate_tuplet :: Rq -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate_tuplet Rq
i [Rq_Tied]
x =
if Int -> [Rq_Tied] -> Bool
rqt_can_notate Int
2 [Rq_Tied]
x
then forall a b. a -> Either a b
Left (forall a. Show a => a -> String
show (String
"rqt_separate_tuplet: separation not required",[Rq_Tied]
x))
else let j :: Rq
j = forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq [Rq_Tied]
x) forall a. Fractional a => a -> a -> a
/ Rq
2
in if Rq
j forall a. Ord a => a -> a -> Bool
< Rq
i
then forall a b. a -> Either a b
Left (forall a. Show a => a -> String
show (String
"rqt_separate_tuplet: j < i",Rq
j,Rq
i))
else [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq
j,Rq
j] [Rq_Tied]
x
rqt_tuplet_subdivide :: Rq -> [Rq_Tied] -> [[Rq_Tied]]
rqt_tuplet_subdivide :: Rq -> [Rq_Tied] -> [[Rq_Tied]]
rqt_tuplet_subdivide Rq
i [Rq_Tied]
x =
case Rq -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate_tuplet Rq
i [Rq_Tied]
x of
Left String
_ -> [[Rq_Tied]
x]
Right [[Rq_Tied]]
r -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Rq -> [Rq_Tied] -> [[Rq_Tied]]
rqt_tuplet_subdivide Rq
i) [[Rq_Tied]]
r
rqt_tuplet_subdivide_seq :: Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq :: Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq Rq
i = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Rq -> [Rq_Tied] -> [[Rq_Tied]]
rqt_tuplet_subdivide Rq
i)
rqt_tuplet_sanity_ :: [Rq_Tied] -> [Rq_Tied]
rqt_tuplet_sanity_ :: [Rq_Tied] -> [Rq_Tied]
rqt_tuplet_sanity_ [Rq_Tied]
t =
let last_tied :: Bool
last_tied = Rq_Tied -> Bool
rqt_tied (forall a. [a] -> a
last [Rq_Tied]
t)
all_tied :: Bool
all_tied = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all Rq_Tied -> Bool
rqt_tied (forall a. Int -> [a] -> [a]
dropRight Int
1 [Rq_Tied]
t)
in if Bool
all_tied
then [(forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq [Rq_Tied]
t),Bool
last_tied)]
else [Rq_Tied]
t
rqt_tuplet_subdivide_seq_sanity_ :: Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq_sanity_ :: Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq_sanity_ Rq
i =
forall a b. (a -> b) -> [a] -> [b]
map [Rq_Tied] -> [Rq_Tied]
rqt_tuplet_sanity_ forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq Rq
i
to_measures_rq :: [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq :: [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq [Rq]
m = [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq]
m forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Rq -> Rq_Tied
rq_rqt
to_measures_rq_untied_err :: [Rq] -> [Rq] -> [[Rq]]
to_measures_rq_untied_err :: [Rq] -> [Rq] -> [[Rq]]
to_measures_rq_untied_err [Rq]
m = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. HasCallStack => String -> a
error String
"to_measures_rq_untied") (forall a b. (a -> b) -> [a] -> [b]
map (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_to_rq_err)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq [Rq]
m
to_measures_rq_cmn :: [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq_cmn :: [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq_cmn [Rq]
m = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a b. (a -> b) -> [a] -> [b]
map [Rq_Tied] -> [Rq_Tied]
rqt_set_to_cmn) forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq [Rq]
m
to_measures_ts :: [Time_Signature] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_ts :: [Time_Signature] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_ts [Time_Signature]
m = [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq (forall a b. (a -> b) -> [a] -> [b]
map Time_Signature -> Rq
ts_rq [Time_Signature]
m)
to_measures_ts_by_eq :: (a -> Rq) -> [Time_Signature] -> [a] -> Maybe [[a]]
to_measures_ts_by_eq :: forall a. (a -> Rq) -> [Time_Signature] -> [a] -> Maybe [[a]]
to_measures_ts_by_eq a -> Rq
f [Time_Signature]
m = forall n a. (Ord n, Num n) => (a -> n) -> [n] -> [a] -> Maybe [[a]]
split_sum_by_eq a -> Rq
f (forall a b. (a -> b) -> [a] -> [b]
map Time_Signature -> Rq
ts_rq [Time_Signature]
m)
m_divisions_rq :: [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_rq :: [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_rq [Rq]
z =
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Rq -> [[Rq_Tied]] -> [[Rq_Tied]]
rqt_tuplet_subdivide_seq_sanity_ (Rq
1forall a. Fractional a => a -> a -> a
/Rq
16) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
forall a b. (a -> b) -> [a] -> [b]
map [Rq_Tied] -> [Rq_Tied]
rqt_set_to_cmn) forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
rqt_separate [Rq]
z
m_divisions_ts :: Time_Signature -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_ts :: Time_Signature -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_ts Time_Signature
ts = [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_rq (Time_Signature -> [Rq]
ts_divisions Time_Signature
ts)
to_divisions_rq :: [[Rq]] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_rq :: [[Rq]] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_rq [[Rq]]
m [Rq]
x =
let m' :: [Rq]
m' = forall a b. (a -> b) -> [a] -> [b]
map forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum [[Rq]]
m
in case [Rq] -> [Rq] -> Either String [[Rq_Tied]]
to_measures_rq [Rq]
m' [Rq]
x of
Right [[Rq_Tied]]
y -> forall a b. [Either a b] -> Either a [b]
all_right (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith [Rq] -> [Rq_Tied] -> Either String [[Rq_Tied]]
m_divisions_rq [[Rq]]
m [[Rq_Tied]]
y)
Left String
e -> forall a b. a -> Either a b
Left String
e
to_divisions_ts :: [Time_Signature] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_ts :: [Time_Signature] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_ts [Time_Signature]
ts = [[Rq]] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_rq (forall a b. (a -> b) -> [a] -> [b]
map Time_Signature -> [Rq]
ts_divisions [Time_Signature]
ts)
p_tuplet_rqt :: [Rq_Tied] -> Maybe ((Integer,Integer),[Rq_Tied])
p_tuplet_rqt :: [Rq_Tied] -> Maybe (Time_Signature, [Rq_Tied])
p_tuplet_rqt [Rq_Tied]
x =
let f :: Time_Signature -> (Time_Signature, [Rq_Tied])
f Time_Signature
t = (Time_Signature
t,forall a b. (a -> b) -> [a] -> [b]
map (Time_Signature -> Rq_Tied -> Rq_Tied
rqt_un_tuplet Time_Signature
t) [Rq_Tied]
x)
in forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Time_Signature -> (Time_Signature, [Rq_Tied])
f ([Rq] -> Maybe Time_Signature
rq_derive_tuplet (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq [Rq_Tied]
x))
p_notate :: Bool -> [Rq_Tied] -> Either String [Duration_A]
p_notate :: Bool -> [Rq_Tied] -> Either String [Duration_A]
p_notate Bool
z [Rq_Tied]
x =
let f :: [Rq_Tied] -> [Duration_A]
f = [Duration_A] -> [Duration_A]
p_simplify forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> [Rq_Tied] -> [Duration_A]
rqt_to_duration_a Bool
z
d :: [Duration_A]
d = case [Rq_Tied] -> Maybe (Time_Signature, [Rq_Tied])
p_tuplet_rqt [Rq_Tied]
x of
Just (Time_Signature
t,[Rq_Tied]
x') -> Time_Signature -> [Duration_A] -> [Duration_A]
da_tuplet Time_Signature
t ([Rq_Tied] -> [Duration_A]
f [Rq_Tied]
x')
Maybe (Time_Signature, [Rq_Tied])
Nothing -> [Rq_Tied] -> [Duration_A]
f [Rq_Tied]
x
in if Int -> [Rq] -> Bool
rq_can_notate Int
2 (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq [Rq_Tied]
x)
then forall a b. b -> Either a b
Right [Duration_A]
d
else forall a b. a -> Either a b
Left (forall a. Show a => a -> String
show (String
"p_notate",Bool
z,[Rq_Tied]
x))
m_notate :: Bool -> [[Rq_Tied]] -> Either String [Duration_A]
m_notate :: Bool -> [[Rq_Tied]] -> Either String [Duration_A]
m_notate Bool
z [[Rq_Tied]]
m =
let z' :: [Bool]
z' = Bool
z forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (Rq_Tied -> Bool
is_tied_right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last) [[Rq_Tied]]
m
in forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat (forall a b. [Either a b] -> Either a [b]
all_right (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Bool -> [Rq_Tied] -> Either String [Duration_A]
p_notate [Bool]
z' [[Rq_Tied]]
m))
mm_notate :: [[[Rq_Tied]]] -> Either String [[Duration_A]]
mm_notate :: [[[Rq_Tied]]] -> Either String [[Duration_A]]
mm_notate [[[Rq_Tied]]]
d =
let z :: [Bool]
z = Bool
False forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (Rq_Tied -> Bool
is_tied_right forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> a
last) [[[Rq_Tied]]]
d
in forall a b. [Either a b] -> Either a [b]
all_right (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Bool -> [[Rq_Tied]] -> Either String [Duration_A]
m_notate [Bool]
z [[[Rq_Tied]]]
d)
type Simplify_T = (Time_Signature,Rq,(Rq,Rq))
type Simplify_P = Simplify_T -> Bool
type Simplify_M = ([Time_Signature],[Rq],[(Rq,Rq)])
meta_table_p :: Simplify_M -> Simplify_P
meta_table_p :: Simplify_M -> Simplify_P
meta_table_p ([Time_Signature]
tt,[Rq]
ss,[(Rq, Rq)]
pp) (Time_Signature
t,Rq
s,(Rq, Rq)
p) = Time_Signature
t forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Time_Signature]
tt Bool -> Bool -> Bool
&& Rq
s forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Rq]
ss Bool -> Bool -> Bool
&& (Rq, Rq)
p forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [(Rq, Rq)]
pp
meta_table_t :: Simplify_M -> [Simplify_T]
meta_table_t :: Simplify_M -> [Simplify_T]
meta_table_t ([Time_Signature]
tt,[Rq]
ss,[(Rq, Rq)]
pp) = [(Time_Signature
t,Rq
s,(Rq, Rq)
p) | Time_Signature
t <- [Time_Signature]
tt, Rq
s <- [Rq]
ss,(Rq, Rq)
p <- [(Rq, Rq)]
pp]
default_table :: Simplify_P
default_table :: Simplify_P
default_table Simplify_T
x =
let t :: [Simplify_M]
t :: [Simplify_M]
t = [([(Integer
3,Integer
4)],[Rq
1],[(Rq
1,Rq
1)])]
p :: [Simplify_P]
p :: [Simplify_P]
p = forall a b. (a -> b) -> [a] -> [b]
map Simplify_M -> Simplify_P
meta_table_p [Simplify_M]
t
in forall (t :: * -> *). Foldable t => t Bool -> Bool
or ([Simplify_P]
p forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure Simplify_T
x)
default_8_rule :: Simplify_P
default_8_rule :: Simplify_P
default_8_rule ((Integer
i,Integer
j),Rq
t,(Rq
p,Rq
q)) =
let r :: Rq
r = Rq
p forall a. Num a => a -> a -> a
+ Rq
q
in Integer
j forall a. Eq a => a -> a -> Bool
== Integer
8 Bool -> Bool -> Bool
&&
forall a. Ratio a -> a
denominator Rq
t forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Integer
1,Integer
2] Bool -> Bool -> Bool
&&
(Rq
r forall a. Ord a => a -> a -> Bool
<= Rq
2 Bool -> Bool -> Bool
|| Rq
r forall a. Eq a => a -> a -> Bool
== Time_Signature -> Rq
ts_rq (Integer
i,Integer
j) Bool -> Bool -> Bool
|| Rq -> Bool
rq_is_integral Rq
r)
default_4_rule :: Simplify_P
default_4_rule :: Simplify_P
default_4_rule ((Integer
_,Integer
j),Rq
t,(Rq
p,Rq
q)) =
let r :: Rq
r = Rq
p forall a. Num a => a -> a -> a
+ Rq
q
in Integer
j forall a. Eq a => a -> a -> Bool
== Integer
4 Bool -> Bool -> Bool
&&
forall a. Ratio a -> a
denominator Rq
t forall a. Eq a => a -> a -> Bool
== Integer
1 Bool -> Bool -> Bool
&&
forall a. Integral a => a -> Bool
even (forall a. Ratio a -> a
numerator Rq
t) Bool -> Bool -> Bool
&&
(Rq
r forall a. Ord a => a -> a -> Bool
<= Rq
2 Bool -> Bool -> Bool
|| Rq -> Bool
rq_is_integral Rq
r)
default_rule :: [Simplify_T] -> Simplify_P
default_rule :: [Simplify_T] -> Simplify_P
default_rule [Simplify_T]
x Simplify_T
r = Simplify_T
r forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Simplify_T]
x Bool -> Bool -> Bool
||
Simplify_P
default_4_rule Simplify_T
r Bool -> Bool -> Bool
||
Simplify_P
default_8_rule Simplify_T
r Bool -> Bool -> Bool
||
Simplify_P
default_table Simplify_T
r
m_simplify :: Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify :: Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify Simplify_P
p Time_Signature
ts =
let f :: Rq -> Duration_A -> Duration_A -> Maybe Duration_A
f Rq
st (Duration
d0,[D_Annotation]
a0) (Duration
d1,[D_Annotation]
a1) =
let t :: Bool
t = D_Annotation
Tie_Right forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [D_Annotation]
a0 Bool -> Bool -> Bool
&& D_Annotation
Tie_Left forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [D_Annotation]
a1
e :: Bool
e = D_Annotation
End_Tuplet forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [D_Annotation]
a0 Bool -> Bool -> Bool
&& Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any D_Annotation -> Bool
begins_tuplet [D_Annotation]
a1)
m :: Bool
m = Duration -> Duration -> Bool
duration_meq Duration
d0 Duration
d1
d :: Maybe Duration
d = Duration -> Duration -> Maybe Duration
sum_dur Duration
d0 Duration
d1
a :: [D_Annotation]
a = forall a. Eq a => a -> [a] -> [a]
delete D_Annotation
Tie_Right [D_Annotation]
a0 forall a. [a] -> [a] -> [a]
++ forall a. Eq a => a -> [a] -> [a]
delete D_Annotation
Tie_Left [D_Annotation]
a1
r :: Bool
r = Simplify_P
p (Time_Signature
ts,Rq
st,(Duration -> Rq
duration_to_rq Duration
d0,Duration -> Rq
duration_to_rq Duration
d1))
n_dots :: Int
n_dots = Int
1
g :: Duration -> Maybe Duration_A
g Duration
i = if Duration -> Int
dots Duration
i forall a. Ord a => a -> a -> Bool
<= Int
n_dots Bool -> Bool -> Bool
&& Bool
t Bool -> Bool -> Bool
&& Bool
e Bool -> Bool -> Bool
&& Bool
m Bool -> Bool -> Bool
&& Bool
r
then forall a. a -> Maybe a
Just (Duration
i,[D_Annotation]
a)
else forall a. Maybe a
Nothing
in Duration -> Maybe Duration_A
g forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Duration
d
z :: Rq -> (Duration, b) -> Rq
z Rq
i (Duration
j,b
_) = Rq
i forall a. Num a => a -> a -> a
+ Duration -> Rq
duration_to_rq Duration
j
in forall b a.
(b -> a -> b) -> b -> (b -> a -> a -> Maybe a) -> [a] -> [a]
coalesce_sum forall {b}. Rq -> (Duration, b) -> Rq
z Rq
0 Rq -> Duration_A -> Duration_A -> Maybe Duration_A
f
m_simplify_fix :: Int -> Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify_fix :: Int -> Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify_fix Int
limit Simplify_P
p Time_Signature
ts [Duration_A]
d =
let d' :: [Duration_A]
d' = Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify Simplify_P
p Time_Signature
ts [Duration_A]
d
in if [Duration_A]
d forall a. Eq a => a -> a -> Bool
== [Duration_A]
d' Bool -> Bool -> Bool
|| Int
limit forall a. Eq a => a -> a -> Bool
== Int
1
then [Duration_A]
d'
else Int -> Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify_fix (Int
limit forall a. Num a => a -> a -> a
- Int
1) Simplify_P
p Time_Signature
ts [Duration_A]
d'
p_simplify_rule :: Simplify_P
p_simplify_rule :: Simplify_P
p_simplify_rule = forall a b. a -> b -> a
const Bool
True
p_simplify :: [Duration_A] -> [Duration_A]
p_simplify :: [Duration_A] -> [Duration_A]
p_simplify = Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify Simplify_P
p_simplify_rule forall a. HasCallStack => a
undefined
notate_rqp :: Int -> Simplify_P -> [Time_Signature] -> Maybe [[Rq]] -> [Rq] ->
Either String [[Duration_A]]
notate_rqp :: Int
-> Simplify_P
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> Either String [[Duration_A]]
notate_rqp Int
limit Simplify_P
r [Time_Signature]
ts Maybe [[Rq]]
ts_p [Rq]
x = do
let ts_p' :: [[Rq]]
ts_p' = forall a. a -> Maybe a -> a
fromMaybe (forall a b. (a -> b) -> [a] -> [b]
map Time_Signature -> [Rq]
ts_divisions [Time_Signature]
ts) Maybe [[Rq]]
ts_p
[[[Rq_Tied]]]
mm <- [[Rq]] -> [Rq] -> Either String [[[Rq_Tied]]]
to_divisions_rq [[Rq]]
ts_p' [Rq]
x
[[Duration_A]]
dd <- [[[Rq_Tied]]] -> Either String [[Duration_A]]
mm_notate [[[Rq_Tied]]]
mm
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (Int -> Simplify_P -> Time_Signature -> [Duration_A] -> [Duration_A]
m_simplify_fix Int
limit Simplify_P
r) [Time_Signature]
ts [[Duration_A]]
dd)
notate :: Int -> Simplify_P -> [Time_Signature] -> [Rq] -> Either String [[Duration_A]]
notate :: Int
-> Simplify_P
-> [Time_Signature]
-> [Rq]
-> Either String [[Duration_A]]
notate Int
limit Simplify_P
r [Time_Signature]
ts = Int
-> Simplify_P
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> Either String [[Duration_A]]
notate_rqp Int
limit Simplify_P
r [Time_Signature]
ts forall a. Maybe a
Nothing
zip_hold_lhs :: (Show t,Show x) => (x -> Bool) -> [x] -> [t] -> ([t],[(x,t)])
zip_hold_lhs :: forall t x.
(Show t, Show x) =>
(x -> Bool) -> [x] -> [t] -> ([t], [(x, t)])
zip_hold_lhs x -> Bool
lhs_f =
let f :: [b] -> x -> ([b], (x, b))
f [b]
st x
e =
case [b]
st of
b
r:[b]
s -> let st' :: [b]
st' = if x -> Bool
lhs_f x
e then [b]
st else [b]
s
in ([b]
st',(x
e,b
r))
[b]
_ -> forall a. HasCallStack => String -> a
error (forall a. Show a => a -> String
show (String
"zip_hold_lhs: rhs ends",[b]
st,x
e))
in forall a b c. (a -> b -> c) -> b -> a -> c
flip (forall (t :: * -> *) s a b.
Traversable t =>
(s -> a -> (s, b)) -> s -> t a -> (s, t b)
mapAccumL forall {b}. Show b => [b] -> x -> ([b], (x, b))
f)
zip_hold_lhs_err :: (Show t,Show x) => (x -> Bool) -> [x] -> [t] -> [(x,t)]
zip_hold_lhs_err :: forall t x.
(Show t, Show x) =>
(x -> Bool) -> [x] -> [t] -> [(x, t)]
zip_hold_lhs_err x -> Bool
lhs_f [x]
p [t]
q =
case forall t x.
(Show t, Show x) =>
(x -> Bool) -> [x] -> [t] -> ([t], [(x, t)])
zip_hold_lhs x -> Bool
lhs_f [x]
p [t]
q of
([],[(x, t)]
r) -> [(x, t)]
r
([t], [(x, t)])
e -> forall a. HasCallStack => String -> a
error (forall a. Show a => a -> String
show (String
"zip_hold_lhs_err: lhs ends",([t], [(x, t)])
e))
zip_hold :: (Show t,Show x) => (x -> Bool) -> (t -> Bool) -> [x] -> [t] -> ([t],[(x,t)])
zip_hold :: forall t x.
(Show t, Show x) =>
(x -> Bool) -> (t -> Bool) -> [x] -> [t] -> ([t], [(x, t)])
zip_hold x -> Bool
lhs_f t -> Bool
rhs_f =
let f :: [(x, t)] -> [x] -> [t] -> ([t], [(x, t)])
f [(x, t)]
r [x]
x [t]
t =
case ([x]
x,[t]
t) of
([],[t]
_) -> ([t]
t,forall a. [a] -> [a]
reverse [(x, t)]
r)
([x]
_,[]) -> forall a. HasCallStack => String -> a
error String
"zip_hold: rhs ends"
(x
x0:[x]
x',t
t0:[t]
t') -> let x'' :: [x]
x'' = if t -> Bool
rhs_f t
t0 then [x]
x else [x]
x'
t'' :: [t]
t'' = if x -> Bool
lhs_f x
x0 then [t]
t else [t]
t'
in [(x, t)] -> [x] -> [t] -> ([t], [(x, t)])
f ((x
x0,t
t0) forall a. a -> [a] -> [a]
: [(x, t)]
r) [x]
x'' [t]
t''
in [(x, t)] -> [x] -> [t] -> ([t], [(x, t)])
f []
m_ascribe :: Show x => [Duration_A] -> [x] -> ([x],[(Duration_A,x)])
m_ascribe :: forall x. Show x => [Duration_A] -> [x] -> ([x], [(Duration_A, x)])
m_ascribe = forall t x.
(Show t, Show x) =>
(x -> Bool) -> [x] -> [t] -> ([t], [(x, t)])
zip_hold_lhs Duration_A -> Bool
da_tied_right
ascribe :: Show x => [Duration_A] -> [x] -> [(Duration_A, x)]
ascribe :: forall x. Show x => [Duration_A] -> [x] -> [(Duration_A, x)]
ascribe [Duration_A]
d = forall a b. (a, b) -> b
snd forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall x. Show x => [Duration_A] -> [x] -> ([x], [(Duration_A, x)])
m_ascribe [Duration_A]
d
mm_ascribe :: Show x => [[Duration_A]] -> [x] -> [[(Duration_A,x)]]
mm_ascribe :: forall x. Show x => [[Duration_A]] -> [x] -> [[(Duration_A, x)]]
mm_ascribe [[Duration_A]]
mm [x]
x =
case [[Duration_A]]
mm of
[] -> []
[Duration_A]
m:[[Duration_A]]
mm' -> let ([x]
x',[(Duration_A, x)]
r) = forall x. Show x => [Duration_A] -> [x] -> ([x], [(Duration_A, x)])
m_ascribe [Duration_A]
m [x]
x
in [(Duration_A, x)]
r forall a. a -> [a] -> [a]
: forall x. Show x => [[Duration_A]] -> [x] -> [[(Duration_A, x)]]
mm_ascribe [[Duration_A]]
mm' [x]
x'
notate_mm_ascribe :: Show a => Int -> [Simplify_T] -> [Time_Signature] -> Maybe [[Rq]] -> [Rq] -> [a] ->
Either String [[(Duration_A,a)]]
notate_mm_ascribe :: forall a.
Show a =>
Int
-> [Simplify_T]
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> [a]
-> Either String [[(Duration_A, a)]]
notate_mm_ascribe Int
limit [Simplify_T]
r [Time_Signature]
ts Maybe [[Rq]]
rqp [Rq]
d [a]
p =
let n :: Either String [[Duration_A]]
n = Int
-> Simplify_P
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> Either String [[Duration_A]]
notate_rqp Int
limit ([Simplify_T] -> Simplify_P
default_rule [Simplify_T]
r) [Time_Signature]
ts Maybe [[Rq]]
rqp [Rq]
d
f :: [[Duration_A]] -> [[(Duration_A, a)]]
f = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall x. Show x => [[Duration_A]] -> [x] -> [[(Duration_A, x)]]
mm_ascribe [a]
p
err :: b -> String
err b
str = forall a. Show a => a -> String
show (String
"notate_mm_ascribe",b
str,[Time_Signature]
ts,[Rq]
d,[a]
p)
in forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> Either a b
Left forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Show a => a -> String
err) (forall a b. b -> Either a b
Right forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Duration_A]] -> [[(Duration_A, a)]]
f) Either String [[Duration_A]]
n
notate_mm_ascribe_err :: Show a => Int -> [Simplify_T] -> [Time_Signature] -> Maybe [[Rq]] -> [Rq] -> [a] ->
[[(Duration_A,a)]]
notate_mm_ascribe_err :: forall a.
Show a =>
Int
-> [Simplify_T]
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> [a]
-> [[(Duration_A, a)]]
notate_mm_ascribe_err = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. HasCallStack => String -> a
error forall a. a -> a
id forall (f :: * -> *) (g :: * -> *) (h :: * -> *) (i :: * -> *)
(j :: * -> *) (k :: * -> *) a b.
(Functor f, Functor g, Functor h, Functor i, Functor j,
Functor k) =>
(a -> b) -> f (g (h (i (j (k a))))) -> f (g (h (i (j (k b)))))
.::::: forall a.
Show a =>
Int
-> [Simplify_T]
-> [Time_Signature]
-> Maybe [[Rq]]
-> [Rq]
-> [a]
-> Either String [[(Duration_A, a)]]
notate_mm_ascribe
group_chd :: (x -> Bool) -> [x] -> [[x]]
group_chd :: forall x. (x -> Bool) -> [x] -> [[x]]
group_chd x -> Bool
f [x]
x =
case forall a. Splitter a -> [a] -> [[a]]
split (forall a. Splitter a -> Splitter a
keepDelimsL (forall a. (a -> Bool) -> Splitter a
whenElt (Bool -> Bool
notforall b c a. (b -> c) -> (a -> b) -> a -> c
.x -> Bool
f))) [x]
x of
[]:[[x]]
r -> [[x]]
r
[[x]]
_ -> forall a. HasCallStack => String -> a
error String
"group_chd: first element chd?"
ascribe_chd :: Show x => (x -> Bool) -> [Duration_A] -> [x] -> [(Duration_A, x)]
ascribe_chd :: forall x.
Show x =>
(x -> Bool) -> [Duration_A] -> [x] -> [(Duration_A, x)]
ascribe_chd x -> Bool
chd_f [Duration_A]
d [x]
x =
let x' :: [[x]]
x' = forall x. (x -> Bool) -> [x] -> [[x]]
group_chd x -> Bool
chd_f [x]
x
jn :: (a, [b]) -> [(a, b)]
jn (a
i,[b]
j) = forall a b. [a] -> [b] -> [(a, b)]
zip (forall a. a -> [a]
repeat a
i) [b]
j
in forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a} {b}. (a, [b]) -> [(a, b)]
jn (forall x. Show x => [Duration_A] -> [x] -> [(Duration_A, x)]
ascribe [Duration_A]
d [[x]]
x')
mm_ascribe_chd :: Show x => (x -> Bool) -> [[Duration_A]] -> [x] -> [[(Duration_A,x)]]
mm_ascribe_chd :: forall x.
Show x =>
(x -> Bool) -> [[Duration_A]] -> [x] -> [[(Duration_A, x)]]
mm_ascribe_chd x -> Bool
chd_f [[Duration_A]]
d [x]
x =
let x' :: [[x]]
x' = forall x. (x -> Bool) -> [x] -> [[x]]
group_chd x -> Bool
chd_f [x]
x
jn :: (a, [b]) -> [(a, b)]
jn (a
i,[b]
j) = forall a b. [a] -> [b] -> [(a, b)]
zip (forall a. a -> [a]
repeat a
i) [b]
j
in forall a b. (a -> b) -> [a] -> [b]
map (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap forall {a} {b}. (a, [b]) -> [(a, b)]
jn) (forall x. Show x => [[Duration_A]] -> [x] -> [[(Duration_A, x)]]
mm_ascribe [[Duration_A]]
d [[x]]
x')