Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Monad m => Launchable m where
- runIO :: LiveProgram m -> LiveProgram IO
- liveMain :: Launchable m => LiveProgram m -> IO ()
- foreground :: Monad m => LiveProgram m -> m ()
- data LaunchedProgram (m :: * -> *) = LaunchedProgram {
- programVar :: MVar (LiveProgram IO)
- threadId :: ThreadId
- launch :: Launchable m => LiveProgram m -> IO (LaunchedProgram m)
- update :: Launchable m => LaunchedProgram m -> LiveProgram m -> IO ()
- stop :: Launchable m => LaunchedProgram m -> IO ()
- launchWithDebugger :: (Monad m, Launchable m) => LiveProgram m -> Debugger m -> IO (LaunchedProgram m)
- background :: MVar (LiveProgram IO) -> IO ()
- stepProgram :: Monad m => LiveProgram m -> m (LiveProgram m)
- stepLaunchedProgram :: (Monad m, Launchable m) => LaunchedProgram m -> IO ()
Documentation
class Monad m => Launchable m where Source #
Monads in which live programs can be launched in IO
,
for example when you have special effects that have to be handled on every reload.
The only thing necessary is to transform the LiveProgram
into one in the IO
monad, and the rest is taken care of in the framework.
runIO :: LiveProgram m -> LiveProgram IO Source #
Instances
Launchable IO Source # | |
Defined in LiveCoding.RuntimeIO.Launch runIO :: LiveProgram IO -> LiveProgram IO Source # | |
(Typeable m, Launchable m) => Launchable (HandlingStateT m) Source # | |
Defined in LiveCoding.RuntimeIO.Launch runIO :: LiveProgram (HandlingStateT m) -> LiveProgram IO Source # | |
(Data e, Finite e, Launchable m) => Launchable (ExceptT e m) Source # | Upon an exception, the program is restarted. To handle or log the exception, see LiveCoding.LiveProgram.Except. |
Defined in LiveCoding.RuntimeIO.Launch runIO :: LiveProgram (ExceptT e m) -> LiveProgram IO Source # |
liveMain :: Launchable m => LiveProgram m -> IO () Source #
The standard top level main
for a live program.
Typically, you will define a top level LiveProgram
in some monad like
,
and then add these two lines of boiler plate:HandlingStateT
IO
main :: IO () main = liveMain liveProgram
foreground :: Monad m => LiveProgram m -> m () Source #
Launch a LiveProgram
in the foreground thread (blocking).
data LaunchedProgram (m :: * -> *) Source #
A launched LiveProgram
and the thread in which it is running.
launch :: Launchable m => LiveProgram m -> IO (LaunchedProgram m) Source #
Launch a LiveProgram
in a separate thread.
The MVar
can be used to update
the program while automatically migrating it.
The ThreadId
represents the thread where the program runs in.
You're advised not to kill it directly, but to run stop
instead.
update :: Launchable m => LaunchedProgram m -> LiveProgram m -> IO () Source #
Migrate (using hotCodeSwap
) the LiveProgram
to a new version.
stop :: Launchable m => LaunchedProgram m -> IO () Source #
Stops a thread where a LiveProgram
is being executed.
Before the thread is killed, an empty program (in the monad m
) is first inserted and stepped.
This can be used to call cleanup actions encoded in the monad,
such as HandlingStateT
.
launchWithDebugger :: (Monad m, Launchable m) => LiveProgram m -> Debugger m -> IO (LaunchedProgram m) Source #
Launch a LiveProgram
, but first attach a debugger to it.
background :: MVar (LiveProgram IO) -> IO () Source #
This is the background task executed by launch
.
stepProgram :: Monad m => LiveProgram m -> m (LiveProgram m) Source #
Advance a LiveProgram
by a single step.
stepLaunchedProgram :: (Monad m, Launchable m) => LaunchedProgram m -> IO () Source #
Advance a launched LiveProgram
by a single step and store the result.