Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Quanta
- qToInt :: Quanta -> Int
- qFromInt :: Integral i => i -> Maybe Quanta
- data TimeSignature = TimeSignature {}
- tsUnit :: Lens' TimeSignature Quanta
- tsLength :: Lens' TimeSignature Int
- class HasTimeSignature a where
- timeSignature :: Lens' a (Maybe TimeSignature)
- (/:) :: Int -> Quanta -> TimeSignature
- data PPQ
- ppqDiv :: Integral a => PPQ -> a
- tsToRatio :: TimeSignature -> Rational
- tsFromRatio :: Rational -> Maybe TimeSignature
- tsFromRatio' :: TimeSignature -> Rational -> Maybe TimeSignature
- ratioPPQ :: forall a. Integral a => PPQ -> Iso' a Rational
- adaptHas :: Lens' a (Maybe a)
- adaptHasLens :: Lens' s a -> Lens' s (Maybe a)
- adaptHasNot :: Lens' s (Maybe a)
- data Tie
- class HasTie a where
- data Slur
- class HasSlur a where
- data Articulation
- class HasArticulation a where
- articulation :: Lens' a (Maybe Articulation)
- newtype RehearsalMark = RehearsalMark {}
- rehearsalText :: Iso' RehearsalMark String
- class HasRehearsalMark a where
- rehearsalMark :: Lens' a (Maybe RehearsalMark)
- newtype Direction = Direction {}
- directionText :: Iso' Direction String
- class HasDirection a where
- data Barline
- class HasBarline a where
- data Repeats
- class HasRepeats a where
- data Clef
- class HasClef a where
- data Beam
- class HasBeams a where
- class HasVoice a where
- newtype Part a = Part {
- _partIdx :: a
- partIdx :: forall a a. Iso (Part a) (Part a) a a
- class HasPart a b | a -> b where
- mshow :: Show a => Getter s (Maybe a) -> String -> s -> String
- mshows :: s -> String -> [s -> String] -> String
- type Note' p d = Noted (Note p d)
- data Noted n = Noted {}
- nVoice :: forall n. Lens' (Noted n) (Maybe String)
- nTie :: forall n. Lens' (Noted n) (Maybe Tie)
- nSlur :: forall n. Lens' (Noted n) (Maybe Slur)
- nNote :: forall n n. Lens (Noted n) (Noted n) n n
- nBeams :: forall n. Lens' (Noted n) [Beam]
- nArticulation :: forall n. Lens' (Noted n) (Maybe Articulation)
- note' :: Note p d -> Note' p d
- noted :: n -> Noted n
- testNote :: Note' [Int] Int
- data Bar n = Bar {}
- bTimeSignature :: forall n. Lens' (Bar n) (Maybe TimeSignature)
- bRepeats :: forall n. Lens' (Bar n) (Maybe Repeats)
- bRehearsalMark :: forall n. Lens' (Bar n) (Maybe RehearsalMark)
- bNotes :: forall n n. Lens (Bar n) (Bar n) (Seq n) (Seq n)
- bDirection :: forall n. Lens' (Bar n) (Maybe Direction)
- bClef :: forall n. Lens' (Bar n) (Maybe Clef)
- bBarline :: forall n. Lens' (Bar n) (Maybe Barline)
- bar :: [n] -> Bar n
- testBar :: Bar (Note [Int] Int)
Documentation
data TimeSignature Source #
Instances
Show TimeSignature Source # | |
Defined in Fadno.Notation showsPrec :: Int -> TimeSignature -> ShowS # show :: TimeSignature -> String # showList :: [TimeSignature] -> ShowS # | |
Eq TimeSignature Source # | |
Defined in Fadno.Notation (==) :: TimeSignature -> TimeSignature -> Bool # (/=) :: TimeSignature -> TimeSignature -> Bool # | |
Ord TimeSignature Source # | |
Defined in Fadno.Notation compare :: TimeSignature -> TimeSignature -> Ordering # (<) :: TimeSignature -> TimeSignature -> Bool # (<=) :: TimeSignature -> TimeSignature -> Bool # (>) :: TimeSignature -> TimeSignature -> Bool # (>=) :: TimeSignature -> TimeSignature -> Bool # max :: TimeSignature -> TimeSignature -> TimeSignature # min :: TimeSignature -> TimeSignature -> TimeSignature # |
class HasTimeSignature a where Source #
timeSignature :: Lens' a (Maybe TimeSignature) Source #
Instances
HasTimeSignature (Bar n) Source # | |
Defined in Fadno.Notation timeSignature :: Lens' (Bar n) (Maybe TimeSignature) Source # |
tsToRatio :: TimeSignature -> Rational Source #
tsFromRatio :: Rational -> Maybe TimeSignature Source #
tsFromRatio' :: TimeSignature -> Rational -> Maybe TimeSignature Source #
ratioPPQ :: forall a. Integral a => PPQ -> Iso' a Rational Source #
Duration iso, from Integral to Rational, given PPQ
adaptHasLens :: Lens' s a -> Lens' s (Maybe a) Source #
Adapt a non-Maybe lens to the HasXXX "Maybe Lens'"
adaptHasNot :: Lens' s (Maybe a) Source #
Adapt a type that does NOT support the HasXXX feature.
Tied notes.
Slurred notes.
data Articulation Source #
Note articulations.
Staccato | |
Accent | |
Tenuto | StrongAccent TODO implement after fixing fadno-xml #7 |
DetachedLegato | |
Staccatissimo | |
Spiccato | |
Scoop | |
Plop | |
Doit | |
Falloff | |
BreathMark | |
Caesura | |
Stress | |
Unstress | |
SoftAccent | |
OtherArticulation String |
Instances
Show Articulation Source # | |
Defined in Fadno.Notation showsPrec :: Int -> Articulation -> ShowS # show :: Articulation -> String # showList :: [Articulation] -> ShowS # | |
HasArticulation Articulation Source # | |
Defined in Fadno.Notation | |
Eq Articulation Source # | |
Defined in Fadno.Notation (==) :: Articulation -> Articulation -> Bool # (/=) :: Articulation -> Articulation -> Bool # | |
Ord Articulation Source # | |
Defined in Fadno.Notation compare :: Articulation -> Articulation -> Ordering # (<) :: Articulation -> Articulation -> Bool # (<=) :: Articulation -> Articulation -> Bool # (>) :: Articulation -> Articulation -> Bool # (>=) :: Articulation -> Articulation -> Bool # max :: Articulation -> Articulation -> Articulation # min :: Articulation -> Articulation -> Articulation # |
class HasArticulation a where Source #
articulation :: Lens' a (Maybe Articulation) Source #
Instances
HasArticulation Articulation Source # | |
Defined in Fadno.Notation | |
HasArticulation (Noted n) Source # | |
Defined in Fadno.Notation articulation :: Lens' (Noted n) (Maybe Articulation) Source # |
newtype RehearsalMark Source #
Bar rehearsal mark.
Instances
class HasRehearsalMark a where Source #
rehearsalMark :: Lens' a (Maybe RehearsalMark) Source #
Instances
HasRehearsalMark RehearsalMark Source # | |
Defined in Fadno.Notation | |
HasRehearsalMark (Bar n) Source # | |
Defined in Fadno.Notation rehearsalMark :: Lens' (Bar n) (Maybe RehearsalMark) Source # |
Musical direction.
Instances
IsString Direction Source # | |
Defined in Fadno.Notation fromString :: String -> Direction # | |
Monoid Direction Source # | |
Semigroup Direction Source # | |
Generic Direction Source # | |
Show Direction Source # | |
Default Direction Source # | |
Defined in Fadno.Notation | |
HasDirection Direction Source # | |
Eq Direction Source # | |
Ord Direction Source # | |
Defined in Fadno.Notation | |
type Rep Direction Source # | |
Defined in Fadno.Notation |
class HasDirection a where Source #
Barline.
class HasBarline a where Source #
class HasRepeats a where Source #
Instances
Generic Clef Source # | |
Show Clef Source # | |
HasClef Clef Source # | |
Eq Clef Source # | |
Ord Clef Source # | |
type Rep Clef Source # | |
Defined in Fadno.Notation type Rep Clef = D1 ('MetaData "Clef" "Fadno.Notation" "fadno-1.1.9.1-Eru2Yc86rln9jozd2rhNAS" 'False) ((C1 ('MetaCons "TrebleClef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BassClef" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AltoClef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PercClef" 'PrefixI 'False) (U1 :: Type -> Type))) |
Adapts musicxml Beams where beams are labeled "1" for eighth beam etc, where instead it is a list implying the first element is eighth etc.
Instances
Foldable Part Source # | |
Defined in Fadno.Notation fold :: Monoid m => Part m -> m # foldMap :: Monoid m => (a -> m) -> Part a -> m # foldMap' :: Monoid m => (a -> m) -> Part a -> m # foldr :: (a -> b -> b) -> b -> Part a -> b # foldr' :: (a -> b -> b) -> b -> Part a -> b # foldl :: (b -> a -> b) -> b -> Part a -> b # foldl' :: (b -> a -> b) -> b -> Part a -> b # foldr1 :: (a -> a -> a) -> Part a -> a # foldl1 :: (a -> a -> a) -> Part a -> a # elem :: Eq a => a -> Part a -> Bool # maximum :: Ord a => Part a -> a # | |
Traversable Part Source # | |
Functor Part Source # | |
IsString a => IsString (Part a) Source # | |
Defined in Fadno.Notation fromString :: String -> Part a # | |
Bounded a => Bounded (Part a) Source # | |
Generic (Part a) Source # | |
Num a => Num (Part a) Source # | |
Real a => Real (Part a) Source # | |
Defined in Fadno.Notation toRational :: Part a -> Rational # | |
Show a => Show (Part a) Source # | |
Eq a => Eq (Part a) Source # | |
Ord a => Ord (Part a) Source # | |
type Rep (Part a) Source # | |
Defined in Fadno.Notation |
mshow :: Show a => Getter s (Maybe a) -> String -> s -> String Source #
Lensy show of a Maybe field, given a ReifiedGetter
and its name.
Instances
nArticulation :: forall n. Lens' (Noted n) (Maybe Articulation) Source #
Bar as list of notes, with notations.
Bar | |
|
Instances
bTimeSignature :: forall n. Lens' (Bar n) (Maybe TimeSignature) Source #
bRehearsalMark :: forall n. Lens' (Bar n) (Maybe RehearsalMark) Source #