module Music.Theory.Duration.Rq.Tied where
import Data.Maybe
import Music.Theory.List
import Music.Theory.Duration
import qualified Music.Theory.Duration.Annotation as Annotation
import Music.Theory.Duration.Rq
type Tied_Right = Bool
type Rq_Tied = (Rq,Tied_Right)
rqt_to_rq :: Rq_Tied -> Maybe Rq
rqt_to_rq :: Rq_Tied -> Maybe Rq
rqt_to_rq (Rq
rq,Tied_Right
x) = if Tied_Right
x then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just Rq
rq
rqt_to_rq_err :: Rq_Tied -> Rq
rqt_to_rq_err :: Rq_Tied -> Rq
rqt_to_rq_err = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => [Char] -> a
error [Char]
"rqt_to_rq") forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rq_Tied -> Maybe Rq
rqt_to_rq
rqt :: Tied_Right -> Rq -> Rq_Tied
rqt :: Tied_Right -> Rq -> Rq_Tied
rqt Tied_Right
t Rq
d = (Rq
d,Tied_Right
t)
rqt_rq :: Rq_Tied -> Rq
rqt_rq :: Rq_Tied -> Rq
rqt_rq = forall a b. (a, b) -> a
fst
rqt_tied :: Rq_Tied -> Tied_Right
rqt_tied :: Rq_Tied -> Tied_Right
rqt_tied = forall a b. (a, b) -> b
snd
is_tied_right :: Rq_Tied -> Bool
is_tied_right :: Rq_Tied -> Tied_Right
is_tied_right = forall a b. (a, b) -> b
snd
rqt_un_tuplet :: (Integer,Integer) -> Rq_Tied -> Rq_Tied
rqt_un_tuplet :: (Integer, Integer) -> Rq_Tied -> Rq_Tied
rqt_un_tuplet (Integer, Integer)
i (Rq
d,Tied_Right
t) = ((Integer, Integer) -> Rq -> Rq
rq_un_tuplet (Integer, Integer)
i Rq
d,Tied_Right
t)
rq_rqt :: Rq -> Rq_Tied
rq_rqt :: Rq -> Rq_Tied
rq_rqt Rq
n = (Rq
n,Tied_Right
False)
rq_tie_last :: [Rq] -> [Rq_Tied]
rq_tie_last :: [Rq] -> [Rq_Tied]
rq_tie_last = forall a b. (a -> b) -> (a -> b) -> [a] -> [b]
at_last Rq -> Rq_Tied
rq_rqt (\Rq
d -> (Rq
d,Tied_Right
True))
rqt_to_duration_a :: Bool -> [Rq_Tied] -> [Annotation.Duration_A]
rqt_to_duration_a :: Tied_Right -> [Rq_Tied] -> [Duration_A]
rqt_to_duration_a Tied_Right
z [Rq_Tied]
x =
let rt :: [Tied_Right]
rt = forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Tied_Right
is_tied_right [Rq_Tied]
x
lt :: [Tied_Right]
lt = Tied_Right
z forall a. a -> [a] -> [a]
: [Tied_Right]
rt
f :: Tied_Right -> a -> Maybe a
f Tied_Right
p a
e = if Tied_Right
p then forall a. a -> Maybe a
Just a
e else forall a. Maybe a
Nothing
g :: Tied_Right -> Tied_Right -> [D_Annotation]
g Tied_Right
r Tied_Right
l = forall a. [Maybe a] -> [a]
catMaybes [forall {a}. Tied_Right -> a -> Maybe a
f Tied_Right
r D_Annotation
Annotation.Tie_Right,forall {a}. Tied_Right -> a -> Maybe a
f Tied_Right
l D_Annotation
Annotation.Tie_Left]
h :: Rq_Tied -> Duration
h = forall a. Show a => a -> Dots -> Rq -> Duration
rq_to_duration_err (forall a. Show a => a -> [Char]
show ([Char]
"rqt_to_duration_a",Tied_Right
z,[Rq_Tied]
x)) Dots
2 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rq_Tied -> Rq
rqt_rq
in forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Duration
h [Rq_Tied]
x) (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith Tied_Right -> Tied_Right -> [D_Annotation]
g [Tied_Right]
rt [Tied_Right]
lt)
rqt_can_notate :: Dots -> [Rq_Tied] -> Bool
rqt_can_notate :: Dots -> [Rq_Tied] -> Tied_Right
rqt_can_notate Dots
k = Dots -> [Rq] -> Tied_Right
rq_can_notate Dots
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map Rq_Tied -> Rq
rqt_rq
rqt_to_cmn :: Rq_Tied -> Maybe (Rq_Tied,Rq_Tied)
rqt_to_cmn :: Rq_Tied -> Maybe (Rq_Tied, Rq_Tied)
rqt_to_cmn (Rq
k,Tied_Right
t) =
let f :: (a, a) -> ((a, Tied_Right), (a, Tied_Right))
f (a
i,a
j) = ((a
i,Tied_Right
True),(a
j,Tied_Right
t))
in forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a} {a}. (a, a) -> ((a, Tied_Right), (a, Tied_Right))
f (Rq -> Maybe (Rq, Rq)
rq_to_cmn Rq
k)
rqt_to_cmn_l :: Rq_Tied -> [Rq_Tied]
rqt_to_cmn_l :: Rq_Tied -> [Rq_Tied]
rqt_to_cmn_l Rq_Tied
x = forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Rq_Tied
x] (\(Rq_Tied
i,Rq_Tied
j) -> [Rq_Tied
i,Rq_Tied
j]) (Rq_Tied -> Maybe (Rq_Tied, Rq_Tied)
rqt_to_cmn Rq_Tied
x)
rqt_set_to_cmn :: [Rq_Tied] -> [Rq_Tied]
rqt_set_to_cmn :: [Rq_Tied] -> [Rq_Tied]
rqt_set_to_cmn = forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap Rq_Tied -> [Rq_Tied]
rqt_to_cmn_l