wxhaskell: Updating a statusField using "on click" of a panel - wxhaskell

I would like some advice on how to update a "statusField" after
clicking on a "panel".
The following program demonstrates the problem. The program draws two
frames. You can imagine the left frame to be some kind of drawing area
and the right frame contains the buttons "Red" and "Green".
After clicking on the button labeled "Red" the text of the statusField is
updated to "Current color: Red". The button labeled "Green" updates the text to "Current color: Green".
How to change the text of the statusField after the user clicked on
the left panel? E.g. change it to "You successfully clicked on the
drawing panel."
Why can't I do it in "on click" the same way as in "on command" for
the buttons? (See annotation in the source below.)
Thank you very much.
module Main where
import Graphics.UI.WX
-- | NOP (= No Operation)
data Command = Nop
| Red
| Green
deriving (Eq)
main :: IO ()
main
= start hello
hello :: IO ()
hello
= do currentCommand <- varCreate $ Nop -- current command performed on next click on "pDrawingarea"
status <- statusField [text := "Welcome."]
-- Frames and Panels
f <- frame [ text := "Demo"
, bgcolor := lightgrey ]
pButtons <- panel f [ bgcolor := lightgrey]
pDrawingarea <- panel f [ on paint := draw
, bgcolor := lightgrey
]
set pDrawingarea [on click := do drawingAreaOnClick status currentCommand pDrawingarea
-- set status [text := "User clicked on the panel."]
-- Problem: uncommenting the line above shows the problem
]
bRed <- button pButtons [text := "Red", on command := do varSet currentCommand Red
set status [text := "Current color: Red"]
]
bGreen <- button pButtons [text := "Green", on command := do varSet currentCommand Green
set status [text := "Current color: Green"]
]
set pButtons [ layout := column 1 [ hstretch.expand $ widget bRed
, hstretch.expand $ widget bGreen
]
]
set f [ statusBar := [status]
, layout := row 3 [
minsize (sz 600 500) $ stretch.expand $ widget pDrawingarea
, vstretch.expand $ rule 3 500
, minsize (sz 200 500) $ vstretch.expand $ widget pButtons
]
]
return ()
draw :: DC a -> Rect -> IO ()
draw dc viewArea
= do putStrLn "Imagine some code to repaint the screen."
drawingAreaOnClick :: statusField -> Var Command -> Panel () -> Point -> IO ()
drawingAreaOnClick sf command panel pt
= do c <- varGet command
case c of
Red -> do putStrLn "Imagine some code to do red painting"
Green -> do putStrLn "Imagine some code to do green painting"

After spending lots of time on this problem I found a solution.
The solution is to change the definition of
drawingAreaOnClick :: statusField -> Var Command -> Panel () -> Point -> IO ()
to
drawingAreaOnClick :: Textual x => x -> Var Command -> Panel () -> Point -> IO ()
Because "statusField" itself is a member of the class "Textual" I don't understand the problem.
For the sake of completeness I will mention that I also switched GHC verions.The original problem occurred with GHC 7.8.4 and the solution I found works with GHC 7.10.3. I can't say if the GHC version affects the problem.
For reference the complete working code:
module Main where
import Graphics.UI.WX
-- | NOP (= No Operation)
data Command = Nop
| Red
| Green
deriving (Eq)
main :: IO ()
main
= start hello
hello :: IO ()
hello
= do currentCommand <- varCreate Nop -- current command performed on next click on "pDrawingarea"
status <- statusField [text := "Welcome."]
-- not needed: currentStatus <- varCreate status
-- Frames and Panels
f <- frame [ text := "Demo"
, bgcolor := lightgrey ]
pButtons <- panel f [ bgcolor := lightgrey]
pDrawingarea <- panel f [ on paint := draw
, bgcolor := lightgrey
]
set pDrawingarea [on click := do drawingAreaOnClick status currentCommand pDrawingarea
-- set status [text := "User clicked on the panel."]
-- Problem: uncommenting the line above shows the problem
]
bRed <- button pButtons [text := "Red", on command := do varSet currentCommand Red
set status [text := "Current color: Red"]
]
bGreen <- button pButtons [text := "Green", on command := do varSet currentCommand Green
set status [text := "Current color: Green"]
--sf <- varGet currentStatus
-- set sf [text := "yyy"]
]
set pButtons [ layout := column 1 [ hstretch.expand $ widget bRed
, hstretch.expand $ widget bGreen
]
]
set f [ statusBar := [status]
, layout := row 3 [
minsize (sz 600 500) $ stretch.expand $ widget pDrawingarea
, vstretch.expand $ rule 3 500
, minsize (sz 200 500) $ vstretch.expand $ widget pButtons
]
]
return ()
draw :: DC a -> Rect -> IO ()
draw dc viewArea
= do putStrLn "Imagine some code to repaint the screen."
drawingAreaOnClick :: Textual x => x -> Var Command -> Panel () -> Point -> IO ()
drawingAreaOnClick sf command panel pt
= do c <- varGet command
set sf [text := "Drawing on the screen."]
case c of
Red -> do putStrLn "Imagine some code to do red painting"
Green -> do putStrLn "Imagine some code to do green painting"

Related

Pandoc `writeMarkdown` does not include metadata, i.e. write (read a) is not a - what extension is required?

I want to creat an utilty to transform some text in a markdown file and want to procude a new markdown file. The metadata is not changed.
The operations read and write should be inverse (or at least idempotent), but I cannot find a way to have pandoc reproduce the input file including the metadata. What combination of Extensions and Options are required?
Here my minimal working example with the newest pandoc from lst-15.13.
-- ---------------------------------------------------------------------------
--
-- Module : a test for pandoc output of yaml
-- ---------------------------------------------------------------------------
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.Text as T
import Text.Pandoc
import Control.Monad.IO.Class (liftIO )
main :: IO ()
main = do
putStrLns $ ["input", showT inputMd]
res <- sub inputMd
case res of
Left st -> putStrLns $ ["error", show st]
Right q ->
do
putStrLns $ ["result q\n", showT $ q]
putStrLns $ ["should be the same as input p\n", showT inputMd]
putStrLns $ ["same", show (inputMd == ( q))]
return ()
return ()
showT = show . T.unpack
putStrLns = putStrLn . unwords
sub :: T.Text -> IO (Either PandocError T.Text)
sub input1 = do
res <- runIO $
do
let readOptions = def{readerStandalone = True
, readerExtensions = extensionsFromList
[Ext_yaml_metadata_block ]
}
p <- readMarkdown readOptions ( input1)
-- def does not analyse metadata
-- readOptions analysis metadata
-- output is then only the markdown
-- t1 :: String <- liftIO $readFile "/home/frank/Workspace8/pandocTest/temp.tpl"
-- t2 <- compileDefaultTemplate (T.pack t1)
let writeOptions = def {writerSetextHeaders = False
, writerExtensions = extensionsFromList
[Ext_yaml_metadata_block]
-- , writerTemplate = Just t2
}
q <- writeMarkdown writeOptions p
-- def gives only the markdown part
-- but not including the titel
liftIO $ putStrLns ["AST \n", show p]
return q
res2 <- handleError res
return res
inputMd = T.unlines ["---"
,"title: The Future of AA"
,"..."
,""
,"## second level"
,"text for nothing"
] :: T.Text
The use of a template comiles but gives a runtime error:
Could not find data file /home/frank/.stack/snapshots/x86_64-linux/668b320207ef95ba5255b2b20895a7f7315ff61076bb3ab82e76f7ef56076320/8.8.3/share/x86_64-linux-ghc-8.8.3/pandoc-2.9.1.1/data/templates/default.
$if(titleblock)$ $titleblock$

R Shiny/Shinydashboard: Hiding the last part of a string in a table

I have a data table that contains some very wide columns and I want to add a scrolling-bar to make it more presentable. So far I have found examples using a scrolling-bar for the entire table - but ideally I would like to have a scrolling-bar for EACH column in the table if that is possible. Below there is an illustrating example. In this code I want a scrolling-bar for both "This_is_a_very_long_name_1", "This_is_a_very_long_name_2" etc.
library("shinydashboard")
library("shiny")
body <- dashboardBody(
fluidPage(
column(width = 4,
box(
title = "Box title", width = NULL, status = "primary",
div(style = 'overflow-x: scroll', tableOutput('table'))
)
)
)
)
ui <- dashboardPage(
dashboardHeader(title = "Column layout"),
dashboardSidebar(),
body
)
server <- function(input, output) {
test.table <- data.frame(lapply(1:8, function(x) {1:10}))
names(test.table) <- paste0('This_is_a_very_long_name_', 1:8)
output$table <- renderTable({
test.table
})
}
# Preview the UI in the console
shinyApp(ui = ui, server = server)
I thought about splitting the table into 8 tables, making a scrolling table for each of them and then putting them next to each other, but space was added betweeen them and it did not look that nice. I think it would be preferable to keeping it as one table (but suggestions are very welcome!).
Does anyone whether this is possible - and how to solve it?
Thanks in advance!
I would not recommend scrolling column header, i think it would not be very clear to read it or so. Here is the code which You can use to get the header in 2 lines so the columns are not too wide:
library("shinydashboard")
library("shiny")
library(DT)
test.table <- data.frame(lapply(1:8, function(x) {1:10}))
names(test.table) <- paste0('This_is_a_very_long_name_', 1:8)
body <- dashboardBody(
fluidPage(
column(width = 8,
box(
title = "Box title", width = NULL, status = "primary",
div(style = 'overflow-x: scroll', dataTableOutput('table'))
)
)
)
)
ui <- dashboardPage(
dashboardHeader(title = "Column layout"),
dashboardSidebar(),
body
)
server <- function(input, output) {
output$table <- renderDataTable({
names(test.table) <- gsub("_"," ",names(test.table))
datatable(test.table, options = list(columnDefs = list(list(width = '100px', targets = c(1:8)))))
})
}
# Preview the UI in the console
shinyApp(ui = ui, server = server)
[UPDATE] --> Column text rendering
Here is a one solution which can be usefull for You. There is no scrolling, however Your row text displays only first three characters (the number of characters displayed can be changed) and ..., with mouse over the row You get the pop up with whole variable name in this row:
library("shinydashboard")
library("shiny")
library(DT)
x <- c("aaaaaaaaaaaaaa", "bbbbbbbbbbbb", "ccccccccccc")
y <- c("aaaaaaaaaaaaaa", "bbbbbbbbbbbb", "ccccccccccc")
z <- c(1:3)
data <- data.frame(x,y,z)
body <- dashboardBody(
fluidPage(
column(width = 4,
box(
title = "Box title", width = NULL, status = "primary",
div(style = 'overflow-x: scroll', dataTableOutput('table'))
)
)
)
)
ui <- dashboardPage(
dashboardHeader(title = "Column layout"),
dashboardSidebar(),
body
)
server <- function(input, output) {
output$table <- renderDataTable({
datatable(data, options = list(columnDefs = list(list(
targets = c(1:3),
render = JS(
"function(data, type, row, meta) {",
"return type === 'display' && data.length > 3 ?",
"'<span title=\"' + data + '\">' + data.substr(0, 3) + '...</span>' : data;",
"}")),list(width = '100px', targets = c(1:3)))))
})
}
# Preview the UI in the console
shinyApp(ui = ui, server = server)

How to close a window with Spec in Pharo

I have a Spec window with several controls. When I click on the Ok button I want the window to be closed.
| m |
m := DynamicComposableModel new.
m instantiateModels: #(text TextModel ok OkToolbar).
m ok okAction: [ self close ].
m openWithSpecLayout: (SpecLayout composed
newColumn: [ : c | c add: #text ; add: #ok height: 30 ];
yourself).
I have tried sending delete and close, but none worked. How can I close the window?
you can do this:
| m |
m := DynamicComposableModel new.
m instantiateModels: #(text TextModel ok OkToolbar).
m ok okAction: [ m window close ].
m openWithSpecLayout: (SpecLayout composed
newColumn: [ : c | c add: #text ; add: #ok height: 30 ];
yourself).

R: Change icon of Tcltk window in Mac and Linux

I have created a progress bar to keep tabs on the execution of some R scripts. And I want to insert a custom icon in the bar instead of the default 'Tk' one. I am able to do this on Windows using a .ico file and the following command
tcl('wm', 'iconbitmap', .win, 'Icon.ico')
But I am a loss about how to do the same in Mac OSX and Linux. Obviously, the .ico format doesn't work but neither does .png, .jpg, .bmp, .xbm or .xpm. Any suggestion on how I could proceed? Sample image and progress bar code attached below:-
Sample image http://tinypic.com/r/jt8efn/6 - http://tinypic.com/r/jt8efn/6
tkProgressBar2 <- function (title = 'Test progress bar', label = '', min = 0, max = 100, initial = 0, width = 300, userfn='helvetica', backg='white') {
useText <- FALSE
have_ttk <- as.character(tcl('info', 'tclversion')) >= '8.5'
if (!have_ttk && as.character(tclRequire('PBar')) == 'FALSE') useText <- TRUE
.win <<- tktoplevel(background=backg)
tkfocus()
tcl('wm', 'geometry', .win, '500x100+450+350')
tcl('wm', 'iconbitmap', .win, '#Icon.xbm')
.val <- initial
.killed <- FALSE
tkwm.geometry(.win, sprintf('%dx80', width + 40))
tkwm.title(.win, title)
fn <- tkfont.create(family = userfn, size = 12)
if (useText) {
.lab <- tklabel(.win, text = label, font = fn, padx = 0, background=backg)
tkpack(.lab, side = 'left')
fn2 <- tkfont.create(family = userfn, size = 16)
.vlab <- tklabel(.win, text = '0%', font = fn2, padx = 20, background=backg)
tkpack(.vlab, side = 'right')
up <- function(value) {
if (!is.finite(value) || value < min || value > max) return()
.val <<- value
tkconfigure(.vlab, text = sprintf('%d%%', round(100 * (value - min)/(max - min))))
}
} else {
.lab <- tklabel(.win, text = label, font = fn, pady = 0, background=backg)
.tkval <- tclVar(0)
tkpack(.lab, side = 'top')
tkpack(tklabel(.win, text = '', font = fn, background=backg), side = 'bottom')
pBar <- if (have_ttk)
ttkprogressbar(.win, length = width, variable = .tkval) else
tkwidget(.win, 'ProgressBar', width = width, variable = .tkval)
tkpack(pBar, side = 'bottom')
up <- function(value) {
if (!is.finite(value) || value < min || value > max) return()
.val <<- value
tclvalue(.tkval) <<- 100 * (value - min)/(max - min)
}
}
getVal <- function() .val
kill <- function() if (!.killed) {
tkdestroy(.win)
.killed <<- TRUE
}
title <- function(title) tkwm.title(.win, title)
lab <- function(label) tkconfigure(.lab, text = label)
tkbind(.win, '<Destroy>', function() stop())
up(initial)
structure(list(getVal = getVal, up = up, title = title, label = lab, kill = kill), class = 'tkProgressBar')
}
pb <- tkProgressBar2(title='Performing k-Means clustering', label='Some information in %', min=0, max=100, initial=0, width=400, userfn='verdana', backg='white')
On Linux you set the icon with wm iconphoto; wm iconbitmap does something else entirely. To do that, you'll need to create a photo image with the image data in it.
I'm guessing that you write this in R as:
tcl('wm', 'iconphoto', .win, tcl('image', 'create', 'photo', '-file', 'Icon.gif'))
I'm not quite sure which image formats are supported by the version of Tk you're using, including any image format support packages it has available. The minimal set is GIF and PPM unless you're (bravely) using 8.6, when PNG is also available by default.
(You can also create the content of a photo image programatically, but that's slow for various reasons.)
OSX doesn't have window icons in the same sense; it's normal for each minimized window to just show a snapshot of itself when it is minimized to the dock.

How can I set an action to occur on a key release in xmonad?

How can I set an action to occur on a key release in xmonad?
I don't like menu bars and panels.
Instead of a panel like xmobar I want to have a full screen page of info, (time, currently selected window and workspace etc) appear when I hold down a key combo and then vanish when I let the keys go.
I could code the info page application myself.
I can set the info page to spawn on a key press.
I can not set anything to happen on a key release.
How can I set an action to occur on a key release?
I am considering extending xmonad myself to do this.
I hope I don't have to though because it'd be really annoying.
XMonad passes all received events, including KeyPress events, to the handleEventHook, so this code would be able to react on keyRelease events:
module KeyUp where
import Data.Monoid
import qualified Data.Map as M
import XMonad
import Control.Monad
keyUpEventHook :: Event -> X All
keyUpEventHook e = handle e >> return (All True)
keyUpKeys (XConf{ config = XConfig {XMonad.modMask = modMask} }) = M.fromList $
[ ((modMask, xK_v), io (print "Hi")) ]
handle :: Event -> X ()
handle (KeyEvent {ev_event_type = t, ev_state = m, ev_keycode = code})
| t == keyRelease = withDisplay $ \dpy -> do
s <- io $ keycodeToKeysym dpy code 0
mClean <- cleanMask m
ks <- asks keyUpKeys
userCodeDef () $ whenJust (M.lookup (mClean, s) ks) id
handle _ = return ()
You would use it like that in your xmonad.hs file:
handleEventHook = handleEventHook defaultConfig `mappend`
keyUpEventHook `mappend`
fullscreenEventHook
Unfortunately, this does not work yet: It will only react on KeyRelease events that have a corresponding entry in the regular keys configuration. This is due to grayKeys in XMonad.Main, grabbing only keys mentioned in keys. You can work-around this by defining a dummy action for every combination that you want to handle in KeyUp:
myKeys conf#(XConfig {XMonad.modMask = modMask}) = M.fromList $
...
, ((modMask , xK_v ), return ())
myStartupHook :: X ()
myStartupHook = do
XConf { display = dpy, theRoot = rootw } <- ask
myKeyCode <- io $ (keysymToKeycode dpy xK_Super_R)
io $ grabKey dpy (myKeyCode) anyModifier rootw True grabModeAsync grabModeAsync
spawn "~/ScriptsVcs/hideTint2.sh"
myHook :: Event -> X All
myHook e = do
case e of
ke#(KeyEvent _ _ _ _ _ _ _ _ _ _ _ _ _ _ _) -> do
if ev_keycode ke == 134
then if ev_state ke == 0
then do
-- key has been pressed
spawn "~/ScriptsVcs/showTint2.sh"
else do
spawn "~/ScriptsVcs/hideTint2.sh"
else pure ()
_ -> pure ()
pure $ All True
The above is an example. Do take note that a 'key release' could occur with a modifier key (ev_state).

Resources