reactive-banana reactimate to retrieve the widget textCtrl Value like textCtrlGetValue - haskell

I would like to retrieve the widget value.
In the following, pressing the button b retrieve s_in and print it , in native wxhaskell.
b <- button f [text:= "print text in console",
on command := textCtrlGetValue s_in >>= putStrLn]
I like to do the same on reactive-banana , but in the following, I get "ff" and not the textCtrlGetValue of s_in2
s_in <- textCtrl f []
s_in2 <- textCtrl f []
b <- button f [text:= "print text in console",
on command := textCtrlGetValue s_in >>= putStrLn]
let networkDescription :: forall t. Frameworks t => Moment t ()
networkDescription = do
b_in <- behaviorText s_in "init"
b_in2 <- behaviorText s_in2 "ff"
e_butt <- event0 b command
-- I need an event, triggered by the button, and filled by the b_in2,
sink s_in2 [text :== id <$> b_in]
reactimate $ (\x -> putStrLn x) <$> b_in2 <# e_butt
the sink updates well sin_2 after s_in .
but the following reactimate line does not get me the textCtrlGetValue of s_in/ b_in I wish to get . how can I "get" it ?

The behavior obtained with the behaviorText function will only react to changes that the user made to the edit box. It does not include programmatic changes, like those performed with the sink function.
Distinguishing between user events and programmatic events is essential for writing responsive UI elements that have bidirectional data flow. See the CurrencyConverter example for a demonstration.
If you want to keep track of programmatic changes, I recommend to stay "within the FRP world", i.e. to use the behavior b_out = id <$> b_in instead of trying to read the text from the widget.
(By the way, id <$> x = x.)

Related

With Reflex.GI.Gtk, how to use and force evaluation of a dynamic from within an event

When using reflex-gi-gtk-0.2.0.0
I can access a dynamic from within an event:
submitButtonE4 <- eventOnSignal submitButton #clicked
(
do
let processDyn dynCompany = do
case dynCompany of
Just company -> do
path <- chartAnnualROA company fileOptions800x600 --generateChart company
Gtk.imageClear chartImage
Gtk.set chartImage [#file := T.pack defaultReportPath]
--return x -- path
case T.null $ T.pack path of
True -> return "" --dynCompany
Nothing -> return "" -- dynCompany
return $ ffor maybeCompanyDyn processDyn
>>= )
But in order to be evaluated, I need to bind it to a label:
sink submitClickStatusLabel [#label :== ffor submitButtonE4 (T.pack . show)]
which does not work as it is in Dynamic (SpiderTimeline x) (IO (Maybe Company)).
So instead I must go and get the info that the dynamic was bound to:
(
do
name <- Gtk.get companyCboxBoxEntryWidget #text
case Map.lookup name companyMap of
Just company -> do
path <- chartAnnualROA company fileOptions800x600 --generateChart company
Gtk.imageClear chartImage
Gtk.set chartImage [#file := T.pack defaultReportPath]
return path
Nothing -> return "../investingRIO/src/Data/Reports/initialChart.svg"
>>= )
and now I can sink it and cause evalution.
sink submitClickStatusLabel [#label :== ffor submitButtonE (T.pack . show)]
I am unable to find any way to force the evaluation when using the first method. How do I force the evalution without sinking to another widget?
Thanks
Here is the new version, based on Kritzefitz's answer.
An event for selecting a company from a combobox, which is same as before
companySelectionE <- eventOnAttribute companyCboxBoxEntryWidget #text
Replaced dynamic with a behavior.
companySelectionB <- hold Nothing $ ffor companySelectionE (`Map.lookup` companyMap)
generateChart (renamed from processDyn) returns a () instead of a FilePath, which was an attempt at forcing evaluation, now done by performEvent.
let
generateChart company = do
case company of
Just companyJ -> do
chartAnnualROA companyJ fileOptions800x600
Gtk.imageClear chartImage
Gtk.set chartImage [#file := T.pack defaultReportPath]
return ()
Nothing -> return ()
submitClickedE now uses eventOnSignal0 instead of eventOnSignal
submitClickedE <- eventOnSignal0 submitButton #clicked
Creating a chart from the selected company is now a behavior instead of a dynamic.
let generateChartB = generateChart <$> companySelectionB
Now I use <# to create a new event from the submit event and generate chart behavior.
let generateChartE = generateChartB <# submitClickedE
And the use of performEvent, which eliminated all the labels I was creating and sinking to in an attempt to get my IO to evaluate. It also eliminated the FilePath return from generateChart, aslo an attempt to force evaluation.
processedCompany <- performEvent $ runGtk <$> generateChartE
Thank cleared up a lot of things for me, thanks.
Here it is in a single quote for easier reading:
companySelectionE <- eventOnAttribute companyCbox #text
companySelectionB <- hold Nothing $ ffor companySelectionE (`Map.lookup` companyMap)
let
generateChart company = do
case company of
Just companyJ -> do
chartAnnualROA companyJ fileOptions800x600
Gtk.set chartImage [#file := T.pack defaultReportPath]
return ()
Nothing -> return ()
submitClickedE <- eventOnSignal0 submitButton #clicked
let generateChartB = generateChart <$> companySelectionB
let generateChartE = generateChartB <# submitClickedE
processedCompany <- performEvent $ runGtk <$> generateChartE
I think most of your trouble comes from the fact, that you want to do substantial amounts of work inside eventOnSignal . This place is not intended to do the actual heavy lifting of your business logic and it doesn't provide you with the proper context to effectively work with reactive values, such as Dynamics, as you are currently experiencing.
The actual use case for the eventOnSignal* family of functions is to obtain basic inputs for your reactive network. The input provided by a button doesn't carry any actual information. It just provides the information when the button has been clicked. For cases like this you usually don't want to use eventOnSignal directly, but rather eventOnSignal0, so let's do that:
submitClickedE <- eventOnSignal0 submitButton #clicked
The type returned by this is submitClickedE :: Event t (). As you can see, the Event has a () as its value, which is what we want, because merely clicking the button doesn't produce any value by itself. But you want to call an IO-producing function on the value inside processDyn, so let's first construct the IO action you want to execute:
let processDynD = processDyn <$> dynCompany
The assignment here has the type processDynD :: Dynamic t (IO (Maybe Company)). As you can see, the IO hasn't been executed yet. Luckily reflex provides an operation to execute IO actions inside reactive values, called performEvent :: Event t (Performable m a) -> m (Event t a). There are two things about this type, that don't quite fit what we need at the moment. First, it expects the monad to be performed to be a Performable m whereas we have IO, but we will get to that in a moment. The second and more pressing concern is that performEvent expects an Event, not a Dynamic. This makes sense, because you can't execute an IO action continuously. You have to decide when the IO action is executed.
AIUI you want the IO to be executed, when the submitButton is clicked. So we want an Event that fires whenever submitClickedE fires, but it should fire the current value inside processDynD. Doing something like this is called “sampling a Behavior with an Event” and can be done using the operator (<#). In your case you want to sample a Dynamic, but you can always turn a Dynamic into a Behavior using current. So to get the expected Event you can use this:
let processDynE = current processDynD <# submitClickedE
The assignment has the value processDynE :: Event t (IO (Maybe Company)). But as you can see, the IO still hasn't been executed. We can now do that using performEvent as discussed earlier:
processedCompany <- performEvent $ runGtk <$> processDynE
We use runGtk to lift the IO in processDynE to the required Performable m. The returned value has the type processedCompany :: Event t (Maybe Company). You can now sink this into your output label, as was your original intention:
sink submitClickStatusLabel [#label :== T.pack . show <$> processedCompany]
Note though, that unlike your original attempt, we now ended up with an Event instead of a Dynamic. If you actually need a Dynamic from all of this, you have to construct it from the Event using holdDyn initialValue processedCompany. But then you have to provide an initialValue because otherwise there is no value for the Dynamic before the submitButton has been clicked for the first time.

Update list of n UI values

I'm looking for a way to update an arbitrary number of UI.inputs based on a valueChange in any of the inputs.
Here is a toy example with just two inputs:
import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core
import Graphics.UI.Threepenny.JQuery
main :: IO ()
main = do
startGUI defaultConfig setup
return ()
setup :: Window -> UI ()
setup w = do
textboxes <- do
tb1 <- UI.input
tb2 <- UI.input
update1 <- stepper "red" $ UI.valueChange tb1
update2 <- stepper "green" $ UI.valueChange tb2
element tb1 # sink value (fmap reverse update2)
element tb2 # sink value (fmap reverse update1)
return $ column [return tb1, return tb2]
getBody w #+ [textboxes]
return ()
Whatever is written in one of the textboxes is copied (reversed) into the other text box.
Now, what if I wanted to have a list of an arbitrary length of input UIs, and any thing written into any of the inputs is copied into all of the other ones? I can create a list of UIs easily enough, but how do I read them all, apply a function to their input (like reverse) and then sink the change into all the other ones?
Any thoughts?
I'm not familiar with pretty much anything you mentioned, but would you be able to make use of the monadic structure and some standard functions to do something like this:
textboxes <- do
tbs <- replicateM 3 UI.input
forM_ tbs $ \tbX -> do
update <- stepper "_" $ UI.valueChange tbX
forM_ tbs $ \tbY -> do
element tbY # sink value (fmap reverse update)
return $ column (map return tbs)
The stepper argument is static and I think you would need a way to skip the triggering control when updating, but in terms of generalizing from two controls to a list of controls I think this might be the right direction?

Reactive Banana: consume parametrized call to an external API

Starting from a previous question here:
Reactive Banana: how to use values from a remote API and merge them in the event stream
I have a bit different problem now: How can I use the Behaviour output as input for an IO operation and finally display the IO operation's result?
Below is the code from the previous answer changed with a second output:
import System.Random
type RemoteValue = Int
-- generate a random value within [0, 10)
getRemoteApiValue :: IO RemoteValue
getRemoteApiValue = (`mod` 10) <$> randomIO
getAnotherRemoteApiValue :: AppState -> IO RemoteValue
getAnotherRemoteApiValue state = (`mod` 10) <$> randomIO + count state
data AppState = AppState { count :: Int } deriving Show
transformState :: RemoteValue -> AppState -> AppState
transformState v (AppState x) = AppState $ x + v
main :: IO ()
main = start $ do
f <- frame [text := "AppState"]
myButton <- button f [text := "Go"]
output <- staticText f []
output2 <- staticText f []
set f [layout := minsize (sz 300 200)
$ margin 10
$ column 5 [widget myButton, widget output, widget output2]]
let networkDescription :: forall t. Frameworks t => Moment t ()
networkDescription = do
ebt <- event0 myButton command
remoteValueB <- fromPoll getRemoteApiValue
myRemoteValue <- changes remoteValueB
let
events = transformState <$> remoteValueB <# ebt
coreOfTheApp :: Behavior t AppState
coreOfTheApp = accumB (AppState 0) events
sink output [text :== show <$> coreOfTheApp]
sink output2 [text :== show <$> reactimate ( getAnotherRemoteApiValue <#> coreOfTheApp)]
network <- compile networkDescription
actuate network
As you can see what I am trying to do it is using the new state of the application -> getAnotherRemoteApiValue -> show. But it doesn't work.
Is actually possible doing that?
UPDATE
Based on the Erik Allik and Heinrich Apfelmus below answers I have the current code situation - that works :) :
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import System.Random
import Graphics.UI.WX hiding (Event, newEvent)
import Reactive.Banana
import Reactive.Banana.WX
data AppState = AppState { count :: Int } deriving Show
initialState :: AppState
initialState = AppState 0
transformState :: RemoteValue -> AppState -> AppState
transformState v (AppState x) = AppState $ x + v
type RemoteValue = Int
main :: IO ()
main = start $ do
f <- frame [text := "AppState"]
myButton <- button f [text := "Go"]
output1 <- staticText f []
output2 <- staticText f []
set f [layout := minsize (sz 300 200)
$ margin 10
$ column 5 [widget myButton, widget output1, widget output2]]
let networkDescription :: forall t. Frameworks t => Moment t ()
networkDescription = do
ebt <- event0 myButton command
remoteValue1B <- fromPoll getRemoteApiValue
let remoteValue1E = remoteValue1B <# ebt
appStateE = accumE initialState $ transformState <$> remoteValue1E
appStateB = stepper initialState appStateE
mapIO' :: (a -> IO b) -> Event t a -> Moment t (Event t b)
mapIO' ioFunc e1 = do
(e2, handler) <- newEvent
reactimate $ (\a -> ioFunc a >>= handler) <$> e1
return e2
remoteValue2E <- mapIO' getAnotherRemoteApiValue appStateE
let remoteValue2B = stepper Nothing $ Just <$> remoteValue2E
sink output1 [text :== show <$> appStateB]
sink output2 [text :== show <$> remoteValue2B]
network <- compile networkDescription
actuate network
getRemoteApiValue :: IO RemoteValue
getRemoteApiValue = do
putStrLn "getRemoteApiValue"
(`mod` 10) <$> randomIO
getAnotherRemoteApiValue :: AppState -> IO RemoteValue
getAnotherRemoteApiValue state = do
putStrLn $ "getAnotherRemoteApiValue: state = " ++ show state
return $ count state
The fundamental problem is a conceptual one: FRP Events and Behaviors can only be combined in a pure way. In principle, it is not possible to have a function of type, say
mapIO' :: (a -> IO b) -> Event a -> Event b
because the order in which the corresponding IO actions are to be executed is undefined.
In practice, it may sometimes be useful to perform IO while combining Events and Behaviors. The execute combinator can do this, as #ErikAllik indicates. Depending on the nature of getAnotherRemoteApiValue, this may be the right thing to do, in particular if this is function is idempotent, or does a quick lookup from location in RAM.
However, if the computation is more involved, then it is probably better to use reactimate to perform the IO computation. Using newEvent to create an AddHandler, we can give an implementation of the mapIO' function:
mapIO' :: (a -> IO b) -> Event a -> MomentIO (Event b)
mapIO' f e1 = do
(e2, handler) <- newEvent
reactimate $ (\a -> f a >>= handler) <$> e1
return e2
The key difference to the pure combinator
fmap :: (a -> b) -> Event a -> Event b
is that the latter guarantees that the input and result events occur simultaneously, while the former gives absolutely no guarantee about when the result event occurs in relation to other events in the network.
Note that execute also guarantees that input and result are have simultaneous occurrences, but places informal restrictions on the IO allowed.
With this trick of combining reactimate with newEvent a similar combinator can be written for Behaviors in a similar fashion. Keep in mind that the toolbox from Reactive.Banana.Frameworks is only appropriate if you are dealing with IO actions whose precise order will necessarily be undefined.
(To keep this answer current, I have used the type signatures from the upcoming reactive-banana 1.0. In version 0.9, the type signature for mapIO' is
mapIO' :: Frameworks t => (a -> IO b) -> Event t a -> Moment t (Event t b)
)
TL;DR: scroll down to the ANSWER: section for a solution along with an explanation.
First of all
getAnotherRemoteApiValue state = (`mod` 10) <$> randomIO + count state
is invalid (i.e. does not typecheck) for reasons completely unrelated to FRP or reactive-banana: you cannot add an Int to an IO Int — just as you can't apply mod 10 to an IO Int directly, which is exactly why, in the answer to your original question, I used <$> (which is another name for fmap from Functor).
I strongly recommend you look up and understand the purpose/meaning of <$>, along with <*> and some other Functor and Applicative type class methods — FRP (at least the way it is designed in reactive-banana) builds heavily upon Functors and Applicatives (and sometimes Monads, Arrows and possibly some other more novel foundation), hence if you don't completely understand those, you won't ever become proficient with FRP.
Secondly, I'm not sure why you're using coreOfTheApp for sink output2 ... — the coreOfTheApp value is related to the other API value.
Thirdly, how should the other API value be displayed? Or, more specifically, when should it be displayed? Your first API value is displayed when the button is clicked but there's no button for the second one — do you want the same button to trigger the API call and display update? Do you want another button? Or do you want it to be polled every n unit of time and simply auto-updated in the UI?
Lastly, reactimate is meant for converting a Behavior into an IO action, which is not what you want, because you already have the show helper and don't need to setText or smth on the static label. In other words, what you need for the second API value is the same as before, except you need to pass something from the app state along with the request to the external API, but aside from that difference, you can still just keep showing the (other) API value using show as normal.
ANSWER:
As to how to convert getAnotherRemoteApiValue :: AppState -> IO RemoteValue into an Event t Int similar to the original remoteValueE:
I first tried to go via IORefs and using changes+reactimate', but that quickly turned out to a dead end (besides being ugly and overly complicated): output2 was always updated one FRP "cycle" too late, so it was always one "version" behind in the UI.
I then, with the help of Oliver Charles (ocharles) on #haskell-game on FreeNode, turned to execute:
execute :: Event t (FrameworksMoment a) -> Moment t (Event t a)
which I still don't fully grasp yet, but it works:
let x = fmap (\s -> FrameworksMoment $ liftIO $ getAnotherRemoteApiValue s)
(appStateB <# ebt)
remoteValue2E <- execute x
so the same button would trigger both actions. But the problem with that quickly turned out to be the same as with the IORef based solution — since the same button would trigger a pair of events, and one event inside that pair depended on the other, the contents of output2 was still one version behind.
I then realised the events relatede to output2 need to be triggered after any events related to output1. However, it's impossible to go from Behavior t a -> Event t a; in other words, once you have a behavior, you can't (easily?) obtain an event from that (except with changes, but changes is tied to reactimate/reactimate', which is not useful here).
I finally noticed that I was essentially "throwing away" an intermediate Event at this line:
appStateB = accumB initialState $ transformState <$> remoteValue1E
by replacing it with
appStateE = accumE initialState $ transformState <$> remoteValue1E
appStateB = stepper initialState -- there seems to be no way to eliminate the initialState duplication but that's fine
so I still had the exact same appStateB, which is used as previously, but I could then also rely on appStateE to reliably trigger further events that rely on the AppState:
let x = fmap (\s -> FrameworksMoment $ liftIO $ getAnotherRemoteApiValue s)
appStateE
remoteValue2E <- execute x
The final sink output2 line looks like:
sink output2 [text :== show <$> remoteValue2B]
All of the code can be seen at http://lpaste.net/142202, with debug output still enabled.
Note that the (\s -> FrameworkMoment $ liftIO $ getAnotherRemoteApiValue s) lambda cannot be converted to point-free style for reasons related to RankN types. I was told this problem will go away in reactive-banana 1.0 because there will be no FrameworkMoment helper type.

Why should we use Behavior in FRP

I am learning reactive-banana. In order to understand the library I have decide to implement a dummy application that would increase a counter whenever someone pushes a button.
The UI library I am using is Gtk but that is not relevant for the explanation.
Here is the very simple implementation that I have come up with:
import Graphics.UI.Gtk
import Reactive.Banana
import Reactive.Banana.Frameworks
makeNetworkDescription addEvent = do
eClick <- fromAddHandler addEvent
reactimate $ (putStrLn . show) <$> (accumE 0 ((+1) <$ eClick))
main :: IO ()
main = do
(addHandler, fireEvent) <- newAddHandler
initGUI
network <- compile $ makeNetworkDescription addHandler
actuate network
window <- windowNew
button <- buttonNew
set window [ containerBorderWidth := 10, containerChild := button ]
set button [ buttonLabel := "Add One" ]
onClicked button $ fireEvent ()
onDestroy window mainQuit
widgetShowAll window
mainGUI
This just dumps the result in the shell. I came up to this solution reading the article by Heinrich Apfelmus. Notice that in my example I have not used a single Behavior.
In the article there is an example of a network:
makeNetworkDescription addKeyEvent = do
eKey <- fromAddHandler addKeyEvent
let
eOctaveChange = filterMapJust getOctaveChange eKey
bOctave = accumB 3 (changeOctave <$> eOctaveChange)
ePitch = filterMapJust (`lookup` charPitches) eKey
bPitch = stepper PC ePitch
bNote = Note <$> bOctave <*> bPitch
eNoteChanged <- changes bNote
reactimate' $ fmap (\n -> putStrLn ("Now playing " ++ show n))
<$> eNoteChanged
The example show a stepper that transforms an Event into a Behavior and brings back an Event using changes. In the above example we could have used only Event and I guess that it would have made no difference (unless I am not understanding something).
So could someone can shed some light on when to use Behavior and why? Should we convert all Events as soon as possible?
In my little experiment I don't see where Behavior can be used.
Thanks
Anytime the FRP network "does something" in Reactive Banana it's because it's reacting to some input event. And the only way it does anything observable outside the system is by wiring up an external system to react to events it generates (using reactimate).
So if all you're doing is immediately reacting to an input event by producing an output event, then no, you won't find much reason to use Behaviour.
Behaviour is very useful for producing program behaviour that depends on multiple event streams, where you have to remember that events happen at different times.
An Event has occurrences; specific instants of time where it has a value. A Behaviour has a value at all points in time, with no instants of time that are special (except with changes, which is convenient but kind of model-breaking).
A simple example familiar from many GUIs would be if I want to react to mouse clicks and have shift-click do something different from a click when the shift key is not held. With a Behaviour holding a value indicating whether the shift key is held down, this is trivial. If I just had Events for shift key press/release and for mouse clicks it's much harder.
In addition to being harder, it's much more low level. Why should I have to do complicated fiddling just to implement a simple concept like shift-click? The choice between Behaviour and Event is a helpful abstraction for implementing your program's concepts in terms that map more closely to the way you think about them outside the programming world.
An example here would be a movable object in a game world. I could have an Event Position representing all the times it moves. Or I could just have a Behaviour Position representing where it is at all times. Usually I'll be thinking of the object as having a position at all times, so Behaviour is a better conceptual fit.
Another place Behaviours are useful is for representing external observations your program can make, where you can only check the "current" value (because the external system won't notify you when changes occur).
For an example, let's say your program has to keep tabs on a temperature sensor and avoid starting a job when the temperature is too high. With an Event Temperature I'll have decide up front how often to poll the temperature sensor (or in response to what). And then have all the same issues as in my other examples about having to manually do something to make the last temperature reading available to the event that decides whether or not to start a job. Or I could use fromPoll to make a Behaviour Temperature. Now I've got a value that represents the time-varying value of the temperature, and I've completely abstracted away from polling the sensor; Reactive Banana itself takes care of polling the sensor as often as it might be needed without me needing to impending any logic for that at all!
Behaviors have a value all the time, whereas Events only have a value at an instant.
Think of it like you would in a spreadsheet - most of the data exists as stable values (Behaviors) that hang around and get updated whenever necessary. (In FRP though, the dependency can go either way without circular reference problems - the data is updated flowing from the changed value to unchanged ones.) You can additionally add code that fires when you press a button or do something else, but most of the data is available all the time.
Certainly you could do all that with just events - when this changes, read this value and that value and output this value, but it's just cleaner to express those relationships declaratively and let the spreadsheet or compiler worry about when to update stuff for you.
stepper is for changing things that happen into values in cells, and change is for watching cells and triggering actions. Your example where the output is text on a command line isn't particularly affected by the lack of persistent data, because the output comes in bursts anyway.
If however you have a graphical user interface, the event-only model, whilst certainly possible, and indeed common, is a little cumbersome compared to the FRP model. In FRP you just specify the relationships between things without being explicit about updates.
It's not necessary to have Behaviors, and analogously you could program an Excel spreadsheet entirely in VBA with no formulae. It's just nicer with the data permanence and equational specification. Once you're used to the new paradigm, you'll not want to go back to manually chasing dependencies and updating stuff.
When you have only 1 Event, or multiple Events that happen simultaneously, or multiple Events of the same type, it's easy to just union or otherwise combine them into a resulting Event, then pass to reactimate and immediately output it. But what if you have 2 Events of 2 different types happening at different times? Then combining them into a resulting Event that you can pass to reactimate becomes an unnecessary complication.
I recommend you to actually try and implement the synthesizer from FRP explanation using reactive-banana with only Events and no Behaviors, you'll quickly see that Behaviors simplify the unnecessary Event manipulations.
Say we have 2 Events, outputting Octave (type synonym for Int) and Pitch (type synonym to Char). User presses keys from a to g to set current pitch, or presses + or - to increment or decrement current octave. The program should output current pitch and current octave, like a0, b2, or f7. Let's say the user pressed these keys in various combinations during different times, so we ended up with 2 event streams (Events) like that:
+ - + -- octave stream (time goes from left to right)
b c -- pitch stream
Every time user presses a key, we output current octave and pitch. But what should be the result event? Suppose default pitch is a and default octave is 0. We should end up with an event stream that looks like this:
a1 b1 b0 c0 c1 -- a1 corresponds to + event, b1 to b, b0 to -, etc
Simple character input/output
Let's try to implement the synthesizer from scratch and see if we can do it without Behaviors. Let's first write a program, where you put a character, press Enter, the program outputs it, and asks for a character again:
import System.IO
import Control.Monad (forever)
main :: IO ()
main = do
-- Terminal config to make output cleaner
hSetEcho stdin False
hSetBuffering stdin NoBuffering
-- Event loop
forever (getChar >>= putChar)
Simple event-network
Let's do the above but with an event-network, to illustrate them.
import Control.Monad (forever)
import System.IO (BufferMode(..), hSetEcho, hSetBuffering, stdin)
import Control.Event.Handler (newAddHandler)
import Reactive.Banana
import Reactive.Banana.Frameworks
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription myAddHandler = do
event <- fromAddHandler myAddHandler
reactimate $ putChar <$> event
main :: IO ()
main = do
-- Terminal config to make output cleaner
hSetEcho stdin False
hSetBuffering stdin NoBuffering
-- Event loop
(myAddHandler, myHandler) <- newAddHandler
network <- compile (makeNetworkDescription myAddHandler)
actuate network
forever (getChar >>= myHandler)
A network is where all your events and behaviors live and interact with each other. They can only do that inside Moment monadic context. In tutorial Functional Reactive Programming kick-starter guide the analogy for event-network is a human brain. A human brain is where all event streams and behaviors interleave with each other, but the only way to access the brain is through receptors, which act as event source (input).
Now, before we proceed, carefully check out the types of the most important functions of the above snippet:
type Handler a = a -> IO ()
newtype AddHandler a = AddHandler { register :: Handler a -> IO (IO ()) }
newAddHandler :: IO (AddHandler a, Handler a)
fromAddHandler :: Frameworks t => AddHandler a -> Moment t (Event t a)
reactimate :: Frameworks t => Event t (IO ()) -> Moment t ()
compile :: (forall t. Frameworks t => Moment t ()) -> IO EventNetwork
actuate :: EventNetwork -> IO ()
Because we use the simplest UI possible — character input/output, we are going to use module Control.Event.Handler, provided by Reactive-banana. Usually the GUI library does this dirty job for us.
A function of type Handler is just an IO action, similar to other IO actions such as getChar or putStrLn (e.g. the latter has type String -> IO ()). A function of type Handler takes a value and performs some IO computation with it. Thus it can only be used inside an IO context (e.g. in main).
From types it's obvious (if you understand basics of monads) that fromAddHandler and reactimate can only be used in Moment context (e.g. makeDescriptionNetwork), while newAddHandler, compile and actuate can only be used in IO context (e.g. main).
You create a pair of values of types AddHandler and Handler using newAddHandler in main, you pass this new AddHandler function to your event-network function, where you can create an event stream out of it using fromAddHandler. You manipulate this event stream as much as you want, then wrap its events in an IO action, and pass the resulting event stream to reactimate.
Filtering events
Now let's only output something, if user presses + or -. Let's output 1 when user presses +, -1 when user presses -. (The rest of the code stays the same).
action :: Char -> Int
action '+' = 1
action '-' = (-1)
action _ = 0
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription myAddHandler = do
event <- fromAddHandler myAddHandler
let event' = action <$> filterE (\e -> e=='+' || e=='-') event
reactimate $ putStrLn . show <$> event'
As we don't output if user presses anything beside + or -, the cleaner approach would be:
action :: Char -> Maybe Int
action '+' = Just 1
action '-' = Just (-1)
action _ = Nothing
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription myAddHandler = do
event <- fromAddHandler myAddHandler
let event' = filterJust . fmap action $ event
reactimate $ putStrLn . show <$> event'
Important functions for Event manipulations (see Reactive.Banana.Combinators for more):
fmap :: Functor f => (a -> b) -> f a -> f b
union :: Event t a -> Event t a -> Event t a
filterE :: (a -> Bool) -> Event t a -> Event t a
accumE :: a -> Event t (a -> a) -> Event t a
filterJust :: Event t (Maybe a) -> Event t a
Accumulating increments and decrements
But we don't want just to output 1 and -1, we want to increment and decrement the value and remember it between key presses! So we need to accumE. accumE accepts a value and a stream of functions of type (a -> a). Every time a new function appears from this stream, it is applied to the value, and the result is remembered. Next time a new function appears, it is applied to the new value, and so on. This allows us to remember, which number we currently have to decrement or increment.
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription myAddHandler = do
event <- fromAddHandler myAddHandler
let event' = filterJust . fmap action $ event
functionStream = (+) <$> event' -- is of type Event t (Int -> Int)
reactimate $ putStrLn . show <$> accumE 0 functionStream
functionStream is basically a stream of functions (+1), (-1), (+1), depending on which key the user pressed.
Uniting two event streams
Now we are ready to implement both octaves and pitch from the original article.
type Octave = Int
type Pitch = Char
actionChangeOctave :: Char -> Maybe Int
actionChangeOctave '+' = Just 1
actionChangeOctave '-' = Just (-1)
actionChangeOctave _ = Nothing
actionPitch :: Char -> Maybe Char
actionPitch c
| c >= 'a' && c <= 'g' = Just c
| otherwise = Nothing
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription addKeyEvent = do
event <- fromAddHandler addKeyEvent
let eChangeOctave = filterJust . fmap actionChangeOctave $ event
eOctave = accumE 0 ((+) <$> eChangeOctave)
ePitch = filterJust . fmap actionPitch $ event
eResult = (show <$> ePitch) `union` (show <$> eOctave)
reactimate $ putStrLn <$> eResult
Our program will output either current pitch or current octave, depending on what the user pressed. It will also preserve the value of the current octave. But wait! That's not what we want! What if we want to output both current pitch and current octave, every time user presses either a letter or + or -?
And here it becomes super-hard. We can't union 2 event-streams of different types, so we can convert both of them to Event t (Pitch, Octave). But if a pitch event and an octave event happen at different time (i.e. they are not simultaneous, which is practically certain in our example), then our temporary event-stream would rather have type Event t (Maybe Pitch, Maybe Octave), with Nothing everywhere you haven't a corresponding event. So if a user presses in sequence + b - c +, and we assume that default octave is 0 and default pitch is a, then we end up with a sequence of pairs [(Nothing, Just 1), (Just 'b', Nothing), (Nothing, Just 0), (Just 'c', Nothing), (Nothing, Just 1)], wrapped in Event.
Then we must figure out how to replace Nothing with what would be the current pitch or octave, so the resulting sequence should be something like [('a', 1), ('b', 1), ('b', 0), ('c', 0), ('c', 1)].
This is too low-level and a true programmer shouldn't worry about aligning events like that, when there is a high-level abstraction available.
Behavior simplifies event manipulation
A few simple modifications, and we achieved the same result.
makeNetworkDescription :: Frameworks t => AddHandler Char -> Moment t ()
makeNetworkDescription addKeyEvent = do
event <- fromAddHandler addKeyEvent
let eChangeOctave = filterJust . fmap actionChangeOctave $ event
bOctave = accumB 0 ((+) <$> eChangeOctave)
ePitch = filterJust . fmap actionPitch $ event
bPitch = stepper 'a' ePitch
bResult = (++) <$> (show <$> bPitch) <*> (show <$> bOctave)
eResult <- changes bResult
reactimate' $ (fmap putStrLn) <$> eResult
Turn pitch Event into Behavior with stepper and replace accumE with accumB to get octave Behavior instead of octave Event. To get the resulting Behavior, use applicative style.
Then, to get the event you must pass to reactimate, pass the resulting Behavior to changes. However, changes returns a complicated monadic value Moment t (Event t (Future a)), therefore you should use reactimate' instead of reactimate. This is also the reason, why you have to lift putStrLn in the above example twice into eResult, because you're lifting it to Future functor inside Event functor.
Check out the types of the functions we used here to understand what goes where:
stepper :: a -> Event t a -> Behavior t a
accumB :: a -> Event t (a -> a) -> Behavior t a
changes :: Frameworks t => Behavior t a -> Moment t (Event t (Future a))
reactimate' :: Frameworks t => Event t (Future (IO ())) -> Moment t ()

using threepenny-gui/reactive in client/server programming

I am trying to figure out how to use Haskell threepenny-gui with its reactive functionality to write a program that lets
the user select an item from a listBox
send the selection to an external server
get back a list of results from the server
populate the listBox with the results
repeat
It seems I will need to use Handler, newEvent and register to do the above. If someone could point me to some existing code that does something like the above that would be great.
The closest I have found is GameThing.hs in the threepenny-gui samples directory (but it doesn't use register).
UPDATE:
I am asking whether I should be using Handler, newEvent and register --- and, if so, some clarification or example of those functions.
Also, to be clear, the big picture is:
browser --> threepenny-gui (on localhost) --> backend server (anywhere on network)
<-- <--
In other words, I need to do some IO (based on user selection) then display the results of that IO.
UPDATE: here is my solution (based on #Taldykin's response): https://github.com/haroldcarr/rdf-triple-browser/tree/master/haskell/src
Here is a piece of code. I will add description a bit later.
{-# LANGUAGE LambdaCase #-}
import Graphics.UI.Threepenny as UI
main :: IO ()
main = do
(evFillList, doFillList) <- newEvent
initialList <- valuesSupply ""
behFillList <- stepper initialList evFillList
startGUI defaultConfig $ \win -> do
list <- ul
sel <- listBox
behFillList
(pure Nothing)
(pure $ \it -> UI.span # set text it)
getBody win #+ [grid [[element list, element sel]]]
setFocus $ getElement sel
on selectionChange (getElement sel) $ \case
Nothing -> return ()
Just ix -> do
items <- currentValue behFillList
let it = items !! ix
liftIO $ valuesSupply it >>= doFillList
element list #+ [li # set html it]
setFocus $ getElement sel
valuesSupply :: String -> IO [String]
valuesSupply x = return [x ++ show i | i <- [0..9]]

Resources