Skip to content

Transient execution model. How to get things done with the transient libraries

Alberto edited this page Oct 5, 2022 · 28 revisions

Haskell is not a conventional language. However, the basic elements of all languages are the same. Transient changes how the programmer does things in Haskell and other languages to make them, hopefully, simpler. To make things simpler and powerful, paradoxically, some of these things are done even less conventionally but more in the haskell way.

The way to program in transient is deeply influenced by his execution model, which is different from the single-threaded model, with explicit multithreading, explicit loops and explicit communications of any conventional way of programming, including the current one in Haskell. Transient uses techniques to perform implicit loops, implicit multithreading, implicit streaming, implicit exception management and implicit communications to make modular and composable code that otherwise would not be composable at all.

Rather than a long technical explanation, the best way to grasp it is through examples of practical usage cases. This why I mix here two apparent different topics: the execution model and how to do things in transient.

Here follow some practical guidelines about how to do some common tasks using transient.

Do NOT use loops.

Loops destroy composition. Use streaming/non-determinism (either multithreaded or not):

forM [1..10]  $ \i -> ...   use:   do i <- threads 0  $ choose [1..10] 
                                      ...   
                                   -- run in the current thread
-- like for i = 1 to 10... 
loop = do                                      do
    name <- getLine           use instead:        name <- waitEvents getLine
    liftIO $ print name                           liftIO $ print name
    loop 

Although getLine does not compose with multithreading since two threads can not getLine nicely and transient is intended to compose everything. For console IO, it is convenient to use specific transient primitives which permits the redirection of console IO to different threads and allows the creation of menus, like option or input

  do
     option "g" "getLine program"
     name <- input (const True) "enter name: " 
     liftIO $ print name

Do NOT use callbacks.

De-invert callbacks with react:

onCallback wathever myCallback    use:     event <- react (onCallback wathever) (return())         
myCallback event=                          continue event
        continue event

So, if you use a framework with callbacks, which are inherently non-composable, you can make composable code by de-inverting the callbacks, so you will create modular and readable code. This expression stop the computation and wait for invocations of the callback, and execute continue event whenever the callback is called.

You can Avoid IFs and be more modular

(just like Haskell parsers do)

       if processableByThis 
          then this 
          else that          use:     this' <|>  that
                                      where 
                                      this' = if not processableByThis then empty else this

Don't use a global session state

As any global variable, that destroys composition and transient is focused on making modular software components that can be composed.

globalState= create mutable var

do                                      do
  v <- readGlobalState            use:    setRState initiaState
  writeGlobalState v'                     (v :: MyType) <- getRState <|> error "no initialized state for this type??"   
                                          setRState v'
-- or, more Haskelly:

main= runReader initialState $ do 
  ...

Since the state is created inside the monadic function, it is modular and composable without further ado. The runReader alternative, very common in Haskell at the time I write this, is equivalent to a mutable global state.

Don't use big initial states

Since you can create as many of them as you need at the moment you need them as long as they have different types.

data Big= Big{
    this :: This
    that :: That                       do
    ...                                  setRState (this :: This)
}                             use:       use (this :: This)
                                         more lines
do                                       setRState (that :: That)
  runReader bigstate $ do                use that
      use this                           use this
      more lines                         ...
      use that
      more lines
      use this
      ...

This also allows quite simple access and modification of fields without the need for lenses. Use newtype keyword to assign different types to simple variables.

A pure (non-mutable) state can be defined and used the same way:

runState state $ do...           use           do
     v <- get                                     setState state
     put v'                                       v <- getState <|> error "MyState not initialized??"
     ...                                          setState v'
                                                  ...

When modifying a pure state, the changes are only accessible to the statements that are after the modification. Since in transient there are no loops and iterations are done using non-determinism, this may be confusing:

data Sum= Sum Int
do
  setSate $ Sum 0 
  n <- threads 0 $ choose [1,2 :: Int] 
  Sum sum  <- getState <|> error "no Sum??? I just initialized it two lines ago!!!"
  setState . Sum $ sum+n 
  Sum sum  <- getState
  liftIO $ print sum

would print 1 and 2 since choosewill send 1 and 2 to the rest of the monadic sequence. But the state is pure and each of the two executions get Sum 0 as initial state for Sum. If you repeat it with setRState and getRState, it will print 1 and 3.

Do NOT fork threads

do not use explicit concurrency. That destroy composition and modularity. Use asynchronous primitives and applicatives:

       ref <- newEmptyMVar
       forkIO $ do r<-job1; writeMVar ref r
       result2<- job2;                              use:     (,) <$> async job1 <*> job2
       result1 <- readMvar ref
       return (result1,result2)
  • Do not fork threads for parallelism. Use alternative:
main= do
  forkIO $ doThis
  forkIO $ doThat          use:        main= async doThis <|>  async doThat <|>  more...
  more...

Take care, since async creates a new thread, and every thread continues the execution until the end of the monad or empty:

do                                             do
  forkIO $ doThis >> doOther                     async doThis <|> async doThat 
  forkIO $ doThat >> doOther    equivalent:      doOther
                                             

If you don't want each fork to continue:

 func=do                                       
  forkIO $ doThis         use:      func= (async doThis >> empty) <|> (async doThat >> empty) <|> more
  forkIO $ doThat 
  more

Otherwise, without empty, func on the right would return three different results: the one of doThis, the one of doThat and the one of more

If you want to reduce parallelism, use thread pooling by adding the threads modifier, without changing the program code:

processing= do
  results <- poolLibrary(numberOfThreads,[dothis,dothat,doOther]) 
  mapM process results -- <- single threaded
    
    use: 

processing'= do    
  eachResult <- threads numberOfThreads $ async doThis <|> async doThat <|> async doOther 
  process eachResult   -- <- still multithreaded

The first returns a list of results while the second return different results in different threads to continue the parallelism. Use collect if you want to collect the results and generate the list of result in a single thread:

processResults <- collect 0 processing'

0 as parameter forces collect to wait until there are no more threads active in processing'

Do not communicate threads with mutable variables

That would need loops (loops annihilate composability) Use event vars (defined in Transient):

      mvaar = newEmptyMVar
      forkIO $ loop1 mvar
      forkIO $ loop2 mvar                evar <-  newEVar
      where                     use:     noloop1 evar <|> noloop2 evar
      loop1 var= do                      where
        r <- takeMVar var                noloop1 evar= do
        process r                            r <- readEvar evar
        ...                                  process r
        loop1                                ...
                                             

Use transient exceptions to fix things and continue tasks without mixing exception code and application code

do                                       do
   myTask `onException`$ \e -> do          onException $ \e -> when (tryToFix e) continue
      if tryTofix e then myTask     use:        -- or:  if tryToFix r then continue else return ()
          else throw e                     myTask                     
(do
   initThis 
   initThat) `onException` $ \(e :: MyException2) -> do handleThat; throwIO e 
             `onException` $ \(e :: MyException1) -> do handleThis; throwIO e

use:

do 
   initThis `onException'` $ \(e :: MyException1) -> handleThis e
   initThat `onException'` $ \(e :: MyException2) -> handleThat e

The above example uses onException from Control.Exception. The second uses onException' from Transient.Base. 'e' has the same type in both cases. They are standard Haskell exceptions, but onException' propagate back (bubble up like JavaScript events) by default trough the monad, and execute the handlers until continue, which resume execution forward or empty which stop executing further handlers; it is not necessary to re-throw them. The code preserves monadic composition. This makes exceptions more useful.

You can compose freely expressions that contain react async and other asynchronous primitives (which stop the computation and return something in another thread) using alternatives (<|>) and applicative (<*>) combinators.

Do NOT use single-threaded management of resources

That may leak when new threads are spawned. Use finalizations:

bracket openResource closeResource 
         $ \handler -> code that uses the resource     use:  do handler <- openClose openResource closeResource
                                                                code that uses the resource

"openClose" uses finalizations. In the second example the code that uses the resource can be multi-threaded and yet the resource will be closed well. See more on finalizations here

Do NOT use explicit communications

Do not use the OOP patterns like MVC or the Actor Model for communications. Use functions:

Client:
do                                  do
   send node message         use:     result <- runAt node $ local process
   result <- receive node           -- and run this program in both client and server

Server:
do
   message <- receive
   result <- process
   send result

runtAt is the distributed communication primitive that support multithreading and streaming (multiple returns)

Node to node communications uses tcp.

Browser: 
 ajaxRequest url params \result -> process  
                                            
                                            use:   result <- atRemote $ local $ process params
                                                   -- compile with ghc and ghcjs
                                                   -- and run it both in browser and server
Server:
 -- routes:
 onRequest 
   [(url1, process1)
   ,(url2,process2)
   ...
 

Browser-server communication uses WebSockets. atRemote is one remote invocation primitive for browser-server and in general for nodes which have a connection opened already. See tutorials about how to compile and set-up programs in the browser.

runAt and atRemote and other communication primitives are based on two basic deeper primitives: wormhole and teleport

Axiom is the transient library for creating DOM interfaces in the browser. widgets are coherent with the transient model:

do
   text <- local $ render $ inputString (Just "edit this text") 
                          `fire` OnChange 
                          ! atr "size" "80"

   response <- atServer $ accessDatabase text  -- invoke execution on the server. 
                                               -- response goes back to the browser
   local $ render $ rawHtml $ p $ show response
   
   where
   
   accessDatabase text= local $ do
#ifndef #ghcjs_HOST_OS
            databaseCode text     -- will be compiled only in the server node
#else
            empty                 -- no server-side code in the browser
#endif

The conditional compilation, as seen above, can be used to compile different local code in the browser and server. inputString for example, runs empty in the server. Its line renders a text box for 80 chars in the browser and stream responses to the server whenever the "OnChange" event is fired.

Clone this wiki locally