| Copyright | Copyright 2016 Ertugrul Söylemez |
|---|---|
| License | Apache License 2.0 |
| Maintainer | Ertugrul Söylemez <esz@posteo.de> |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Rapid
Contents
Description
This library provides a safer and more convenient wrapper around the foreign-store library.
You can use it for background services within a GHCi session that survive loading, reloading and unloading modules, which is particularly useful when writing long-running programs like servers and user interfaces.
Please read the "Safety and securty" section below!
- data Rapid k
- rapid :: forall k r. Word32 -> (Rapid k -> IO r) -> IO r
- restart :: Ord k => Rapid k -> k -> IO () -> IO ()
- start :: Ord k => Rapid k -> k -> IO () -> IO ()
- stop :: Ord k => Rapid k -> k -> x -> IO ()
- createRef :: (Ord k, Typeable a) => Rapid k -> k -> IO a -> IO a
- deleteRef :: Ord k => Rapid k -> k -> IO ()
- writeRef :: (Ord k, Typeable a) => Rapid k -> k -> IO a -> IO a
Introduction
To use this library in your project create a module conventionally named
DevelMain that exports an action conventionally named update:
module DevelMain (update) where
import Rapid
update :: IO ()
update =
rapid 0 $ \r ->
-- Your service management goes here.
pure ()The idea is that within a GHCi session this update action is run
whenever you want to reload your project during development. In the
simplest case, like in a web application, your project consists of a
single service that is just restarted each time you reload. Here is an
example using the Snap Framework:
import qualified Data.Text as T
import Rapid
import Snap.Core
import Snap.Http.Server
update =
rapid 0 $ \r ->
restart r "webserver" $
quickHttpServe (writeText (T.pack "Hello world!"))Once you run update in a GHCi session, a server is started (port 8000)
that keeps running in the background, even when you reload modules. The
REPL is fully responsive, so you can continue working. When you want to
apply the changes you have made, you run update again. To see this in
action, change the text string in the example, reload the module and
then run update. Also observe that nothing is changed until you
actually run update.
When you want to stop a running background thread, replace restart
within the update action by stop and run update. The action given
to stop is actually ignored. It only takes the action argument for
your convenience.
You can run multiple threads at the same time and also have threads that are not restarted during a reload, but are only started and then kept running:
update =
rapid 0 $ \r ->
start r "database" myDatabase
start r "worker" myBackgroundWorker
restart r "webserver" myWebServerUsually you would put restart in front of the component that you are
currently working on, while using start with all others.
Communication
If you need your background threads to communicate with each other, for
example by using concurrency primitives, some additional support is
required. You cannot just create a TVar within your update action.
It would be a different one for every invocation, so threads that are
restarted would not communicate with already running threads, because
they would use a fresh TVar, while the old threads would still use the
old one.
To solve this, you need to wrap your newTVar action with createRef.
The TVar created this way will survive reloads in the same way as
background threads do. In particular, if there is already one from an
older invocation of update, it will be reused:
import Control.Concurrent.STM
import Control.Monad
import Rapid
update =
rapid 0 $ \r -> do
mv1 <- createRef r "var1" newEmptyTMVarIO
mv2 <- createRef r "var2" newEmptyTMVarIO
start r "producer" $
mapM_ (atomically . putTMVar mv1) [0 :: Integer ..]
restart r "consumer" $
forever . atomically $ do
x <- takeTMVar mv1
putTMVar mv2 (x, "blah")
-- For debugging the update action:
replicateM_ 3 $
atomically (takeTMVar mv2) >>= printYou can now change the string "blah" in the consumer thread and then
run update. You will notice that the numbers in the left component of
the tuples keep increasing even after a reload, while the string in the
right component changes. That means the producer thread was not
restarted, but the consumer thread was. Yet the restarted consumer
thread still refers to the same TVar as before, so it still receives
from the producer.
Reusing expensive resources
Mutable references as introduced in the previous section can also be used to shorten the development cycle in the case when an expensive resource has to be created. As an example imagine that you need to parse a huge file into a data structure. You can keep the result of that in memory across reloads. Example with parsing JSON:
import Control.Exception
import Data.Aeson
import qualified Data.ByteString as B
update =
rapid 0 $ \r ->
value <- createRef r "file" $
B.readFile "blah.json" >>=
either (throwIO . userError) pure . eitherDecode
-- You can now reuse 'value' across reloads.If you want to recreate the value at some point, you can just change
createRef to writeRef and then run update. Keep in mind to change
it back createRef afterward. Use deleteRef to remove values you no
longer need, so they can be garbage-collected.
Emacs integration
This library integrates well with
haskell-interactive-mode,
particularly with its somewhat hidden
haskell-process-reload-devel-main function.
This function finds your DevelMain module by looking for a buffer
named DevelMain.hs, loads or reloads it in your current project's
interactive session and then runs update. Assuming that you are
already using haskell-interactive-mode all you need to do to use it is
to keep your DevelMain module open in a buffer and type M-x
haskell-process-reload-devel-main RET when you want to hot-reload. You
may want to bind it to a key:
(define-key haskell-mode-map (kbd "C-c m") 'haskell-process-reload-devel-main)
Since you will likely always reload the current module before running
update, you can save a few keystrokes by defining a small function
that does both and bind that one to a key instead:
(defun my-haskell-run-devel () "Reloads the current module and then hot-reloads code via DevelMain.update." (interactive) (haskell-process-load-file) (haskell-process-reload-devel-main)) (define-key haskell-mode-map (kbd "C-c m") 'my-haskell-run-devel)
Safety and security
It's easy to crash your GHCi session with this library. In order to prevent that, you must follow these rules:
- Do not change your service name type (the type argument of
Rapid, i.e. the second argument torestart,startandstop) within a session. The simplest way to do that is to resist the temptation to define a custom name type, and just use strings instead. If you do change the name type, you should restart GHCi. - Be careful with mutable variable created with
createRef: If the value type changes (e.g. constructors or fields were changed), the variable must be recreated, for example by usingwriteRefonce. This most likely entails restarting all threads that were using the variable. Again the safest option is to just restart GHCi. - If any package in the current environment changes (especially this
library itself), for example by updating a package via
cabalorstack, theupdateaction is likely to crash or go wrong in subtle ways due to binary incompatibility. If packages change, restart GHCi. - This library is a development tool! Do not even think of using it to hot-reload in a productive environment! There are much safer and more appropriate ways to hot-reload code in production, for example by using a plugin system.
The reason for this unsafety is that the underlying foreign-store library is itself very unsafe in nature and requires that we maintain binary compatibility. This library hides most of that unsafety, but still requires that you follow the rules above.
Please take the last rule seriously and never ever use this library in production! If something goes wrong during a reload, we do not get a convenient run-time exception; we get a memory violation, which can cause anything from a segfault to a remotely exploitable security hole.
Hot code reloading
Arguments
| :: Word32 | Store index (if in doubt, use 0). |
| -> (Rapid k -> IO r) | Action on the Rapid state. |
| -> IO r |
Retrieve the current Rapid state handle, and pass it to the given
continuation. If the state handle doesn't exist, it is created. The
key type k is used for naming reloadable services like threads.
Warning: The key type must not change during a session. If you need to change the key type, currently the safest option is to restart GHCi.
This function uses the foreign-store library to establish a state handle that survives GHCi reloads and is suitable for hot reloading.
The first argument is the Store index. If you do not use the
foreign-store library in your development workflow, just use 0,
otherwise use any unused index.
Threads
Arguments
| :: Ord k | |
| => Rapid k | Rapid state handle. |
| -> k | Name of the thread. |
| -> IO () | Action the thread runs. |
| -> IO () |
Create a thread with the given name that runs the given action.
The thread is restarted each time an update occurs.
start :: Ord k => Rapid k -> k -> IO () -> IO () Source #
Create a thread with the given name that runs the given action.
When an update occurs and the thread is currently not running, it is started.
stop :: Ord k => Rapid k -> k -> x -> IO () Source #
Delete the thread with the given name.
When an update occurs and the thread is currently running, it is cancelled.
Communication
Arguments
| :: (Ord k, Typeable a) | |
| => Rapid k | Rapid state handle. |
| -> k | Name of the mutable variable. |
| -> IO a | Action to create. |
| -> IO a |
Get the value of the mutable variable with the given name. If it does not exist, it is created and initialised with the value returned by the given action.
Mutable variables should only be used with values that can be
garbage-collected, for example communication primitives like
MVar and TVar, but also pure run-time
information that is expensive to generate, for example the parsed
contents of a file.
Delete the mutable variable with the given name, if it exists.
Arguments
| :: (Ord k, Typeable a) | |
| => Rapid k | Rapid state handle. |
| -> k | Name of the mutable variable. |
| -> IO a | Value action. |
| -> IO a |
Overwrite the mutable variable with the given name with the value returned by the given action. If the mutable variable does not exist, it is created.
This function may be used to change the value type of a mutable variable.