using threepenny-gui/reactive in client/server programming - haskell

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]]

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?

Entering relations to database using Persistent

Starting out with Haskell and Yesod, probably getting a bit too far with Yesod relative to Haskell :)
I build entities using Persistent via
share [mkPersist sqlSettings, mkMigrate "migrateAll"][persistLowerCase|
Game
title String
company String
UniqueTitle title
deriving Show
Tag
label String
description String Maybe
UniqueLabel label
deriving Show
GameTag
gameId GameId
tagId TagId
UniqueGameTag gameId tagId
|]
-- Yesod related code ...
In main I have
main :: IO ()
main = do
let taggings = fromFile :: [(Game, Tag)] -- fromFile code not included
runStderrLoggingT $ withSqlitePool ":inmemory:" 10 $ λpool → liftIO $ do
runResourceT $ flip runSqlPool pool $ do
runMigration migrateAll
let (g, t) = head taggings
gid ← insert g
tid ← insert t
insert (GameTag gid tid)
warp 3000 $ App pool
Doing this I get the first relation into the database, and by selecting elements from the list I can add more 'by hand', but I can't figure out how to get all the relations into the database by somehow iterating over taggings. How do i define a function that I can map over taggings ::[(Game, Tag)] and inserts the game tags of the type GameTag constructed
by Persistent?
The main trick here isn't in pulling out the function, that is easy:
f (g, t) = do
gid <- insert g
tid <- insert t
insert (GameTag gid tid)
The trick is knowing how to use this.... Standard map won't work alone, because the function is defined in a monad (you can use it, it will just give you a list of actions back without running them).
map f taggings -- returns just a list, type [ResourceT IO a], doesn't run anything
Here are two ways to actually run the actions from within main.
sequence (map f taggings) --sequentially runs the actions in the list
or, the more readable
forM taggings f
or, in the slightly more verbose
forM taggings $ \tagging -> do
f tagging
You also might want to look at mapM. Also also should learn about forM_ and sequence_ to supress the (often useless) return values.

How to look back to the previous moment

I am reading a button's state (whether being pressed or not) every moment:
readButton :: IO Boolean
readButton = ...
main = do
(add, fire) <- newAddHandler
network <- compile (desc add)
actuate network
forever $ do
buttonState <- readButton
fire buttonState
desc addButtonEvent = do
eButtonState <- fromAddHandler addButtonEvent
...
All the read states are stored into eButtonState in the network description desc.
The button is considered to be newly pressed when the current moment's state is 1 with the previous moment's being 0. So, if the event sequence was a list, the function would be written like this:
f :: [Bool] -> Bool
f (True:False:_) = True
f _ = False
I want to apply this function to eButtonState so I would know whether the button is newly pressed or not in the moment.
Is it ever possible? How would you do it? I would appreciate if there is a better or more common idea or method to achieve this goal.
Here is one way (this is a runnable demo):
import Reactive.Banana
import Reactive.Banana.Frameworks
import Control.Monad
import Control.Applicative -- Needed if you aren't on GHC 7.10.
desc addDriver = do
-- Refreshes the button state. Presumably fired by external IO.
eButtonDriver <- fromAddHandler addDriver
let -- Canonical repersentation of the button state.
bButtonState = stepper False eButtonDriver
-- Observes the button just before changing its state.
ePreviousState = bButtonState <# eButtonDriver
-- Performs the test your f function would do.
newlyPressed :: Bool -> Bool -> Bool
newlyPressed previous current = not previous && current
-- Applies the test. This works because eButtonDriver and
-- ePreviousState are fired simultaneously.
eNewlyPressed = unionWith newlyPressed
ePreviousState eButtonDriver
-- The same but more compactly, without needing ePreviousState.
{-
eNewlyPressed = newlyPressed <$> bButtonState <#> eButtonDriver
-}
reactimate (print <$> eNewlyPressed)
main = do
(addDriver, fireDriver) <- newAddHandler
network <- compile (desc addDriver)
actuate network
-- Demo: enter y to turn the button on, and any other string to
-- turn it off.
forever $ do
buttonState <- (== "y") <$> getLine
fireDriver buttonState
Notes:
Events are transient, behaviors are permanent is a good general rule to decide whether you need a behavior or an event stream. In this case, you need to look at what the button state was before the update in order to decide whether it was newly updated. The natural thing to do, then, is to represent the button state with a behavior (bButtonState), which is updated by an event fired externally (eButtonDriver).
For details about what the combinators are doing, see Reactive.Banana.Combinators.
For the fine print on the timing of events and behavior updates in reactive-banana, see this question.
Depending on what you are trying to do, the changes function might be useful. Be aware of the caveats related to it mentioned by the documentation.

Mixing Threepenny-Gui and StateT

I have a question on the interaction of Threepenny-Gui with StateT.
Consider this toy program that, every time the button is clicked, adds a "Hi" item in the list:
import Control.Monad
import Control.Monad.State
import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core hiding (get)
main :: IO ()
main = startGUI defaultConfig setup
setup :: Window -> UI ()
setup w = void $ do
return w # set title "Ciao"
buttonAndList <- mkButtonAndList
getBody w #+ map element buttonAndList
mkButtonAndList :: UI [Element]
mkButtonAndList = do
myButton <- UI.button # set text "Click me!"
myList <- UI.ul
on UI.click myButton $ \_ -> element myList #+ [UI.li # set text "Hi"]
return [myButton, myList]
Now, instead of "Hi", I'd like it to print the natural numbers. I know that I could use the fact that the UI monad is a wrapper around IO, and read/write the number I reached so far in a database, but, for educational purposes, I'd like to know if I can do it using StateT, or otherwise accessing the content of the list via Threepenny-gui interface.
StateT won't work in this case. The problem is that you need the state of your counter to persist between invocations of the button callback. Since the callback (and startGUI as well) produce UI actions, any StateT computation to be ran using them has to be self-contained, so that you can call runStateT and make use of the resulting UI action.
There are two main ways to keep persistent state with Threepenny. The first and most immediate is using an IORef (which is just a mutable variable which lives in IO) to hold the counter state. That results in code much like that written with conventional event-callback GUI libraries.
import Data.IORef
import Control.Monad.Trans (liftIO)
-- etc.
mkButtonAndList :: UI [Element]
mkButtonAndList = do
myButton <- UI.button # set text "Click me!"
myList <- UI.ul
counter <- liftIO $ newIORef (0 :: Int) -- Mutable cell initialization.
on UI.click myButton $ \_ -> do
count <- liftIO $ readIORef counter -- Reads the current value.
element myList #+ [UI.li # set text (show count)]
lift IO $ modifyIORef counter (+1) -- Increments the counter.
return [myButton, myList]
The second way is switching from the imperative callback interface to the declarative FRP interface provided by Reactive.Threepenny.
mkButtonAndList :: UI [Element]
mkButtonAndList = do
myButton <- UI.button # set text "Click me!"
myList <- UI.ul
let eClick = UI.click myButton -- Event fired by button clicks.
eIncrement = (+1) <$ eClick -- The (+1) function is carried as event data.
bCounter <- accumB 0 eIncrement -- Accumulates the increments into a counter.
-- A separate event will carry the current value of the counter.
let eCount = bCounter <# eClick
-- Registers a callback.
onEvent eCount $ \count ->
element myList #+ [UI.li # set text (show count)]
return [myButton, myList]
Typical usage of Reactive.Threepenny goes like this:
First, you get hold of an Event from user input through Graphics.UI.Threepenny.Events (or domEvent, if your chosen event is not covered by that module). Here, the "raw" input event is eClick.
Then, you massage event data using Control.Applicative and Reactive.Threepenny combinators. In our example, we forward eClick as eIncrement and eCount, setting different event data in each case.
Finally, you make use of the event data, by building either a Behavior (like bCounter) or a callback (by using onEvent) out of it. A behavior is somewhat like a mutable variable, except that changes to it are specified in a principled way by your network of events, and not by arbitrary updates strewn through your code base. An useful function for handling behaviors not shown here is sink function, which allows you to bind an attribute in the DOM to the value of a behavior.
An additional example, plus some more commentary on the two approaches, is provided in this question and Apfelmus' answer to it.
Minutiae: one thing you might be concerned about in the FRP version is whether eCount will get the value in bCounter before or after the update triggered by eIncrement. The answer is that the value will surely be the old one, as intended, because, as mentioned by the Reactive.Threepenny documentation, Behavior updates and callback firing have a notional delay that does not happen with other Event manipulation.

Resources