{-# LANGUAGE ConstrainedClassMethods #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
module Musicology.Core
( module Musicology.Pitch
, Timed(..)
, HasTime(..)
, Pitched(..)
, HasInterval(..)
, HasPitch(..)
, Identifiable(..)
, TimedEvent(..)
, timedEventContent
, Note(..)
, NoteId(..)
, OnOff(..)
, onOffContent
, isOn
, isOff
, Tied(..)
, LeftTied(..)
, RightTied(..)
, rightTie
, leftTie
, fullTie
)
where
import Musicology.Pitch
import Data.Functor.Identity ( Identity(..) )
import GHC.Generics ( Generic )
import Control.DeepSeq ( NFData )
import Data.Hashable ( Hashable )
import Lens.Micro
import Lens.Micro.Extras
import Data.Aeson
class (Num (TimeOf a), Ord (TimeOf a)) => Timed a where
type TimeOf a
class Timed a => HasTime a where
onsetL :: Lens' a (TimeOf a)
onsetL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. HasTime a => a -> TimeOf a
onset (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. HasTime a => TimeOf a -> a -> a
setOnset)
offsetL :: Lens' a (TimeOf a)
offsetL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. HasTime a => a -> TimeOf a
offset (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. HasTime a => TimeOf a -> a -> a
setOffset)
onset :: a -> TimeOf a
onset = forall a s. Getting a s a -> s -> a
view forall a. HasTime a => Lens' a (TimeOf a)
onsetL
offset :: a -> TimeOf a
offset = forall a s. Getting a s a -> s -> a
view forall a. HasTime a => Lens' a (TimeOf a)
offsetL
setOnset :: TimeOf a -> a -> a
setOnset = forall s t a b. ASetter s t a b -> b -> s -> t
set forall a. HasTime a => Lens' a (TimeOf a)
onsetL
setOffset :: TimeOf a -> a -> a
setOffset = forall s t a b. ASetter s t a b -> b -> s -> t
set forall a. HasTime a => Lens' a (TimeOf a)
offsetL
class (Interval (IntervalOf a),
ReTypeInterval a (IntervalOf a) ~ a) => Pitched a where
type IntervalOf a
type ReTypeInterval a p
class Pitched a => HasInterval a where
intervalL :: (IntervalOf (ReTypeInterval a p2) ~ p2)
=> Lens a (ReTypeInterval a p2) (IntervalOf a) p2
intervalL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. HasInterval a => a -> IntervalOf a
interval (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a p2.
(HasInterval a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
p2 -> a -> ReTypeInterval a p2
setInterval)
interval :: a -> IntervalOf a
interval = forall a s. Getting a s a -> s -> a
view forall a p2.
(HasInterval a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (IntervalOf a) p2
intervalL
setInterval :: (IntervalOf (ReTypeInterval a p2) ~ p2)
=> p2 -> a -> ReTypeInterval a p2
setInterval = forall s t a b. ASetter s t a b -> b -> s -> t
set forall a p2.
(HasInterval a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (IntervalOf a) p2
intervalL
class (Pitched a) => HasPitch a where
pitchL :: (IntervalOf (ReTypeInterval a p2) ~ p2)
=> Lens a (ReTypeInterval a p2) (Pitch (IntervalOf a)) (Pitch p2)
pitchL = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
lens forall a. HasPitch a => a -> Pitch (IntervalOf a)
pitch (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a p2.
(HasPitch a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Pitch p2 -> a -> ReTypeInterval a p2
setPitch)
pitch :: a -> Pitch (IntervalOf a)
pitch = forall a s. Getting a s a -> s -> a
view forall a p2.
(HasPitch a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (Pitch (IntervalOf a)) (Pitch p2)
pitchL
setPitch :: (IntervalOf (ReTypeInterval a p2) ~ p2)
=> Pitch p2 -> a -> ReTypeInterval a p2
setPitch = forall s t a b. ASetter s t a b -> b -> s -> t
set forall a p2.
(HasPitch a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (Pitch (IntervalOf a)) (Pitch p2)
pitchL
instance Interval i => Pitched (Pitch i) where
type IntervalOf (Pitch i) = i
type ReTypeInterval (Pitch i) i' = Pitch i'
instance Interval i => HasPitch (Pitch i) where
pitch :: Pitch i -> Pitch (IntervalOf (Pitch i))
pitch = forall a. a -> a
id
setPitch :: forall p2.
(IntervalOf (ReTypeInterval (Pitch i) p2) ~ p2) =>
Pitch p2 -> Pitch i -> ReTypeInterval (Pitch i) p2
setPitch = forall a b. a -> b -> a
const
instance Interval p => Pitched [p] where
type IntervalOf [p] = p
type ReTypeInterval [p] p2 = [p2]
instance Interval p => Pitched (Maybe p) where
type IntervalOf (Maybe p) = p
type ReTypeInterval (Maybe p) p2 = Maybe p2
instance Interval p => Pitched (Identity p) where
type IntervalOf (Identity p) = p
type ReTypeInterval (Identity p) p2 = Identity p2
class Identifiable i where
type IdOf i
getId :: i -> IdOf i
data TimedEvent c t = TimedEvent c t t
deriving (TimedEvent c t -> TimedEvent c t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall c t.
(Eq c, Eq t) =>
TimedEvent c t -> TimedEvent c t -> Bool
/= :: TimedEvent c t -> TimedEvent c t -> Bool
$c/= :: forall c t.
(Eq c, Eq t) =>
TimedEvent c t -> TimedEvent c t -> Bool
== :: TimedEvent c t -> TimedEvent c t -> Bool
$c== :: forall c t.
(Eq c, Eq t) =>
TimedEvent c t -> TimedEvent c t -> Bool
Eq, TimedEvent c t -> TimedEvent c t -> Bool
TimedEvent c t -> TimedEvent c t -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {c} {t}. (Ord c, Ord t) => Eq (TimedEvent c t)
forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Bool
forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Ordering
forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> TimedEvent c t
min :: TimedEvent c t -> TimedEvent c t -> TimedEvent c t
$cmin :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> TimedEvent c t
max :: TimedEvent c t -> TimedEvent c t -> TimedEvent c t
$cmax :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> TimedEvent c t
>= :: TimedEvent c t -> TimedEvent c t -> Bool
$c>= :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Bool
> :: TimedEvent c t -> TimedEvent c t -> Bool
$c> :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Bool
<= :: TimedEvent c t -> TimedEvent c t -> Bool
$c<= :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Bool
< :: TimedEvent c t -> TimedEvent c t -> Bool
$c< :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Bool
compare :: TimedEvent c t -> TimedEvent c t -> Ordering
$ccompare :: forall c t.
(Ord c, Ord t) =>
TimedEvent c t -> TimedEvent c t -> Ordering
Ord, Int -> TimedEvent c t -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall c t. (Show c, Show t) => Int -> TimedEvent c t -> ShowS
forall c t. (Show c, Show t) => [TimedEvent c t] -> ShowS
forall c t. (Show c, Show t) => TimedEvent c t -> String
showList :: [TimedEvent c t] -> ShowS
$cshowList :: forall c t. (Show c, Show t) => [TimedEvent c t] -> ShowS
show :: TimedEvent c t -> String
$cshow :: forall c t. (Show c, Show t) => TimedEvent c t -> String
showsPrec :: Int -> TimedEvent c t -> ShowS
$cshowsPrec :: forall c t. (Show c, Show t) => Int -> TimedEvent c t -> ShowS
Show, ReadPrec [TimedEvent c t]
ReadPrec (TimedEvent c t)
ReadS [TimedEvent c t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall c t. (Read c, Read t) => ReadPrec [TimedEvent c t]
forall c t. (Read c, Read t) => ReadPrec (TimedEvent c t)
forall c t. (Read c, Read t) => Int -> ReadS (TimedEvent c t)
forall c t. (Read c, Read t) => ReadS [TimedEvent c t]
readListPrec :: ReadPrec [TimedEvent c t]
$creadListPrec :: forall c t. (Read c, Read t) => ReadPrec [TimedEvent c t]
readPrec :: ReadPrec (TimedEvent c t)
$creadPrec :: forall c t. (Read c, Read t) => ReadPrec (TimedEvent c t)
readList :: ReadS [TimedEvent c t]
$creadList :: forall c t. (Read c, Read t) => ReadS [TimedEvent c t]
readsPrec :: Int -> ReadS (TimedEvent c t)
$creadsPrec :: forall c t. (Read c, Read t) => Int -> ReadS (TimedEvent c t)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall c t x. Rep (TimedEvent c t) x -> TimedEvent c t
forall c t x. TimedEvent c t -> Rep (TimedEvent c t) x
$cto :: forall c t x. Rep (TimedEvent c t) x -> TimedEvent c t
$cfrom :: forall c t x. TimedEvent c t -> Rep (TimedEvent c t) x
Generic, forall a. (a -> ()) -> NFData a
forall c t. (NFData c, NFData t) => TimedEvent c t -> ()
rnf :: TimedEvent c t -> ()
$crnf :: forall c t. (NFData c, NFData t) => TimedEvent c t -> ()
NFData, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {c} {t}. (Hashable c, Hashable t) => Eq (TimedEvent c t)
forall c t.
(Hashable c, Hashable t) =>
Int -> TimedEvent c t -> Int
forall c t. (Hashable c, Hashable t) => TimedEvent c t -> Int
hash :: TimedEvent c t -> Int
$chash :: forall c t. (Hashable c, Hashable t) => TimedEvent c t -> Int
hashWithSalt :: Int -> TimedEvent c t -> Int
$chashWithSalt :: forall c t.
(Hashable c, Hashable t) =>
Int -> TimedEvent c t -> Int
Hashable)
timedEventContent :: TimedEvent c t -> c
timedEventContent (TimedEvent c
c t
_ t
_) = c
c
instance (Num t, Ord t) => Timed (TimedEvent p t) where
type TimeOf (TimedEvent p t) = t
instance (Num t, Ord t) => HasTime (TimedEvent p t) where
onsetL :: Lens' (TimedEvent p t) (TimeOf (TimedEvent p t))
onsetL TimeOf (TimedEvent p t) -> f (TimeOf (TimedEvent p t))
f (TimedEvent p
e t
on t
off) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t
on' -> forall c t. c -> t -> t -> TimedEvent c t
TimedEvent p
e t
on' t
off) (TimeOf (TimedEvent p t) -> f (TimeOf (TimedEvent p t))
f t
on)
offsetL :: Lens' (TimedEvent p t) (TimeOf (TimedEvent p t))
offsetL TimeOf (TimedEvent p t) -> f (TimeOf (TimedEvent p t))
f (TimedEvent p
e t
on t
off) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall c t. c -> t -> t -> TimedEvent c t
TimedEvent p
e t
on) (TimeOf (TimedEvent p t) -> f (TimeOf (TimedEvent p t))
f t
off)
instance Pitched c => Pitched (TimedEvent c t) where
type IntervalOf (TimedEvent c t) = IntervalOf c
type ReTypeInterval (TimedEvent c t) p2 = TimedEvent (ReTypeInterval c p2) t
data Note p t = Note !(Pitch p) !t !t
deriving (Note p t -> Note p t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall p t. (Eq p, Eq t) => Note p t -> Note p t -> Bool
/= :: Note p t -> Note p t -> Bool
$c/= :: forall p t. (Eq p, Eq t) => Note p t -> Note p t -> Bool
== :: Note p t -> Note p t -> Bool
$c== :: forall p t. (Eq p, Eq t) => Note p t -> Note p t -> Bool
Eq, Note p t -> Note p t -> Bool
Note p t -> Note p t -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {p} {t}. (Ord p, Ord t) => Eq (Note p t)
forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Bool
forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Ordering
forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Note p t
min :: Note p t -> Note p t -> Note p t
$cmin :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Note p t
max :: Note p t -> Note p t -> Note p t
$cmax :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Note p t
>= :: Note p t -> Note p t -> Bool
$c>= :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Bool
> :: Note p t -> Note p t -> Bool
$c> :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Bool
<= :: Note p t -> Note p t -> Bool
$c<= :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Bool
< :: Note p t -> Note p t -> Bool
$c< :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Bool
compare :: Note p t -> Note p t -> Ordering
$ccompare :: forall p t. (Ord p, Ord t) => Note p t -> Note p t -> Ordering
Ord, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p t x. Rep (Note p t) x -> Note p t
forall p t x. Note p t -> Rep (Note p t) x
$cto :: forall p t x. Rep (Note p t) x -> Note p t
$cfrom :: forall p t x. Note p t -> Rep (Note p t) x
Generic, forall a. (a -> ()) -> NFData a
forall p t. (NFData p, NFData t) => Note p t -> ()
rnf :: Note p t -> ()
$crnf :: forall p t. (NFData p, NFData t) => Note p t -> ()
NFData, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {p} {t}. (Hashable p, Hashable t) => Eq (Note p t)
forall p t. (Hashable p, Hashable t) => Int -> Note p t -> Int
forall p t. (Hashable p, Hashable t) => Note p t -> Int
hash :: Note p t -> Int
$chash :: forall p t. (Hashable p, Hashable t) => Note p t -> Int
hashWithSalt :: Int -> Note p t -> Int
$chashWithSalt :: forall p t. (Hashable p, Hashable t) => Int -> Note p t -> Int
Hashable)
deriving instance (Show (Pitch p), Show t) => Show (Note p t)
deriving instance (Read (Pitch p), Read t) => Read (Note p t)
instance (Num t, Ord t) => Timed (Note p t) where
type TimeOf (Note p t) = t
instance (Num t, Ord t) => HasTime (Note p t) where
onsetL :: Lens' (Note p t) (TimeOf (Note p t))
onsetL TimeOf (Note p t) -> f (TimeOf (Note p t))
f (Note Pitch p
p t
on t
off) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t
on' -> forall p t. Pitch p -> t -> t -> Note p t
Note Pitch p
p t
on' t
off) (TimeOf (Note p t) -> f (TimeOf (Note p t))
f t
on)
offsetL :: Lens' (Note p t) (TimeOf (Note p t))
offsetL TimeOf (Note p t) -> f (TimeOf (Note p t))
f (Note Pitch p
p t
on t
off) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall p t. Pitch p -> t -> t -> Note p t
Note Pitch p
p t
on) (TimeOf (Note p t) -> f (TimeOf (Note p t))
f t
off)
instance Interval p => Pitched (Note p t) where
type IntervalOf (Note p t) = p
type ReTypeInterval (Note p t) p2 = Note p2 t
instance Interval p => HasPitch (Note p t) where
pitchL :: Lens (Note p t) (Note p2 t) (Pitch p) (Pitch p2)
pitchL :: forall p2. Lens (Note p t) (Note p2 t) (Pitch p) (Pitch p2)
pitchL Pitch p -> f (Pitch p2)
f (Note Pitch p
p t
on t
off) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Pitch p2
p' -> forall p t. Pitch p -> t -> t -> Note p t
Note Pitch p2
p' t
on t
off) (Pitch p -> f (Pitch p2)
f Pitch p
p)
instance (ToJSON p, ToJSON t) => ToJSON (Note p t) where
toJSON :: Note p t -> Value
toJSON (Note (Pitch p
p) t
on t
off) =
[Pair] -> Value
object [Key
"pitch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= p
p, Key
"onset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
on, Key
"offset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
off]
toEncoding :: Note p t -> Encoding
toEncoding (Note (Pitch p
p) t
on t
off) =
Series -> Encoding
pairs (Key
"pitch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= p
p forall a. Semigroup a => a -> a -> a
<> Key
"onset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
on forall a. Semigroup a => a -> a -> a
<> Key
"offset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
off)
instance (FromJSON p, FromJSON t) => FromJSON (Note p t) where
parseJSON :: Value -> Parser (Note p t)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Note" forall a b. (a -> b) -> a -> b
$ \Object
v ->
forall p t. Pitch p -> t -> t -> Note p t
Note forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall {a}. a -> Pitch a
toPitch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pitch") forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"onset" forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"offset"
data NoteId p t i = NoteId !(Pitch p) !t !t !i
deriving (NoteId p t i -> NoteId p t i -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall p t i.
(Eq p, Eq t, Eq i) =>
NoteId p t i -> NoteId p t i -> Bool
/= :: NoteId p t i -> NoteId p t i -> Bool
$c/= :: forall p t i.
(Eq p, Eq t, Eq i) =>
NoteId p t i -> NoteId p t i -> Bool
== :: NoteId p t i -> NoteId p t i -> Bool
$c== :: forall p t i.
(Eq p, Eq t, Eq i) =>
NoteId p t i -> NoteId p t i -> Bool
Eq, NoteId p t i -> NoteId p t i -> Bool
NoteId p t i -> NoteId p t i -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {p} {t} {i}. (Ord p, Ord t, Ord i) => Eq (NoteId p t i)
forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Bool
forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Ordering
forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> NoteId p t i
min :: NoteId p t i -> NoteId p t i -> NoteId p t i
$cmin :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> NoteId p t i
max :: NoteId p t i -> NoteId p t i -> NoteId p t i
$cmax :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> NoteId p t i
>= :: NoteId p t i -> NoteId p t i -> Bool
$c>= :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Bool
> :: NoteId p t i -> NoteId p t i -> Bool
$c> :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Bool
<= :: NoteId p t i -> NoteId p t i -> Bool
$c<= :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Bool
< :: NoteId p t i -> NoteId p t i -> Bool
$c< :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Bool
compare :: NoteId p t i -> NoteId p t i -> Ordering
$ccompare :: forall p t i.
(Ord p, Ord t, Ord i) =>
NoteId p t i -> NoteId p t i -> Ordering
Ord, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall p t i x. Rep (NoteId p t i) x -> NoteId p t i
forall p t i x. NoteId p t i -> Rep (NoteId p t i) x
$cto :: forall p t i x. Rep (NoteId p t i) x -> NoteId p t i
$cfrom :: forall p t i x. NoteId p t i -> Rep (NoteId p t i) x
Generic, forall a. (a -> ()) -> NFData a
forall p t i. (NFData p, NFData t, NFData i) => NoteId p t i -> ()
rnf :: NoteId p t i -> ()
$crnf :: forall p t i. (NFData p, NFData t, NFData i) => NoteId p t i -> ()
NFData, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {p} {t} {i}.
(Hashable p, Hashable t, Hashable i) =>
Eq (NoteId p t i)
forall p t i.
(Hashable p, Hashable t, Hashable i) =>
Int -> NoteId p t i -> Int
forall p t i.
(Hashable p, Hashable t, Hashable i) =>
NoteId p t i -> Int
hash :: NoteId p t i -> Int
$chash :: forall p t i.
(Hashable p, Hashable t, Hashable i) =>
NoteId p t i -> Int
hashWithSalt :: Int -> NoteId p t i -> Int
$chashWithSalt :: forall p t i.
(Hashable p, Hashable t, Hashable i) =>
Int -> NoteId p t i -> Int
Hashable)
deriving instance (Show (Pitch p), Show t, Show i) => Show (NoteId p t i)
deriving instance (Read (Pitch p), Read t, Read i) => Read (NoteId p t i)
instance (Num t, Ord t) => Timed (NoteId p t i) where
type TimeOf (NoteId p t i) = t
instance (Num t, Ord t) => HasTime (NoteId p t i) where
onsetL :: Lens' (NoteId p t i) (TimeOf (NoteId p t i))
onsetL TimeOf (NoteId p t i) -> f (TimeOf (NoteId p t i))
f (NoteId Pitch p
p t
on t
off i
id) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t
on' -> forall p t i. Pitch p -> t -> t -> i -> NoteId p t i
NoteId Pitch p
p t
on' t
off i
id) (TimeOf (NoteId p t i) -> f (TimeOf (NoteId p t i))
f t
on)
offsetL :: Lens' (NoteId p t i) (TimeOf (NoteId p t i))
offsetL TimeOf (NoteId p t i) -> f (TimeOf (NoteId p t i))
f (NoteId Pitch p
p t
on t
off i
id) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\t
off' -> forall p t i. Pitch p -> t -> t -> i -> NoteId p t i
NoteId Pitch p
p t
on t
off' i
id) (TimeOf (NoteId p t i) -> f (TimeOf (NoteId p t i))
f t
off)
instance Interval p => Pitched (NoteId p t i) where
type IntervalOf (NoteId p t i) = p
type ReTypeInterval (NoteId p t i) p2 = NoteId p2 t i
instance Interval p => HasPitch (NoteId p t i) where
pitchL :: Lens (NoteId p t i) (NoteId p2 t i) (Pitch p) (Pitch p2)
pitchL :: forall p2. Lens (NoteId p t i) (NoteId p2 t i) (Pitch p) (Pitch p2)
pitchL Pitch p -> f (Pitch p2)
f (NoteId Pitch p
p t
on t
off i
id) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Pitch p2
p' -> forall p t i. Pitch p -> t -> t -> i -> NoteId p t i
NoteId Pitch p2
p' t
on t
off i
id) (Pitch p -> f (Pitch p2)
f Pitch p
p)
instance Identifiable (NoteId p t i) where
type IdOf (NoteId p t i) = i
getId :: NoteId p t i -> IdOf (NoteId p t i)
getId (NoteId Pitch p
_ t
_ t
_ i
i) = i
i
instance (ToJSON p, ToJSON t, ToJSON i) => ToJSON (NoteId p t i) where
toJSON :: NoteId p t i -> Value
toJSON (NoteId (Pitch p
p) t
on t
off i
id) =
[Pair] -> Value
object [Key
"pitch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= p
p, Key
"onset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
on, Key
"offset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
off, Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= i
id]
toEncoding :: NoteId p t i -> Encoding
toEncoding (NoteId (Pitch p
p) t
on t
off i
id) =
Series -> Encoding
pairs (Key
"pitch" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= p
p forall a. Semigroup a => a -> a -> a
<> Key
"onset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
on forall a. Semigroup a => a -> a -> a
<> Key
"offset" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= t
off forall a. Semigroup a => a -> a -> a
<> Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
.= i
id)
instance (FromJSON p, FromJSON t, FromJSON i) => FromJSON (NoteId p t i) where
parseJSON :: Value -> Parser (NoteId p t i)
parseJSON = forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"Note" forall a b. (a -> b) -> a -> b
$ \Object
v ->
forall p t i. Pitch p -> t -> t -> i -> NoteId p t i
NoteId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall {a}. a -> Pitch a
toPitch forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"pitch")
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"onset"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"offset"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"id"
data OnOff c t = Onset c !t
| Offset c !t
deriving (OnOff c t -> OnOff c t -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall c t. (Eq c, Eq t) => OnOff c t -> OnOff c t -> Bool
/= :: OnOff c t -> OnOff c t -> Bool
$c/= :: forall c t. (Eq c, Eq t) => OnOff c t -> OnOff c t -> Bool
== :: OnOff c t -> OnOff c t -> Bool
$c== :: forall c t. (Eq c, Eq t) => OnOff c t -> OnOff c t -> Bool
Eq, OnOff c t -> OnOff c t -> Bool
OnOff c t -> OnOff c t -> Ordering
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {c} {t}. (Ord c, Ord t) => Eq (OnOff c t)
forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Bool
forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Ordering
forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> OnOff c t
min :: OnOff c t -> OnOff c t -> OnOff c t
$cmin :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> OnOff c t
max :: OnOff c t -> OnOff c t -> OnOff c t
$cmax :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> OnOff c t
>= :: OnOff c t -> OnOff c t -> Bool
$c>= :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Bool
> :: OnOff c t -> OnOff c t -> Bool
$c> :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Bool
<= :: OnOff c t -> OnOff c t -> Bool
$c<= :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Bool
< :: OnOff c t -> OnOff c t -> Bool
$c< :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Bool
compare :: OnOff c t -> OnOff c t -> Ordering
$ccompare :: forall c t. (Ord c, Ord t) => OnOff c t -> OnOff c t -> Ordering
Ord, Int -> OnOff c t -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall c t. (Show c, Show t) => Int -> OnOff c t -> ShowS
forall c t. (Show c, Show t) => [OnOff c t] -> ShowS
forall c t. (Show c, Show t) => OnOff c t -> String
showList :: [OnOff c t] -> ShowS
$cshowList :: forall c t. (Show c, Show t) => [OnOff c t] -> ShowS
show :: OnOff c t -> String
$cshow :: forall c t. (Show c, Show t) => OnOff c t -> String
showsPrec :: Int -> OnOff c t -> ShowS
$cshowsPrec :: forall c t. (Show c, Show t) => Int -> OnOff c t -> ShowS
Show, ReadPrec [OnOff c t]
ReadPrec (OnOff c t)
ReadS [OnOff c t]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall c t. (Read c, Read t) => ReadPrec [OnOff c t]
forall c t. (Read c, Read t) => ReadPrec (OnOff c t)
forall c t. (Read c, Read t) => Int -> ReadS (OnOff c t)
forall c t. (Read c, Read t) => ReadS [OnOff c t]
readListPrec :: ReadPrec [OnOff c t]
$creadListPrec :: forall c t. (Read c, Read t) => ReadPrec [OnOff c t]
readPrec :: ReadPrec (OnOff c t)
$creadPrec :: forall c t. (Read c, Read t) => ReadPrec (OnOff c t)
readList :: ReadS [OnOff c t]
$creadList :: forall c t. (Read c, Read t) => ReadS [OnOff c t]
readsPrec :: Int -> ReadS (OnOff c t)
$creadsPrec :: forall c t. (Read c, Read t) => Int -> ReadS (OnOff c t)
Read, forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall c t x. Rep (OnOff c t) x -> OnOff c t
forall c t x. OnOff c t -> Rep (OnOff c t) x
$cto :: forall c t x. Rep (OnOff c t) x -> OnOff c t
$cfrom :: forall c t x. OnOff c t -> Rep (OnOff c t) x
Generic, forall a. (a -> ()) -> NFData a
forall c t. (NFData c, NFData t) => OnOff c t -> ()
rnf :: OnOff c t -> ()
$crnf :: forall c t. (NFData c, NFData t) => OnOff c t -> ()
NFData, forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {c} {t}. (Hashable c, Hashable t) => Eq (OnOff c t)
forall c t. (Hashable c, Hashable t) => Int -> OnOff c t -> Int
forall c t. (Hashable c, Hashable t) => OnOff c t -> Int
hash :: OnOff c t -> Int
$chash :: forall c t. (Hashable c, Hashable t) => OnOff c t -> Int
hashWithSalt :: Int -> OnOff c t -> Int
$chashWithSalt :: forall c t. (Hashable c, Hashable t) => Int -> OnOff c t -> Int
Hashable)
isOn :: OnOff c t -> Bool
isOn (Onset c
_ t
_) = Bool
True
isOn (Offset c
_ t
_) = Bool
False
ifOff :: OnOff c t -> Bool
ifOff (Onset c
_ t
_) = Bool
False
isOff :: OnOff c t -> Bool
isOff (Offset c
_ t
_) = Bool
True
onOffContent :: Lens (OnOff c t) (OnOff c2 t) c c2
onOffContent :: forall c t c2. Lens (OnOff c t) (OnOff c2 t) c c2
onOffContent c -> f c2
f (Onset c
c t
t) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall c t. c -> t -> OnOff c t
`Onset` t
t) (c -> f c2
f c
c)
onOffContent c -> f c2
f (Offset c
c t
t) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall c t. c -> t -> OnOff c t
`Offset` t
t) (c -> f c2
f c
c)
instance (Num t, Ord t) => Timed (OnOff c t) where
type TimeOf (OnOff c t) = t
instance (Num t, Ord t) => HasTime (OnOff p t) where
onsetL :: Lens' (OnOff p t) (TimeOf (OnOff p t))
onsetL TimeOf (OnOff p t) -> f (TimeOf (OnOff p t))
f (Onset p
p t
t) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall c t. c -> t -> OnOff c t
Onset p
p) (TimeOf (OnOff p t) -> f (TimeOf (OnOff p t))
f t
t)
onsetL TimeOf (OnOff p t) -> f (TimeOf (OnOff p t))
f (Offset p
p t
t) = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall c t. c -> t -> OnOff c t
Offset p
p) (TimeOf (OnOff p t) -> f (TimeOf (OnOff p t))
f t
t)
offsetL :: Lens' (OnOff p t) (TimeOf (OnOff p t))
offsetL = forall a. HasTime a => Lens' a (TimeOf a)
onsetL
instance Pitched c => Pitched (OnOff c t) where
type IntervalOf (OnOff c t) = IntervalOf c
type ReTypeInterval (OnOff c t) p2 = OnOff (ReTypeInterval c p2) t
instance HasInterval c => HasInterval (OnOff c t) where
intervalL :: forall p2.
(IntervalOf (ReTypeInterval (OnOff c t) p2) ~ p2) =>
Lens
(OnOff c t)
(ReTypeInterval (OnOff c t) p2)
(IntervalOf (OnOff c t))
p2
intervalL = forall c t c2. Lens (OnOff c t) (OnOff c2 t) c c2
onOffContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a p2.
(HasInterval a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (IntervalOf a) p2
intervalL
instance HasPitch c => HasPitch (OnOff c t) where
pitchL :: forall p2.
(IntervalOf (ReTypeInterval (OnOff c t) p2) ~ p2) =>
Lens
(OnOff c t)
(ReTypeInterval (OnOff c t) p2)
(Pitch (IntervalOf (OnOff c t)))
(Pitch p2)
pitchL = forall c t c2. Lens (OnOff c t) (OnOff c2 t) c c2
onOffContent forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a p2.
(HasPitch a, IntervalOf (ReTypeInterval a p2) ~ p2) =>
Lens a (ReTypeInterval a p2) (Pitch (IntervalOf a)) (Pitch p2)
pitchL
data Tied = Single
| Starts
| Continues
| Stops
deriving (Int -> Tied -> ShowS
[Tied] -> ShowS
Tied -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Tied] -> ShowS
$cshowList :: [Tied] -> ShowS
show :: Tied -> String
$cshow :: Tied -> String
showsPrec :: Int -> Tied -> ShowS
$cshowsPrec :: Int -> Tied -> ShowS
Show, Tied -> Tied -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Tied -> Tied -> Bool
$c/= :: Tied -> Tied -> Bool
== :: Tied -> Tied -> Bool
$c== :: Tied -> Tied -> Bool
Eq, Eq Tied
Tied -> Tied -> Bool
Tied -> Tied -> Ordering
Tied -> Tied -> Tied
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Tied -> Tied -> Tied
$cmin :: Tied -> Tied -> Tied
max :: Tied -> Tied -> Tied
$cmax :: Tied -> Tied -> Tied
>= :: Tied -> Tied -> Bool
$c>= :: Tied -> Tied -> Bool
> :: Tied -> Tied -> Bool
$c> :: Tied -> Tied -> Bool
<= :: Tied -> Tied -> Bool
$c<= :: Tied -> Tied -> Bool
< :: Tied -> Tied -> Bool
$c< :: Tied -> Tied -> Bool
compare :: Tied -> Tied -> Ordering
$ccompare :: Tied -> Tied -> Ordering
Ord, forall x. Rep Tied x -> Tied
forall x. Tied -> Rep Tied x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Tied x -> Tied
$cfrom :: forall x. Tied -> Rep Tied x
Generic, Tied -> ()
forall a. (a -> ()) -> NFData a
rnf :: Tied -> ()
$crnf :: Tied -> ()
NFData, Eq Tied
Int -> Tied -> Int
Tied -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Tied -> Int
$chash :: Tied -> Int
hashWithSalt :: Int -> Tied -> Int
$chashWithSalt :: Int -> Tied -> Int
Hashable)
data RightTied = Holds
| Ends
deriving (Int -> RightTied -> ShowS
[RightTied] -> ShowS
RightTied -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RightTied] -> ShowS
$cshowList :: [RightTied] -> ShowS
show :: RightTied -> String
$cshow :: RightTied -> String
showsPrec :: Int -> RightTied -> ShowS
$cshowsPrec :: Int -> RightTied -> ShowS
Show, RightTied -> RightTied -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RightTied -> RightTied -> Bool
$c/= :: RightTied -> RightTied -> Bool
== :: RightTied -> RightTied -> Bool
$c== :: RightTied -> RightTied -> Bool
Eq, Eq RightTied
RightTied -> RightTied -> Bool
RightTied -> RightTied -> Ordering
RightTied -> RightTied -> RightTied
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: RightTied -> RightTied -> RightTied
$cmin :: RightTied -> RightTied -> RightTied
max :: RightTied -> RightTied -> RightTied
$cmax :: RightTied -> RightTied -> RightTied
>= :: RightTied -> RightTied -> Bool
$c>= :: RightTied -> RightTied -> Bool
> :: RightTied -> RightTied -> Bool
$c> :: RightTied -> RightTied -> Bool
<= :: RightTied -> RightTied -> Bool
$c<= :: RightTied -> RightTied -> Bool
< :: RightTied -> RightTied -> Bool
$c< :: RightTied -> RightTied -> Bool
compare :: RightTied -> RightTied -> Ordering
$ccompare :: RightTied -> RightTied -> Ordering
Ord, forall x. Rep RightTied x -> RightTied
forall x. RightTied -> Rep RightTied x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RightTied x -> RightTied
$cfrom :: forall x. RightTied -> Rep RightTied x
Generic, RightTied -> ()
forall a. (a -> ()) -> NFData a
rnf :: RightTied -> ()
$crnf :: RightTied -> ()
NFData, Eq RightTied
Int -> RightTied -> Int
RightTied -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: RightTied -> Int
$chash :: RightTied -> Int
hashWithSalt :: Int -> RightTied -> Int
$chashWithSalt :: Int -> RightTied -> Int
Hashable)
rightTie :: Tied -> RightTied
rightTie :: Tied -> RightTied
rightTie Tied
Single = RightTied
Ends
rightTie Tied
Starts = RightTied
Holds
rightTie Tied
Continues = RightTied
Holds
rightTie Tied
Stops = RightTied
Ends
data LeftTied = New
| Held
deriving (Int -> LeftTied -> ShowS
[LeftTied] -> ShowS
LeftTied -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LeftTied] -> ShowS
$cshowList :: [LeftTied] -> ShowS
show :: LeftTied -> String
$cshow :: LeftTied -> String
showsPrec :: Int -> LeftTied -> ShowS
$cshowsPrec :: Int -> LeftTied -> ShowS
Show, LeftTied -> LeftTied -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LeftTied -> LeftTied -> Bool
$c/= :: LeftTied -> LeftTied -> Bool
== :: LeftTied -> LeftTied -> Bool
$c== :: LeftTied -> LeftTied -> Bool
Eq, Eq LeftTied
LeftTied -> LeftTied -> Bool
LeftTied -> LeftTied -> Ordering
LeftTied -> LeftTied -> LeftTied
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: LeftTied -> LeftTied -> LeftTied
$cmin :: LeftTied -> LeftTied -> LeftTied
max :: LeftTied -> LeftTied -> LeftTied
$cmax :: LeftTied -> LeftTied -> LeftTied
>= :: LeftTied -> LeftTied -> Bool
$c>= :: LeftTied -> LeftTied -> Bool
> :: LeftTied -> LeftTied -> Bool
$c> :: LeftTied -> LeftTied -> Bool
<= :: LeftTied -> LeftTied -> Bool
$c<= :: LeftTied -> LeftTied -> Bool
< :: LeftTied -> LeftTied -> Bool
$c< :: LeftTied -> LeftTied -> Bool
compare :: LeftTied -> LeftTied -> Ordering
$ccompare :: LeftTied -> LeftTied -> Ordering
Ord, forall x. Rep LeftTied x -> LeftTied
forall x. LeftTied -> Rep LeftTied x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep LeftTied x -> LeftTied
$cfrom :: forall x. LeftTied -> Rep LeftTied x
Generic, LeftTied -> ()
forall a. (a -> ()) -> NFData a
rnf :: LeftTied -> ()
$crnf :: LeftTied -> ()
NFData, Eq LeftTied
Int -> LeftTied -> Int
LeftTied -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: LeftTied -> Int
$chash :: LeftTied -> Int
hashWithSalt :: Int -> LeftTied -> Int
$chashWithSalt :: Int -> LeftTied -> Int
Hashable)
leftTie :: Tied -> LeftTied
leftTie :: Tied -> LeftTied
leftTie Tied
Single = LeftTied
New
leftTie Tied
Starts = LeftTied
New
leftTie Tied
Continues = LeftTied
Held
leftTie Tied
Stops = LeftTied
Held
fullTie :: LeftTied -> RightTied -> Tied
fullTie :: LeftTied -> RightTied -> Tied
fullTie LeftTied
New RightTied
Ends = Tied
Single
fullTie LeftTied
New RightTied
Holds = Tied
Starts
fullTie LeftTied
Held RightTied
Holds = Tied
Continues
fullTie LeftTied
Held RightTied
Ends = Tied
Stops