Safe Haskell | Safe-Inferred |
---|
This module defines basic tracklang types.
The Derive.PSignal section is re-exported from Derive.PSignal. I'd rather move it to PSignal, but it needs to be here to avoid circular imports.
Here are the names for various aspects of signals:
numbers pitches both scalar Signal.Y PSignal.Y name ScoreT.Control ScoreT.PControl signal Signal.Control PSignal.PSignal ref DeriveT.ControlRef DeriveT.PControlRef Ref
Synopsis
- newtype PSignal = PSignal (Segment.Boxed Pitch)
- _signal :: PSignal -> Segment.Boxed Pitch
- interpolate :: Segment.Interpolate Pitch
- type Pitch = RawPitch Untransposed_
- type Transposed = RawPitch Transposed_
- data RawPitch a = Pitch {}
- pitch :: Scale -> (PitchConfig -> Either PitchError Pitch.NoteNumber) -> (PitchConfig -> Either PitchError Pitch.Note) -> PitchConfig -> Pitch
- coerce :: RawPitch a -> RawPitch b
- pitch_nn :: Transposed -> Either PitchError Pitch.NoteNumber
- pitch_note :: Transposed -> Either PitchError Pitch.Note
- data PitchConfig = PitchConfig !Environ !ScoreT.ControlValMap
- data Scale = Scale {}
- detailed_error :: RawPitch a -> PitchError -> Text
- data PitchError
- data OutOfRange = OutOfRange {
- oor_nn :: !(Maybe Pitch.NoteNumber)
- oor_degree :: !(Maybe Pitch.FSemi)
- oor_valid :: !(Maybe (Int, Int))
- oor_transposers :: !ScoreT.ControlValMap
- out_of_range :: OutOfRange
- out_of_range_error :: Real a => a -> (Int, Int) -> PitchError
- pitches_equal :: RawPitch a -> RawPitch a -> Bool
- data Duration
- data TimeType
- multiply_duration :: Duration -> Double -> Duration
- newtype Environ = Environ (Map EnvKey.Key Val)
- null :: Environ -> Bool
- insert :: EnvKey.Key -> Val -> Environ -> Environ
- lookup :: EnvKey.Key -> Environ -> Maybe Val
- environ_attributes :: Environ -> Attrs.Attributes
- data Val
- vals_equal :: Val -> Val -> Maybe Bool
- types_equal :: Val -> Val -> Bool
- val_to_mini :: Val -> Maybe Expr.MiniVal
- newtype Quoted = Quoted Expr
- show_call_val :: Val -> Text
- num :: Double -> Val
- constant_val :: Val -> Maybe (ScoreT.Typed Signal.Y)
- constant :: ScoreT.Type -> Signal.Y -> Val
- score_time :: ScoreTime.ScoreTime -> Val
- real_time :: RealTime.RealTime -> Val
- transposition :: Pitch.Transpose -> Val
- str :: Text -> Val
- to_scale_id :: Val -> Maybe Pitch.ScaleId
- quoted :: Expr.Symbol -> [Val] -> Quoted
- quoted0 :: Expr.Symbol -> Quoted
- type ControlRef = Ref ScoreT.Control ScoreT.TypedSignal
- type PControlRef = Ref ScoreT.PControl PSignal
- data Ref control val = Ref control (Maybe val)
- type Expr = Expr.Expr Val
- type Call = Expr.Call Val
- type Term = Expr.Term Val
- type PitchCall = Call
- map_str :: (Expr.Str -> Expr.Str) -> Call -> Call
- type PitchMap = Map ScoreT.PControl PSignal
- type PitchFunction = RealTime.RealTime -> Maybe Pitch
- data CFunction = CFunction {
- cf_name :: !Text
- cf_signal :: !ScoreT.TypedSignal
- cf_function :: !(Dynamic -> Signal.Control -> RealTime.RealTime -> Signal.Y)
- call_cfunction :: Dynamic -> CFunction -> ScoreT.TypedFunction
- data PFunction = PFunction {}
- data Dynamic = Dynamic {
- dyn_pitch :: !PSignal
- dyn_environ :: !Environ
- dyn_event_serial :: !Int
- dyn_warp :: !Warp.Warp
- dyn_ruler :: Ruler.Marklists
- empty_dynamic :: Dynamic
Derive.PSignal
A pitch signal is similar to a Signal.Control
, except that its values
are Pitch
es instead of plain floating point values.
Instances
interpolate :: Segment.Interpolate Pitch Source #
A pitch interpolated a certain distance between two other pitches.
type Pitch = RawPitch Untransposed_ Source #
This is an untransposed pitch. All pitches have transposition signals from the dynamic state applied when they are converted to MIDI or whatever backend. So if I want the final concrete pitch, I have to apply the transposition signals. But if I want to emit a note with this pitch, I want the untransposed one, or the transposition will be applied twice. I use a phantom type parameter to keep them straight.
type Transposed = RawPitch Transposed_ Source #
The transposed version of Pitch
.
A pitch is an abstract value that can generate a Pitch.NoteNumber
or
symbolic Pitch.Note
.
Pitch | |
|
Instances
ToVal Pitch Source # | |
Typecheck Pitch Source # | |
Typecheck PitchFunction Source # | |
Defined in Derive.Typecheck from_val :: Val -> Checked PitchFunction Source # to_type :: Proxy PitchFunction -> Type Source # from_subtrack :: Track -> Maybe PitchFunction Source # | |
Show (RawPitch a) Source # | |
DeepSeq.NFData (RawPitch a) Source # | It can't be reduced since it has lambdas, but at least this way you can easily rnf things that contain it. |
Defined in Derive.DeriveT | |
ShowVal.ShowVal (RawPitch a) Source # | Pitches have no literal syntax, but I have to print something. |
Pretty.Pretty (RawPitch a) Source # | Will look like: 62.95nn,4i(*wayang) |
pitch :: Scale -> (PitchConfig -> Either PitchError Pitch.NoteNumber) -> (PitchConfig -> Either PitchError Pitch.Note) -> PitchConfig -> Pitch Source #
Make an abstract Pitch.
pitch_nn :: Transposed -> Either PitchError Pitch.NoteNumber Source #
Usually I only want to evaluate a fully transposed pitch. Exceptions
are documented by applying coerce
.
pitch_note :: Transposed -> Either PitchError Pitch.Note Source #
Usually I only want to evaluate a fully transposed pitch. Exceptions
are documented by applying coerce
.
data PitchConfig Source #
A PitchConfig is the data that can continue to influence the pitch's frequency.
Pitches are configured by controls and by an environ. The controls
are for values that change over time, such as transposition or tuning.
They're combined additively, which is really only appropriate for
transposition. Controls are mostly applied only on conversion to the
performer. TODO I don't entirely remember why. However, this leads to
some trickiness because if I want to compare a pitch to an absolute
NoteNumber, I need the final transposed value, but if I put it in an event
it must be untransposed, or transposition will be applied twice.
To avoid double. To avoid this, there's a phantom type parameter to
distinguish an untransposed Pitch
from a Transposed
one.
The Environ is for symbolic configuration, such as key or tuning mode. Unlike controls, though, it's taken from the environ in scope when the pith is created. Otherwise, you can't evaluate a pitch with a different key by setting the environ.
Instances
Monoid PitchConfig Source # | |
Defined in Derive.DeriveT mempty :: PitchConfig # mappend :: PitchConfig -> PitchConfig -> PitchConfig # mconcat :: [PitchConfig] -> PitchConfig # | |
Semigroup PitchConfig Source # | |
Defined in Derive.DeriveT (<>) :: PitchConfig -> PitchConfig -> PitchConfig # sconcat :: NonEmpty PitchConfig -> PitchConfig # stimes :: Integral b => b -> PitchConfig -> PitchConfig # | |
Show PitchConfig Source # | |
Defined in Derive.DeriveT showsPrec :: Int -> PitchConfig -> ShowS # show :: PitchConfig -> String # showList :: [PitchConfig] -> ShowS # | |
Pretty.Pretty PitchConfig Source # | |
Defined in Derive.DeriveT pretty :: PitchConfig -> Text Source # format :: PitchConfig -> Doc Source # formatList :: [PitchConfig] -> Doc Source # |
PSignal can't take a Scale because that would be a circular import. Fortunately it only needs a few fields. However, because of the circularity, the Scale.Scale -> PSignal.Scale constructor is in Derive.Derive.
Scale | |
|
Instances
detailed_error :: RawPitch a -> PitchError -> Text Source #
Annotate a PitchError with additional info. TODO I should probably accumulate info all the way up to get a full "stack trace" of what happened to a pitch (e.g. interpolation), which maybe means abandon PitchError and just use Text, or go ever further with structure? Meanwhile, this seems to do ok practically speaking.
data PitchError Source #
Things that can go wrong evaluating a pitch.
UnparseableNote !Pitch.Note | |
OutOfRangeError !OutOfRange | |
InvalidInput | Input note doesn't map to a scale note. |
EnvironError !EnvKey.Key !(Maybe Text) | A required environ value was missing or had the wrong type or value. Nothing if the value is missing, otherwise a Text description. |
ControlError !ScoreT.Control !Text | Same as EnvironError, but for control vals. |
NotImplemented | The scale doesn't implement that operation. |
PitchError !Text | Other kind of error. |
Instances
Show PitchError Source # | |
Defined in Derive.DeriveT showsPrec :: Int -> PitchError -> ShowS # show :: PitchError -> String # showList :: [PitchError] -> ShowS # | |
Eq PitchError Source # | |
Defined in Derive.DeriveT (==) :: PitchError -> PitchError -> Bool # (/=) :: PitchError -> PitchError -> Bool # | |
Ord PitchError Source # | |
Defined in Derive.DeriveT compare :: PitchError -> PitchError -> Ordering # (<) :: PitchError -> PitchError -> Bool # (<=) :: PitchError -> PitchError -> Bool # (>) :: PitchError -> PitchError -> Bool # (>=) :: PitchError -> PitchError -> Bool # max :: PitchError -> PitchError -> PitchError # min :: PitchError -> PitchError -> PitchError # | |
Pretty.Pretty PitchError Source # | |
Defined in Derive.DeriveT pretty :: PitchError -> Text Source # format :: PitchError -> Doc Source # formatList :: [PitchError] -> Doc Source # |
data OutOfRange Source #
Note out of the scale's range. The values are transpositions from the environment, in case it was out of range because of a transposition.
Some scales have a restricted range, in which case they should throw
out_of_range
, which pitch_nn
and pitch_note
will annotate with the
transposition signals. Other scales have unlimited range, in which case
they're limited by the backend. In this case pitch_nn
checks 0--127,
which happens to be MIDI's limitation.
OutOfRange | |
|
Instances
Show OutOfRange Source # | |
Defined in Derive.DeriveT showsPrec :: Int -> OutOfRange -> ShowS # show :: OutOfRange -> String # showList :: [OutOfRange] -> ShowS # | |
Eq OutOfRange Source # | |
Defined in Derive.DeriveT (==) :: OutOfRange -> OutOfRange -> Bool # (/=) :: OutOfRange -> OutOfRange -> Bool # | |
Ord OutOfRange Source # | |
Defined in Derive.DeriveT compare :: OutOfRange -> OutOfRange -> Ordering # (<) :: OutOfRange -> OutOfRange -> Bool # (<=) :: OutOfRange -> OutOfRange -> Bool # (>) :: OutOfRange -> OutOfRange -> Bool # (>=) :: OutOfRange -> OutOfRange -> Bool # max :: OutOfRange -> OutOfRange -> OutOfRange # min :: OutOfRange -> OutOfRange -> OutOfRange # | |
Pretty.Pretty OutOfRange Source # | |
Defined in Derive.DeriveT pretty :: OutOfRange -> Text Source # format :: OutOfRange -> Doc Source # formatList :: [OutOfRange] -> Doc Source # |
out_of_range_error :: Real a => a -> (Int, Int) -> PitchError Source #
Duration
Some calls can operate in either RealTime or ScoreTime.
multiply_duration :: Duration -> Double -> Duration Source #
Duration can't be in Fractional since you can't multiple a RealDuration by a ScoreDuration, but scaling operations are still useful.
Environ
insert :: EnvKey.Key -> Val -> Environ -> Environ Source #
Insert a val directly, with no typechecking.
Val
This is the type of first class values in the tracklang. It's main purpose is the type for arguments to tracklang calls, and val calls' return type.
VSignal !(ScoreT.Typed Signal.Control) | A number with an optional type suffix. It also has a ratio style literal, though the output is still a floating point value, not a true ratio. Constant literal: Signal literal: |
VPitch !Pitch | No literal, but is returned from val calls, notably scale calls. |
VPSignal !PSignal | |
VAttributes !Attrs.Attributes | A set of Attributes for an instrument. Literal: |
VControlRef !ControlRef | A control name. An optional value gives a default if the control isn't present. Literal: |
VPControlRef !PControlRef | A pitch control name. The scale is taken from the environ. Unlike
a control signal, the empty string is a valid signal name and means the
default pitch signal. The Literal: |
VNotePitch !Pitch.Pitch | A parsed Literal: |
VStr !Expr.Str | A string. There is an unquoted and a quoted form, parsed at
Literal: |
VQuoted !Quoted | A quoted expression. Quoted calls are resolved by Derive.Sig when it typechecks arguments. This way you can set an argument default to an expression that will be evaluated every time the call occurs. Derive.Sig expects that the expression is a valid val call, which means no pipes. Literal: |
VCFunction !CFunction | |
VPFunction !PFunction | |
VNotGiven | An explicit not-given arg for functions so you can use positional args with defaults. Literal: |
VSeparator | A token used as a separator when calls want to parse their argument lists via their own complicated means. TODO only used by old gamakam, get rid of this Literal: |
VList ![Val] | List of values. Literal: |
Instances
Show Val Source # | |
DeepSeq.NFData Val Source # | |
Defined in Derive.DeriveT | |
ShowVal.ShowVal Val Source # | This instance is actually invalid due to showing VPitch, which has no
literal, and for |
ToVal Val Source # | |
Typecheck Val Source # | |
Pretty.Pretty Val Source # | |
ShowVal.ShowVal (Expr.Call Val) Source # | |
ShowVal.ShowVal (Expr.Expr Val) Source # | |
ShowVal.ShowVal (Expr.Term Val) Source # | |
Pretty.Pretty (Expr.Call Val) Source # | |
Pretty.Pretty (Expr.Term Val) Source # | |
vals_equal :: Val -> Val -> Maybe Bool Source #
Return Nothing if the Vals can't be compared, and whether or not they're equal otherwise.
val_to_mini :: Val -> Maybe Expr.MiniVal Source #
Instances
Show Quoted Source # | |
ShowVal.ShowVal Quoted Source # | Unlike Exprs in general, a Quoted Expr should be representable with show_val. This is because a Quoted has only been parsed, not evaluated, so it shouldn't have anything unshowable, like pitches. |
ToVal Quoted Source # | |
Typecheck Quoted Source # | Anything except a pitch can be coerced to a quoted, using ShowVal. This means you can write a lot of things without quotes. Pitches have to be quoted because they explicitly have an invalid ShowVal. |
Pretty.Pretty Quoted Source # | |
show_call_val :: Val -> Text Source #
Show a str intended for call position. Call position is special in that it can contain any character except space and equals without quoting.
val utils
constant_val :: Val -> Maybe (ScoreT.Typed Signal.Y) Source #
score_time :: ScoreTime.ScoreTime -> Val Source #
real_time :: RealTime.RealTime -> Val Source #
transposition :: Pitch.Transpose -> Val Source #
to_scale_id :: Val -> Maybe Pitch.ScaleId Source #
quoted0 :: Expr.Symbol -> Quoted Source #
Ref
type PControlRef = Ref ScoreT.PControl PSignal Source #
Instances
Expr
call utils
type aliases
type PitchFunction = RealTime.RealTime -> Maybe Pitch Source #
ControlFunction
Another representation of a signal, complementary to Signal.Control
.
It's more powerful because it has access to a subset of the Dynamic state,
as well as the Control
is was originally bound to. However, it's also
less powerful because you can't inspect it to see if it's constant, or emit
exactly the samples present without resorting to sampling, or draw it on
the UI. This is the ubiquitous code vs. data tradeoff.
In addition, the main motivation to add control functions was to randomize values, which means that, unlike signals, they're not actually functions at all, and thus couldn't be rendered as a continuous signal. This means that functions are only suitable for sampling at points, not for slicing over time ranges.
Having both signals and functions is awkward because then some calls may ignore a control function if they require a signal, which is inconsistent and confusing. This is the case for all control generators since the signal usually is on a control track and will wind up being rendered on the UI. So the convention is that control functions are generally just modifications of an underlying signal, rather than synthesizing a signal.
Another awkward thing about CFunction is that it really wants to be in Deriver, but can't, due to circular imports. The alternative is a giant hs-boot file, or lumping thousands of lines into Derive.Deriver.Monad. Currently it's a plain function but if I want logging and exceptions I could use Derive.Deriver.DeriveM. It still wouldn't solve the main problem, which is that I can't reuse the Deriver functions, and instead have to rewrite them.
See NOTE [control-function].
CFunction | |
|
A simple pure function.
A stripped down Derive.Deriver.Monad.Dynamic for ControlFunctions
to use. The duplication is unfortunate, see CFunction
.
Dynamic | |
|