Karya, built on 2023-08-29T07:47:28 (patch 7a412d5d6ba4968ca4155ef276a062ccdeb9109a)
Safe HaskellSafe-Inferred

Cmd.Cmd

Description

Core CmdT monad that cmds run in.

A Cmd is what user actions turn into. The main thing they do is edit Ui.State, or Cmd.State, but a special subset can also do IO actions like saving and loading files.

The Cmd monad has two kinds of exception: abort or throw. Abort means that the Cmd decided that it's not the proper Cmd for this Msg (keystroke, mouse movement, whatever) and another Cmd should get a crack at it. Throw means that the Cmd failed and there is nothing to be done but log an error. When an exception is thrown, the ui and cmd states are rolled back and midi output is discarded.

Cmds should be in the monad Cmd.M m => m ....

They have to be polymorphic because they run in both IO and Identity. IO because some cmds such saving and loading files require IO, and Identity because the majority of cmds don't. REPL cmds run in IO so they can load and save, and the result is that any cmd that wants to be used from both Identity cmds (bound to keystrokes) and the REPL must be polymorphic in the monad.

Previously I used M instead of Monad m => CmdT m ... to establish Functor, but post-AMP I don't need that any more. But to maintain consistency I'll keep using M.

Synopsis

Documentation

data Backend Source #

This merges the compiled-id Inst.Backend and the per-score UiConfig.Backend.

Instances

Instances details
Show Backend Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty Backend Source # 
Instance details

Defined in Cmd.Cmd

data ResolvedInstrument Source #

This is an instrument as looked up by lookup_instrument or get_lookup_instrument. This merges compiled-in and runtime instrument data.

data Modifier Source #

Constructors

KeyMod Key.Modifier 
MouseMod Types.MouseButton (Maybe.Maybe (Types.TrackNum, UiMsg.Track))

Mouse button, and track it went down at, if any. The block is not recorded. You can't drag across blocks so you know any click must apply to the focused block.

MidiMod Midi.Channel Midi.Key

Only chan and key are stored. While it may be useful to map according to the device, this code doesn't know which devices are available. Block or track level handlers can query the device themselves.

Instances

Instances details
Read Modifier Source # 
Instance details

Defined in Cmd.Cmd

Show Modifier Source # 
Instance details

Defined in Cmd.Cmd

Eq Modifier Source # 
Instance details

Defined in Cmd.Cmd

Ord Modifier Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty Modifier Source # 
Instance details

Defined in Cmd.Cmd

data SelectionHistory Source #

Remember previous selections. This should be updated only by significant movements, so clicks and cmd-a, but not hjkl stuff.

data HistoryEntry Source #

Constructors

HistoryEntry 

Fields

  • hist_state :: !Ui.State
     
  • hist_damage :: !Update.UiDamage

    Since track event updates are not caught by diff but recorded by Ui.State, I have to save those too, or else an undo or redo will miss the event changes. TODO ugly, can I avoid this?

    If this HistoryEntry is in the past, these are the updates that took it to the future, not the updates emitted by the cmd itself. If the HistoryEntry is in the future, the updates take it to the past, which are the updated emitted by the cmd. So don't be confused if it looks like a HistoryEntry has the wrong updates.

  • hist_names :: ![Text]

    Cmds involved creating this entry.

  • hist_commit :: !(Maybe.Maybe GitT.Commit)

    The Commit where this entry was saved. Nothing if the entry is unsaved.

Instances

Instances details
Show HistoryEntry Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty HistoryEntry Source # 
Instance details

Defined in Cmd.Cmd

data HistoryCollect Source #

Constructors

HistoryCollect 

Fields

  • state_cmd_names :: ![Text]

    This is cleared after each cmd. A cmd can cons its name on, and the cmd is recorded with the (optional) set of names it returns. Hopefully each cmd has at least one name, since this makes the history more readable. There can be more than one name if the history records several cmds or if one cmd calls another.

  • state_suppress_edit :: !(Maybe.Maybe EditMode)

    Suppress history record until the EditMode changes from the given one. This is a bit of a hack so that every keystroke in a raw edit isn't recorded separately.

  • state_suppressed :: !(Maybe.Maybe SaveGitT.SaveHistory)

    The Git.Commit in the SaveHistory should definitely be Nothing.

Instances

Instances details
Show HistoryCollect Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty HistoryCollect Source # 
Instance details

Defined in Cmd.Cmd

data HistoryConfig Source #

Constructors

HistoryConfig 

Fields

  • hist_keep :: !Int

    Keep this many previous history entries in memory.

  • hist_last_commit :: !(Maybe.Maybe GitT.Commit)

    Checkpoints are saved relative to the state at the next checkpoint. So it's important to keep the commit of that checkpoint up to date, otherwise the state and the checkpoints will get out of sync.

Instances

Instances details
Show HistoryConfig Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty HistoryConfig Source # 
Instance details

Defined in Cmd.Cmd

data LastCmd Source #

Record some information about the last cmd for the benefit of maintain_history.

Constructors

UndoRedo

This cmd set the state because it was an undo or redo. Otherwise undo and redo themselves would be recorded and multiple undo would be impossible!

Load (Maybe.Maybe GitT.Commit) [Text]

This cmd set the state because of a load. This should reset all the history so I can start loading from the new state's history.

Instances

Instances details
Show LastCmd Source # 
Instance details

Defined in Cmd.Cmd

data History Source #

Ghosts of state past, present, and future.

Constructors

History 

Fields

  • hist_past :: ![HistoryEntry]
     
  • hist_present :: !HistoryEntry

    The present is actually the immediate past. When you undo, the undo itself is actually in the future of the state you want to undo. So another way of looking at it is that you undo from the past to a point further in the past. But since you always require a "recent past" to exist, it's more convenient to break it out and call it the "present". Isn't time travel confusing?

  • hist_future :: ![HistoryEntry]
     
  • hist_last_cmd :: !(Maybe.Maybe LastCmd)
     

Instances

Instances details
Show History Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty History Source # 
Instance details

Defined in Cmd.Cmd

type InstrumentDb = Inst.Db InstrumentCode Source #

Instantiate Inst.Db with the code type. The only reason the Db has the type parameter is so I can define it in its own module without a circular import.

type InstrumentPostproc = Score.Event -> (Score.Event, [Log.Msg]) Source #

Process each event before conversion. This is like a postproc call, but it can only map events 1:1 and you don't have to explicitly call it.

This can change the duration, but should not change Score.event_start, because the events are not resorted afterwards. Also, it's applied during conversion, so it only makes sense to modify Score.event_duration, Score.event_controls, Score.event_pitch, and Score.event_environ. TODO so I could have it return just those? But then it has to return Maybe to not modify and needs a record type.

data InstrumentCode Source #

The code part of an instrument, i.e. the calls and cmds it brings into scope.

This has to be in Cmd.Cmd for circular import reasons.

Constructors

InstrumentCode 

Fields

Instances

Instances details
Show InstrumentCode Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty InstrumentCode Source # 
Instance details

Defined in Cmd.Cmd

data WriteDeviceState Source #

Constructors

WriteDeviceState 

Fields

Instances

Instances details
Show WriteDeviceState Source # 
Instance details

Defined in Cmd.Cmd

Eq WriteDeviceState Source # 
Instance details

Defined in Cmd.Cmd

data Action Source #

Repeat a recorded action.

Select event and duration and hit shift-1 to record InsertEvent. Text edits record ReplaceText, PrependText, or AppendText in the last action field (bound to .), which you can then save.

Constructors

InsertEvent !(Maybe.Maybe TrackTime) !Text

If a duration is given, the event has that duration, otherwise it gets the current time step.

ReplaceText !Text 
PrependText !Text 
AppendText !Text 

Instances

Instances details
Show Action Source # 
Instance details

Defined in Cmd.Cmd

Eq Action Source # 
Instance details

Defined in Cmd.Cmd

Methods

(==) :: Action -> Action -> Bool #

(/=) :: Action -> Action -> Bool #

Pretty.Pretty Action Source # 
Instance details

Defined in Cmd.Cmd

data EditMode Source #

These enable various commands to edit event text. What exactly val and method mean are dependent on the track.

Constructors

NoEdit 
ValEdit 
MethodEdit 

Instances

Instances details
Show EditMode Source # 
Instance details

Defined in Cmd.Cmd

Eq EditMode Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty EditMode Source # 
Instance details

Defined in Cmd.Cmd

data EditState Source #

Editing state, modified in the course of editing.

Constructors

EditState 

Fields

Instances

Instances details
Show EditState Source # 
Instance details

Defined in Cmd.Cmd

Eq EditState Source # 
Instance details

Defined in Cmd.Cmd

type TrackSelection = (Sel.Selection, BlockId, Maybe.Maybe TrackId) Source #

Just a Sel.Selection annotated with its BlockId and TrackId. There's no deep reason for it, it just saves a bit of work for selection hooks.

newtype Hooks Source #

Hooks are Cmds that run after some event.

Constructors

Hooks 

Fields

Instances

Instances details
Monoid Hooks Source # 
Instance details

Defined in Cmd.Cmd

Methods

mempty :: Hooks #

mappend :: Hooks -> Hooks -> Hooks #

mconcat :: [Hooks] -> Hooks #

Semigroup Hooks Source # 
Instance details

Defined in Cmd.Cmd

Methods

(<>) :: Hooks -> Hooks -> Hooks #

sconcat :: NonEmpty Hooks -> Hooks #

stimes :: Integral b => b -> Hooks -> Hooks #

Show Hooks Source # 
Instance details

Defined in Cmd.Cmd

Methods

showsPrec :: Int -> Hooks -> ShowS #

show :: Hooks -> String #

showList :: [Hooks] -> ShowS #

data SyncConfig Source #

Configure synchronization. MMC is used to set the play position and MTC is used to start and stop playing.

MMC has start and stop msgs, but they seem useless, since they're sysexes, which are not delivered precisely.

Constructors

SyncConfig 

Fields

  • sync_device :: !Midi.WriteDevice
     
  • sync_device_id :: !Mmc.DeviceId

    Send MMC to this device.

  • sync_mtc :: !Bool

    If true, send MTC on the sync_device. If this is set, MMC play and stop will be omitted, since the presence of MTC should be enough to get the DAW started, provided it's in external sync mode.

    DAWs tend to spend a long time synchronizing, presumably because hardware devices take time to spin up. That's unnecessary in software, so in Cubase you can set "lock frames" to 2, and in Reaper you can set "synchronize by seeking ahead" to 67ms.

  • sync_frame_rate :: !Midi.FrameRate
     

Instances

Instances details
Show SyncConfig Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty SyncConfig Source # 
Instance details

Defined in Cmd.Cmd

data StepState Source #

Step play is a way of playing back the performance in non-realtime.

Constructors

StepState 

Fields

Instances

Instances details
Show StepState Source # 
Instance details

Defined in Cmd.Cmd

newtype Thread Source #

Wrap Async to make it showable. I use Async instead of ThreadId because I want to make sure they can run their finalizers when the app quits, and I can wait on an Async, but not on a ThreadId. At the moment, the finalizers are killing im subprocesses. kill_thread uses Async.cancel, which synchronously waits for the thread to complete.

Constructors

Thread (Async.Async ()) 

Instances

Instances details
Show Thread Source # 
Instance details

Defined in Cmd.Cmd

data PlayCmd Source #

Wrapper around CmdId PlayArgs to make it Showable.

Constructors

PlayCmd !Text !(CmdId PlayArgs) 

Instances

Instances details
Show PlayCmd Source # 
Instance details

Defined in Cmd.Cmd

data PlayState Source #

State concerning derivation, performance, and playing the performance.

Constructors

PlayState 

Fields

Instances

Instances details
Show PlayState Source # 
Instance details

Defined in Cmd.Cmd

data Config Source #

Config type variables that change never or rarely. These mostly come from the App.StaticConfig.

Constructors

Config 

Fields

Instances

Instances details
Show Config Source # 
Instance details

Defined in Cmd.Cmd

data Fingerprint Source #

Keep track of loaded files and a fingerprint for their contents. This is used to detect when they should be reloaded.

Constructors

Fingerprint ![FilePath] !Int 

Instances

Instances details
Monoid Fingerprint Source # 
Instance details

Defined in Cmd.Cmd

Semigroup Fingerprint Source # 
Instance details

Defined in Cmd.Cmd

Show Fingerprint Source # 
Instance details

Defined in Cmd.Cmd

Eq Fingerprint Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty Fingerprint Source # 
Instance details

Defined in Cmd.Cmd

data KyCache Source #

A loaded and parsed ky file, or an error string. This also has the files loaded and their timestamps, to detect when one has changed.

Constructors

KyCache !(Either Text (Builtins, InstrumentAliases)) !Fingerprint 
PermanentKy !(Builtins, InstrumentAliases)

This disables the cache mechanism. Tests use this to avoid having to set SaveFile.

Instances

Instances details
Show KyCache Source # 
Instance details

Defined in Cmd.Cmd

data KeycapsState Source #

The set of things that can affect a keycaps window. So when this changes, the window has to be updated. I assume the KeycapsT.Layout is constant, so it's not in here, which allows me to cache global keymaps in CAFs.

Instances

Instances details
Show KeycapsState Source # 
Instance details

Defined in Cmd.Cmd

Eq KeycapsState Source # 
Instance details

Defined in Cmd.Cmd

data SavedState Source #

Constructors

JustLoaded

Just loaded from a file. This is almost like SavedChanges, except that it's required so sync_status can tell the difference between the state changing because it was just loaded (set to SavedChanges) and changing due to an edit (set to UnsavedChanges).

UnsavedChanges 
SavedChanges 

Instances

Instances details
Show SavedState Source # 
Instance details

Defined in Cmd.Cmd

Eq SavedState Source # 
Instance details

Defined in Cmd.Cmd

data Saved Source #

This tracks how much the score has been saved to disk.

Constructors

Saved 

Instances

Instances details
Show Saved Source # 
Instance details

Defined in Cmd.Cmd

Methods

showsPrec :: Int -> Saved -> ShowS #

show :: Saved -> String #

showList :: [Saved] -> ShowS #

Eq Saved Source # 
Instance details

Defined in Cmd.Cmd

Methods

(==) :: Saved -> Saved -> Bool #

(/=) :: Saved -> Saved -> Bool #

data Writable Source #

Constructors

ReadWrite 
ReadOnly 

Instances

Instances details
Show Writable Source # 
Instance details

Defined in Cmd.Cmd

Eq Writable Source # 
Instance details

Defined in Cmd.Cmd

data SaveFile Source #

Instances

Instances details
Show SaveFile Source # 
Instance details

Defined in Cmd.Cmd

Eq SaveFile Source # 
Instance details

Defined in Cmd.Cmd

data State Source #

App global state. Unlike Ui.State, this is not saved to disk. This is normally modified inside a CmdT, which is also a StateT, so it can also use the UI state functions. If an exception is thrown, both this state and the UI state will be rolled back.

This is kind of an unorganized wodge. The problem is that since state is all centralized in one place, every special snowflake Cmd that needs its own bit of state winds up getting its own little knob in here. On one hand, it's non-modular. On the other hand, it lets me keep an eye on it.

So far, most Cmds are pretty fundamental, so they more or less deserve their spots here. If it gets out of control, though, I'll have to either come up with a clever way of storing typed data where they can't collide, say by having a Cmd return a new Cmd and keeping the state trapped inside, or a less clever but simpler and easier way like Map Name Dynamic.

Constructors

State 

Fields

Instances

Instances details
Show State Source # 
Instance details

Defined in Cmd.Cmd

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

data Thru Source #

Constructors

MidiThru !Interface.Message

Send MIDI thru. You can give it a timestamp, but it should be 0 for thru, which will cause it to go straight to the front of the queue. Use midi for normal midi thru.

ImThru !Thru.Message 
OscThru ![OSC.OSC] 

Instances

Instances details
Show Thru Source # 
Instance details

Defined in Cmd.Cmd

Methods

showsPrec :: Int -> Thru -> ShowS #

show :: Thru -> String #

showList :: [Thru] -> ShowS #

class (Log.LogMonad m, Ui.M m) => M m where Source #

Methods

get :: m State Source #

put :: State -> m () Source #

write_thru :: Thru -> m () Source #

Log a note to send out. This is the midi or im thru mechanism.

abort :: m a Source #

An abort is an exception to get out of CmdT, but it's considered the same as returning Continue. It's so a command can back out if e.g. it's selected by the Handler but has an additional prerequisite such as having an active block.

catch_abort :: m a -> m (Maybe.Maybe a) Source #

Instances

Instances details
Monad m => M (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

newtype CmdT m a Source #

Constructors

CmdT (CmdStack m a) 

Instances

Instances details
MonadTrans CmdT Source #

For some reason, newtype deriving doesn't work on MonadTrans.

Instance details

Defined in Cmd.Cmd

Methods

lift :: Monad m => m a -> CmdT m a #

Monad m => MonadError Ui.Error (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Methods

throwError :: Ui.Error -> CmdT m a #

catchError :: CmdT m a -> (Ui.Error -> CmdT m a) -> CmdT m a #

MonadIO m => MonadIO (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Methods

liftIO :: IO a -> CmdT m a #

Monad m => Applicative (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Methods

pure :: a -> CmdT m a #

(<*>) :: CmdT m (a -> b) -> CmdT m a -> CmdT m b #

liftA2 :: (a -> b -> c) -> CmdT m a -> CmdT m b -> CmdT m c #

(*>) :: CmdT m a -> CmdT m b -> CmdT m b #

(<*) :: CmdT m a -> CmdT m b -> CmdT m a #

Functor m => Functor (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Methods

fmap :: (a -> b) -> CmdT m a -> CmdT m b #

(<$) :: a -> CmdT m b -> CmdT m a #

Monad m => Monad (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Methods

(>>=) :: CmdT m a -> (a -> CmdT m b) -> CmdT m b #

(>>) :: CmdT m a -> CmdT m b -> CmdT m b #

return :: a -> CmdT m a #

Monad m => M (CmdT m) Source # 
Instance details

Defined in Cmd.Cmd

Monad m => Ui.M (CmdT m) Source #

And to the UI state operations.

Instance details

Defined in Cmd.Cmd

Monad m => Log.LogMonad (CmdT m) Source #

Give CmdT unlifted access to all the logging functions.

Instance details

Defined in Cmd.Cmd

Methods

write :: Log.Msg -> CmdT m () Source #

type Result a = (State, [Thru], [Log.Msg], Either Ui.Error (a, Ui.State, Update.UiDamage)) Source #

The result of running a Cmd.

type RunCmd cmd_m val_m a = Ui.State -> State -> CmdT cmd_m a -> val_m (Result a) Source #

Cmds can run in either Identity or IO, but are generally returned in IO, just to make things uniform.

data FloatingInput Source #

Constructors

FloatingOpen !ViewId !Types.TrackNum !ScoreTime !Text !(Int, Int)

Open a new floating text input. View, track, pos, (select start, select end).

FloatingInsert !Text

Insert the given text into an already open edit box.

Instances

Instances details
Show FloatingInput Source # 
Instance details

Defined in Cmd.Cmd

data PlayArgs Source #

Arguments for play. This is a special return value to trigger a play, see Cmd.PlayC for details.

Constructors

PlayArgs 

Fields

Instances

Instances details
Show PlayArgs Source # 
Instance details

Defined in Cmd.Cmd

data Status Source #

Constructors

Continue

Continue processing, so another Cmd will have an opportunity to see the Msg.

Done

Stop further cmd processing, "consuming" the Msg.

Play !PlayArgs

Hack to control import dependencies, see Cmd.PlayC.

FloatingInput !FloatingInput

Open a FloatingInput box.

Quit

Pack it up and go home.

Instances

Instances details
Show Status Source # 
Instance details

Defined in Cmd.Cmd

type CmdL a = CmdT IO a Source #

Cmds used by the REPL, which all run in IO.

data MouseOn Source #

Where a click or drag occurred.

Instances

Instances details
Show MouseOn Source # 
Instance details

Defined in Cmd.Cmd

Eq MouseOn Source # 
Instance details

Defined in Cmd.Cmd

Methods

(==) :: MouseOn -> MouseOn -> Bool #

(/=) :: MouseOn -> MouseOn -> Bool #

Ord MouseOn Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty MouseOn Source # 
Instance details

Defined in Cmd.Cmd

data Bindable Source #

Constructors

Key Bool Key.Key

Key IsRepeat Key

Click Types.MouseButton MouseOn Int

Click MouseButton Clicks

Drag Types.MouseButton MouseOn 
Release Types.MouseButton MouseOn

Mouse button release.

Note Midi.Channel Midi.Key

Channel can be used to restrict bindings to a certain keyboard. This should probably be something more abstract though, such as a device which can be set by the static config.

Instances

Instances details
Show Bindable Source # 
Instance details

Defined in Cmd.Cmd

Eq Bindable Source # 
Instance details

Defined in Cmd.Cmd

Ord Bindable Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty Bindable Source # 
Instance details

Defined in Cmd.Cmd

data KeySpec Source #

Constructors

KeySpec !(Set Modifier) !Bindable 

Instances

Instances details
Show KeySpec Source # 
Instance details

Defined in Cmd.Cmd

Eq KeySpec Source # 
Instance details

Defined in Cmd.Cmd

Methods

(==) :: KeySpec -> KeySpec -> Bool #

(/=) :: KeySpec -> KeySpec -> Bool #

Ord KeySpec Source # 
Instance details

Defined in Cmd.Cmd

Pretty.Pretty KeySpec Source # 
Instance details

Defined in Cmd.Cmd

data NoteEntryMap a Source #

NoteEntry might depend on base octave, and might have different mappings for unshifted or shifted.

Instances

Instances details
Functor NoteEntryMap Source # 
Instance details

Defined in Cmd.Cmd

Methods

fmap :: (a -> b) -> NoteEntryMap a -> NoteEntryMap b #

(<$) :: a -> NoteEntryMap b -> NoteEntryMap a #

Show a => Show (NoteEntryMap a) Source # 
Instance details

Defined in Cmd.Cmd

data NamedCmd m Source #

Pair a Cmd with a Doc that can be used for logging, undo, etc.

Constructors

NamedCmd 

Fields

Instances

Instances details
Pretty.Pretty (NamedCmd m) Source # 
Instance details

Defined in Cmd.Cmd

data Handler m Source #

This is the toplevel object representing a cmd. Fundamentally it's just Msg -> Status, but it's also wrapped up in some documentation, so cmds can be introspected.

Instances

Instances details
Pretty.Pretty (Handler m) Source # 
Instance details

Defined in Cmd.Cmd

call :: M m => Handler m -> Msg.Msg -> m Status Source #

mods_down :: M m => m (Set Modifier) Source #

Return the mods currently down, stripping out non-modifier keys and notes, so that overlapping keys will still match. Mouse mods are not filtered, so each mouse chord can be bound individually.

merge_status :: Status -> Status -> Status Source #

Combine two Statuses by keeping the one with higher priority. Yes, Status could be a Monoid but merge should be a rare operation.

run :: Monad m => a -> RunCmd m m a Source #

run_ :: Monad m => Ui.State -> State -> CmdT m a -> m (Either String (a, State, Ui.State), [Log.Msg]) Source #

Like run, but discard MIDI thru and updates.

eval :: Monad m => Ui.State -> State -> CmdT m a -> m (Either String a, [Log.Msg]) Source #

Like run_, but discard all the final states.

run_id :: Ui.State -> State -> CmdT Identity a -> Result (Maybe.Maybe a) Source #

Run the Cmd in Identity, returning Nothing if it aborted.

run_id_io :: RunCmd Identity IO Status Source #

Run the given command in Identity, but return it in IO, just as a convenient way to have a uniform return type with run (provided it is run in IO).

lift_id :: M m => CmdId a -> m a Source #

Promote a CmdId to a generic cmd, which can also run as a CmdT IO. TODO: shouldn't it be possible to do this for free?

sequence_cmds :: M m => [a -> m Status] -> a -> m Status Source #

Run a set of Cmds as a single Cmd. The first one to return non-Continue will return. Cmds can use this to dispatch to other Cmds.

osc :: M m => [OSC.OSC] -> m () Source #

throw :: (CallStack.Stack, M m) => Text -> m a Source #

This is the same as Ui.throw, but it feels like things in Cmd may not always want to reuse State's exceptions, so they should call this one.

ignore_abort :: M m => m a -> m () Source #

Run a subcomputation that is allowed to abort.

rethrow_io :: IO a -> CmdT IO a Source #

Run an IO action, rethrowing any IO exception as a Cmd exception.

abort_unless :: M m => Maybe.Maybe a -> m a Source #

Extract a Just value, or abort. Generally used to check for Cmd conditions that don't fit into a Keymap.

require :: (CallStack.Stack, M m) => Text -> Maybe.Maybe a -> m a Source #

Throw an exception with the given msg on Nothing.

require_right :: (CallStack.Stack, M m) => (err -> Text) -> Either err a -> m a Source #

state_save_dir :: State -> Maybe.Maybe FilePath Source #

Absolute directory of the save file.

score_path :: State -> FilePath Source #

Unique name for this score, for the global im cache.

reinit_state :: HistoryEntry -> State -> State Source #

Reset the parts of the State which are specific to a "session". This should be called whenever an entirely new state is loaded.

state_midi_writer :: State -> Interface.Message -> IO () Source #

Get a midi writer that takes the config_wdev_map into account.

to_absolute :: State -> Path.Relative -> FilePath Source #

Convert a relative path to place it in the app dir.

lookup_scale :: LookupScale Source #

This was previously in Config, and configured via StaticConfig. But it turns out I don't really use StaticConfig. It has a name here just so I don't get references to Scale.All.lookup_scale everywhere.

running_threads :: CmdT IO [BlockId] Source #

Get currently evaluating root BlockIds.

strip_modifier :: Modifier -> Modifier Source #

Take a modifier to its key in the modifier map which has extra info like mouse down position stripped.

gets :: M m => (State -> a) -> m a Source #

modify :: M m => (State -> State) -> m () Source #

get_screen :: M m => Maybe.Maybe (Int, Int) -> m Rect.Rect Source #

Return the rect of the screen closest to the given point, or the default.

invalidate_performances :: M m => m () Source #

Clear all performances, which will cause them to be rederived. This is stronger than Ui.update_all, because Ui.update_all will simply cause diff to look at the blocks for diffs, while this will force a re-derivation even if there are no apparent diffs.

keys_down :: M m => m (Map Modifier Modifier) Source #

Keys currently held down, as in state_keys_down.

lookup_focused_block :: M m => m (Maybe.Maybe BlockId) Source #

In some circumstances I don't want to abort if there's no focused block.

focus :: Ui.M m => ViewId -> m () Source #

Request focus. state_focused_view will be updated once fltk reports the focus change.

get_insert_tracknum :: M m => m (Maybe.Maybe Types.TrackNum) Source #

Get the leftmost track covered by the insert selection, which is considered the "focused" track by convention.

set_view_status :: M m => ViewId -> (Int, Text) -> Maybe.Maybe Text -> m () Source #

This just calls Ui.set_view_status, but all status setting should go through here so they can be uniformly filtered or logged or something.

set_global_status :: M m => Text -> Text -> m () Source #

Emit a special log msg that will cause log view to put this key and value in its status bar. A value of "" will cause logview to delete that key.

set_status :: M m => (Int, Text) -> Maybe.Maybe Text -> m () Source #

Set a status variable on all views.

memoized_instrument :: UiConfig.Allocations -> InstrumentDb -> ScoreT.Instrument -> Either Text ResolvedInstrument Source #

This memoizes instrument resolution in case you're going to do it a lot. resolve_instrument has to merge some things so it's not exactly free. The spine-strict Map makes this less efficient for one-off lookups, but so far all uses are mapping the lookup across many events.

Of course, the memoization only works as long as the memo table persists, which should happen if you use get_lookup_instrument and reuse the function it returns.

lookup_qualified :: M m => InstT.Qualified -> m (Maybe.Maybe Inst) Source #

Look up an instrument that might not be allocated.

derive_immediately :: M m => [BlockId] -> m () Source #

inflict_block_damage :: M m => BlockId -> m () Source #

Cause a block to rederive even if there haven't been any edits on it.

inflict_track_damage :: M m => BlockId -> TrackId -> m () Source #

Cause a track to rederive even if there haven't been any edits on it.

set_edit_box :: M m => Block.Box -> Block.Box -> m () Source #

At the Ui level, the edit box is per-block, but I use it to indicate edit mode, which is global. So it gets stored in Cmd.State and must be synced with new blocks.

set_note_text :: M m => Text -> m () Source #

name :: M m => Text -> m a -> m a Source #

Give a name to a Cmd. The name is applied when the cmd returns so the names come out in call order, and it doesn't incur overhead for cmds that abort.

suppress_history :: M m => EditMode -> Text -> m a -> m a Source #

Like name, but also set the state_suppress_edit. This will suppress history recording until the edit mode changes from the given one.

log_event :: BlockId -> TrackId -> Event.Event -> Text Source #

Log an event so that it can be clicked on in logview.

all_notes_off :: M m => m () Source #

Turn off all sounding notes, reset controls. TODO clear out WriteDeviceState?

data Performance Source #

This holds the final performance for a given block. It is used to actually play music, and poked and prodded in a separate thread to control its evaluation.

This is basically the same as Result. I could make them be the same, but Performance wasn't always the same and may not be the same in the future.

Unlike other records, the fields here are all lazy. This is because I need to put an unevaluated Performance into Cmd.state_current_performances, and then force the fields in a separate thread. Also I need to modify perf_damage without forcing any of the others.

Constructors

Performance 

Fields

Instances

Instances details
Show Performance Source # 
Instance details

Defined in Cmd.Msg

Pretty.Pretty Performance Source # 
Instance details

Defined in Cmd.Msg