capturing right-click event on treeview row [haskell gtk2hs] - user-interface

I have searched thoroughly (at least I believe so) and I didn't find any answer for my problem, so I'd like to ask you for help.
I'm trying to determine when a user right-clicks a row in my treeView (list of users) and then show a pop-up window with options to edit and delete them.
Here's how my app looks so far
Here's the code that generates the treeView:
import Graphics.UI.Gtk
import System.Glib.Signals (on)
import Graphics.UI.Gtk.Glade
import Graphics.UI.Gtk.ModelView as New
import SzuDB
data GUI = GUI {
mainWindow :: Window,
--Buttony
dodajUczBt :: Button,
cancelAddUczBt :: Button,
zapiszUczBtn :: Button,
--TreeView
listaUczView :: TreeView,
-- Dialogi
dodajUzDialog :: Dialog,
-- Entry
nImie :: Entry,
nNazwisko :: Entry,
nWiek :: SpinButton,
lblLiczbaUcz :: Label
}
-- Różne listy
data ListStores = ListStores { uczestnicy :: ListStore Uczestnik }
main = do
initGUI
dbh <- connect "szu.db"
gui <- loadGlade "szu.glade" dbh
-- lapiemy uzytkownikow
uczestnicy <- getAllUsers dbh
labelSetText (lblLiczbaUcz gui) $ "Liczba uczestników: "++ show (length uczestnicy)
listaUczestnikow <- New.listStoreNew uczestnicy
New.treeViewSetModel (listaUczView gui) listaUczestnikow
wyswietlUczestnikow (listaUczView gui) listaUczestnikow
let liststore = ListStores $ listaUczestnikow
loadGUIEvents gui dbh liststore
widgetShowAll (mainWindow gui)
mainGUI
-- loadGlade etc.
wyswietlUczestnikow view uczestnik = do
New.treeViewSetHeadersVisible view True
-- add a couple columns
renderer1 <- New.cellRendererTextNew
col1 <- New.treeViewColumnNew
New.treeViewColumnPackStart col1 renderer1 True
New.cellLayoutSetAttributes col1 renderer1 uczestnik $ \row -> [ New.cellText := imie row ]
New.treeViewColumnSetTitle col1 "Imię"
New.treeViewAppendColumn view col1
renderer2 <- New.cellRendererTextNew
col2 <- New.treeViewColumnNew
New.treeViewColumnPackStart col2 renderer2 True
New.cellLayoutSetAttributes col2 renderer2 uczestnik $ \row -> [ New.cellText := nazwisko row ]
New.treeViewColumnSetTitle col2 "Nazwisko"
New.treeViewAppendColumn view col2
renderer3 <- New.cellRendererTextNew
col3 <- New.treeViewColumnNew
New.treeViewColumnPackStart col3 renderer3 True
New.cellLayoutSetAttributes col3 renderer3 uczestnik $ \row -> [ New.cellText := show (wiek row) ]
New.treeViewColumnSetTitle col3 "Wiek"
New.treeViewAppendColumn view col3
--
-- ladujemy wydarzenia
--
-- loadGuiEvents etc.
I have already tried to use the example at http://www.muitovar.com/gtk2hs/chap7-2.html but it resulted in compile error (it said that eventButton is used with one argument while it requires none).
Any help would be greatly appreciated :)
Cheers

Okay it seems I'm going be the first one to find answer for my own question :)
(1) First of all the example at http://www.muitovar.com/gtk2hs/chap7-2.html didn't work for me because you have two eventButton functions in gtk2hs and you have to use the one from Graphics.UI.Gtk.Gdk.Events. So you have to add at the beginning of the file:
import Graphics.UI.Gtk.Gdk.Events as Ev
and then add Ev. prefix to eventButton, RightButton and eventSent. It'll work now :)
(2) How to respond to right clicks on treeView row:
Having solved the aforementioned problem I stumbled upon this example, where it's shown how to respond to selecting a row in treeView. So I mixed those two solutions and came up with something like this (most of the code comes from the treeview example with some of my tweaks):
module Main where
{- an example how to select from a list
not satisfactory yet:
- there should be a simpler way to render a simple list
- i could not convert the model i got back to a list
from which to get the value
- the interface offers a great number of functions
and it is very difficult to find which ones are
really needed for simple tasks
-}
import Graphics.UI.Gtk
import Graphics.UI.Gtk.ModelView as Model
import Graphics.UI.Gtk.Gdk.Events as Ev
main :: IO ()
main = do
initGUI -- is start
window <- windowNew
list <- listStoreNew ["Vince", "Jhen", "Chris", "Sharon"]
treeview <- Model.treeViewNewWithModel list
Model.treeViewSetHeadersVisible treeview True
-- there should be a simpler way to render a list as the following!
col <- Model.treeViewColumnNew
Model.treeViewColumnSetTitle col "colTitle"
renderer <- Model.cellRendererTextNew
Model.cellLayoutPackStart col renderer False
Model.cellLayoutSetAttributes col renderer list
$ \ind -> [Model.cellText := ind]
Model.treeViewAppendColumn treeview col
--tree <- Model.treeViewGetSelection treeview
--Model.treeSelectionSetMode tree SelectionSingle
--Model.onSelectionChanged tree (oneSelection list tree)
set window [ windowDefaultWidth := 100
, windowDefaultHeight := 200
, containerChild := treeview
]
-- here comes the right-click popup
eda <- actionNew "EDA" "Edit" Nothing Nothing
pra <- actionNew "PRA" "Process" Nothing Nothing
rma <- actionNew "RMA" "Remove" Nothing Nothing
saa <- actionNew "SAA" "Save" Nothing Nothing
agr <- actionGroupNew "AGR1"
mapM_ (actionGroupAddAction agr) [eda,pra,rma,saa]
uiman <- uiManagerNew
uiManagerAddUiFromString uiman uiDecl
uiManagerInsertActionGroup uiman agr 0
maybePopup <- uiManagerGetWidget uiman "/ui/popup"
let pop = case maybePopup of
(Just x) -> x
Nothing -> error "Cannot get popup from string"
onButtonPress treeview (\x -> if (Ev.eventButton x) == Ev.RightButton
then do
menuPopup (castToMenu pop) Nothing
return (Ev.eventSent x)
else return (Ev.eventSent x))
mapM_ (prAct treeview list) [eda,pra,rma,saa]
onDestroy window mainQuit
widgetShowAll window
mainGUI
return ()
uiDecl = "<ui> \
\ <popup>\
\ <menuitem action=\"EDA\" />\
\ <menuitem action=\"PRA\" />\
\ <menuitem action=\"RMA\" />\
\ <separator />\
\ <menuitem action=\"SAA\" />\
\ </popup>\
\ </ui>"
-- Handle the right-click. You can write a function that'll respond to various
-- actions, like for example: handleAction "EDA" = do something, etc.
prAct treeview list a = onActionActivate a $ do
name <- actionGetName a
-- getting the selected row
tree <- Model.treeViewGetSelection treeview
-- you can also use treeSelectionGetSelected to get the Iter object
-- and then convert it to Int by using listStoreIterToIndex and so get
-- the ListStore item at given index
sel <- Model.treeSelectionGetSelectedRows tree
let s = head (head sel)
v <- Model.listStoreGetValue list s
putStrLn ("Action Name: " ++ name ++ " | Item: " ++ v)
I hope it'll be helpful for someone :)
Cheers

Related

Edit a datatable in shiny throwing an error : Can't subset with `[` using an object of class NULL

I am trying to edit a data table (DT: datatable) on server side and i am using a reactive data table which is rendered on the front end. Now i want to edit the data table and retrieve the information from edited data table. Here is a reproducible example of what i am trying to achieve as mentioned in the comments in the reprex :
library(shiny)
library(DT)
library(tidyverse)
d <- iris
ui <- fluidPage(
dataTableOutput("table1"),
dataTableOutput("table2")
)
server <- function(input,output,session){
# This is the main table I would want to display in its full context
output$table1 <- renderDataTable(
datatable(d)
)
get_row <-reactive({
d %>% slice(input$table1_rows_selected)})
# Here the table with row selected from table 1 is displayed
output$table2 <- renderDataTable({
datatable(get_row(),
editable = TRUE)
})
# Now as the cell gets edited in table 2, i want the edited value to show and make the last column values = NA
proxy <- dataTableProxy("table2")
observeEvent(eventExpr = input$table2_cell_edit, handlerExpr = {
x <- isolate(get_row())
info = input$table2_cell_edit
i = info$row
j = info$column
v = info$value
x[i, j] <<- DT::coerceValue(v, x[i, j])
x <- x %>% mutate(Species = NA)
replaceData(proxy, x, resetPaging = FALSE)
})
}
shinyApp(ui = ui, server = server)
I am getting an error Error in <<-: object 'x' not found. Not sure where am i wrong.
The solution came down to your input$table2_cell_edit names. It uses col not column. The error created an empty x that couldn't accept your assignment of the new value. I used a simpler assignment of the new value.
In the future, use the print() function to print out variables in your app to figure out what's being passed or not passed downstream. That's how a figured out this error.
library(shiny)
library(DT)
library(tidyverse)
d <- iris
ui <- fluidPage(
dataTableOutput("table1"),
dataTableOutput("table2")
)
server <- function(input,output,session){
# This is the main table I would want to display in its full context
output$table1 <- renderDataTable(
datatable(d)
)
get_row <-reactive({
req(input$table1_rows_selected)
d %>% slice(input$table1_rows_selected)})
# Here the table with row selected from table 1 is displayed
output$table2 <- renderDataTable({
req(get_row)
datatable(get_row(),
editable = TRUE)
})
# Now as the cell gets edited in table 2, i want the edited value to show and make the last column values = NA
proxy <- dataTableProxy("table2")
observeEvent(eventExpr = input$table2_cell_edit, handlerExpr = {
x <- isolate(get_row())
info = input$table2_cell_edit
i = info$row
### info uses 'col' not 'column'
j = info$col
v = info$value
### used a base R subset assignment
x[i, j] <- v
x <- x %>% mutate(Species = NA)
replaceData(proxy, x, resetPaging = FALSE)
})
}
shinyApp(ui = ui, server = server)

Debugging <<loop>> error message in haskell

Hello i am encountering this error message in a Haskell program and i do not know where is the loop coming from.There are almost no IO methods so that i can hook myself to them and print the partial result in the terminal.
I start with a file , i read it and then there are only pure methods.How can i debug this ?
Is there a way to attach to methods or create a helper that can do the following:
Having a method method::a->b how can i somehow wrap it in a iomethod::(a->b)->IO (a->b) to be able to test in in GHCI (i want to insert some putStrLn-s etc ?
P.S My data suffer transformations IO a(->b->c->d->......)->IO x and i do not know how to debug the part that is in the parathesis (that is the code that contains the pure methods)
Types and typeclass definitions and implementations
data TCPFile=Rfile (Maybe Readme) | Dfile Samples | Empty
data Header=Header { ftype::Char}
newtype Samples=Samples{values::[Maybe Double]}deriving(Show)
data Readme=Readme{ maxClients::Int, minClients::Int,stepClients::Int,maxDelay::Int,minDelay::Int,stepDelay::Int}deriving(Show)
data FileData=FileData{ header::Header,rawContent::Text}
(>>?)::Maybe a->(a->Maybe b)->Maybe b
(Just t) >>? f=f t
Nothing >>? _=Nothing
class TextEncode a where
fromText::Text-> a
getHeader::TCPFile->Header
getHeader (Rfile _ ) = Header { ftype='r'}
getHeader (Dfile _ )= Header{ftype='d'}
getHeader _ = Header {ftype='e'}
instance Show TCPFile where
show (Rfile t)="Rfile " ++"{"++content++"}" where
content=case t of
Nothing->""
Just c -> show c
show (Dfile c)="Dfile " ++"{"++show c ++ "}"
instance TextEncode Samples where
fromText text=Samples (map (readMaybe.unpack) cols) where
cols=splitOn (pack ",") text
instance TextEncode Readme where
fromText txt =let len= length dat
dat= case len of
6 ->Prelude.take 6 .readData $ txt
_ ->[0,0,0,0,0,0] in
Readme{maxClients=Prelude.head dat,minClients=dat!!1,stepClients=dat!!2,maxDelay=dat!!3,minDelay=dat!!4,stepDelay=dat!!5} where
instance TextEncode TCPFile where
fromText = textToFile
Main
module Main where
import Data.Text(Text,pack,unpack)
import Data.Text.IO(readFile,writeFile)
import TCPFile(TCPFile)
main::IO()
main=do
dat<-readTcpFile "test.txt"
print dat
readTcpFile::FilePath->IO TCPFile
readTcpFile path =fromText <$> Data.Text.IO.readFile path
textToFile::Text->TCPFile
textToFile input=case readHeader input >>? (\h -> Just (FileData h input)) >>? makeFile of
Just r -> r
Nothing ->Empty
readHeader::Text->Maybe Header
readHeader txt=case Data.Text.head txt of
'r' ->Just (Header{ ftype='r'})
'd' ->Just (Header {ftype ='d'})
_ -> Nothing
makeFile::FileData->Maybe TCPFile
makeFile fd= case ftype.header $ fd of
'r'->Just (Rfile (Just (fromText . rawContent $ fd)))
'd'->Just (Dfile (fromText . rawContent $ fd))
_ ->Nothing
readData::Text->[Int]
readData =catMaybes . maybeValues where
maybeValues=mvalues.split.filterText "{}"
#all the methods under this line are used in the above method
mvalues::[Text]->[Maybe Int]
mvalues arr=map (\x->(readMaybe::String->Maybe Int).unpack $ x) arr
split::Text->[Text]
split =splitOn (pack ",")
filterText::[Char]->Text->Text
filterText chars tx=Data.Text.filter (\x -> not (x `elem` chars)) tx
I want first to clean the Text from given characters , in our case }{ then split it by ,.After the text is split by commas i want to parse them, and create either a Rfile which contains 6 integers , either a Dfile (datafile) which contains any given number of integers.
Input
I have a file with the following content: r,1.22,3.45,6.66,5.55,6.33,2.32} and i am running runghc main 2>err.hs
Expected Output : Rfile (Just (Readme 1.22 3.45 6.66 5.55 6.33 2.32))
In the TextEncode Readme instance, len and dat depend on each other:
instance TextEncode Readme where
fromText txt =let len= length dat
dat= case len of
To debug this kind of thing, other than staring at the code, one thing you can do is compile with -prof -fprof-auto -rtsopts, and run your program with the cmd line options +RTS -xc. This should print a trace when the <<loop>> exception is raised (or if the program loops instead, when you kill it (Ctrl+C)). See the GHC manual https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/runtime_control.html#rts-flag--xc
As Li-yao Xia said part of the problem is the infinite recursion, but if you tried the following code, then the problem still remains.
instance TextEncode Readme where
fromText txt =let len= length [1,2,3,4,5,6] --dat
dat= case len of
The second issue is that the file contains decimal numbers but all the conversion function are expecting Maybe Int, changing the definitions of the following functions should give the expected results, on the other hand probably the correct fix is that the file should have integers and not decimal numbers.
readData::Text->[Double]
--readData xs = [1,2,3,4,5,6,6]
readData =catMaybes . maybeValues where
maybeValues = mvalues . split . filterText "{}"
--all the methods under this line are used in the above method
mvalues::[Text]->[Maybe Double]
mvalues arr=map (\x->(readMaybe::String->Maybe Double).unpack $ x) arr
data Readme=Readme{ maxClients::Double, minClients::Double,stepClients::Double,maxDelay::Double,minDelay::Double,stepDelay::Double}deriving(Show)

Elm, how to get current time and post it to server

According to this answer and its helpful Ellie I now have an idea of how we get the current time in Elm 0.18.
I want to get the current time and then post it in JSON to my server. I already have a POST working with a hardcoded timestamp, but I just don't see how to get the current time and then include it in the JSON I am POSTing.
My guess is that I need to chain a couple of commands (get current time, make a POST to server).
[I have also read another SO which shows how you can run a few commands in a row by directly calling the update function, which sounds like a nice idea but I am not sure if it is what I need for my situation.]
Experiment ([edit] perhaps more of a distraction than was intended)
In order to get my head around this I thought I would try to solve a similar problem that I can more easily set up in Ellie.
In the original Ellie the current time is gotten, updated into the model, and then the view function shows it.
In my version I wanted this to be a two-step process and therefore have grown the model to be a Maybe Float for the time and a String message. The view function shows the message string and a button -- the plan is that when the button is pressed it tells the runtime to 'go get the current time and then copy it across into the message slot'.
If I can solve this problem then I feel like I can solve my original problem.
My Ellie does not do this yet. When you press the button the time is gotten and is put into the time slot in the model, but I do not know how to tell the runtime to '...now copy that time across into the message slot'. The PutTimeInMessage message is in place, but I don't know how to get it to run after the GetCurrentTime message/command.
Any suggestions?
Here is my code so far (it compiles), which you can run here in Ellie:
module Main exposing (..)
import Html exposing (..)
import Html.Events exposing (..)
import Time exposing (Time)
import Date
import Task
type alias Model =
{ time : Maybe Float
, message : String
}
type Msg
= OnTime Time
| GetCurrentTime
| PutTimeInMessage
update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
case msg of
OnTime t ->
( { model | time = Just t }, Cmd.none )
GetCurrentTime ->
( model, getTime )
PutTimeInMessage ->
case model.time of
Nothing ->
( model, Cmd.none )
Just t ->
( { model | message = toString t }, Cmd.none )
view : Model -> Html Msg
view model =
div []
[ div []
[ button [ onClick GetCurrentTime ] [ Html.text "Get now time." ]
]
, model.message |> Html.text
]
getTime : Cmd Msg
getTime =
Time.now
|> Task.perform OnTime
main =
Html.program
{ init = ( Model Nothing "Empty message.", Cmd.none )
, update = update
, view = view
, subscriptions = always Sub.none
}
The way I see it, you can just update message field along with time field, when OnTime message is received. Thus, the whole update function is going to look like this:
update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
case msg of
OnTime t ->
( { model | time = Just t, message = toString t }, Cmd.none )
GetCurrentTime ->
( model, getTime )
The message is set in OnTime action, because in the GetCurrentTime time is unknown and is known only after getTime function is perform and OnTime message is received.
If you still want to use a separate action for putting the message, then the following code is the option:
update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
case msg of
OnTime t ->
update PutTimeInMessage { model | time = Just t }
GetCurrentTime ->
( model, getTime )
PutTimeInMessage ->
case model.time of
Nothing ->
( model, Cmd.none )
Just t ->
( { model | message = toString t }, Cmd.none )
But to be honest, the most preferable solution, would be just displaying the time in the view differently, so you don't need the message field (but probably I don't see the whole picture):
view : Model -> Html Msg
view model =
div []
[ div []
[ button [ onClick GetCurrentTime ] [ Html.text "Get now time." ]
]
, viewTime model.time
]
viewTime : Maybe Float -> Html Msg
viewTime time =
case time of
Nothing -> Html.text "Empty message."
Just t -> Html.text (toString t)
I came across an SO which explained how to do a sequence of Http requests with Task.andThen. Since I can see the type of Time.now is a Task I figured that I could adapt that example for my purposes if I use Http.toTask.
Below is the solution I came up with and here it is in Ellie:
module Main exposing (..)
import Html exposing (..)
import Html.Events exposing (..)
import Http
import Json.Decode as JD
import Json.Encode as JE
import Task
import Time
type alias Model =
{ url : String
}
type Msg
= PostTimeToServer
| PostDone (Result Http.Error String)
update : Msg -> Model -> ( Model, Cmd Msg )
update msg model =
case msg of
PostTimeToServer ->
( model, postTimeToServer model.url )
PostDone _ ->
( model, Cmd.none )
view : Model -> Html Msg
view model =
div []
[ div []
[ button [ onClick PostTimeToServer ] [ Html.text "POST the current time." ]
]
]
postTimeToServer : String -> Cmd Msg
postTimeToServer url =
let
getTime =
Time.now
postTime t =
JD.string
|> Http.post url (JE.float t |> Http.jsonBody)
|> Http.toTask
request =
getTime <<-- Here is
|> Task.andThen postTime <<-- the key bit.
in
Task.attempt PostDone request
main =
Html.program
{ init = ( Model "url_here", Cmd.none )
, update = update
, view = view
, subscriptions = always Sub.none
}

Fields and Events in Elm 0.13

This question somehow relates to How to use Fields in Elm 0.13 (and we are working on the same assignment).
In my case, everything that changes in the game should generate a Event:
data Event = NewGame
| PauseGame
| Turn [KeyCode]
| PlayerActive [Bool]
| PlayerChanged [PlayerSettings]
| Tick Time
The PlayerChanged event, for example, is generated as follows:
settingsSignal : Signal Event
settingsSignal =
lift PlayerChanged <|
combine [ pOneSettingsSignal, pTwoSettingsSignal
, pThreeSettingsSignal, pFourSettingsSignal]
pOneSettingsSignal : Signal PlayerSettings
pOneSettingsSignal =
PlayerSettings <~ (Controls <~ lift toCode pOneUp.signal
~ lift toCode pOneDown.signal
~ lift toCode pOneLeft.signal
~ lift toCode pOneRight.signal)
~ (pOneColor.signal)
~ (lift contentToString pOneName.signal)
where pOne<Direction> and pOneColor are inputs for dropDowns and pOneName is an Input for a Input.Field:
pOneName : Input Content
pOneName = input (Content nameOne (Selection 0 0 Forward))
I hereby assume that when I update the text field (or a dropdown), a PlayerChanged [PlayerSettings] event will be generated. All event get combined as follows:
eventSignal : Signal Event
eventSignal = merges [ clockSignal
, newGameSignal
, pauseGameSignal
, turnSignal
, activeSignal
, settingsSignal ]
and finally the event signal is lifted onto an update function:
gameState : Signal Game
gameState =
foldp update initialGame eventSignal
main = lift2 view gameState Window.dimensions
However, when the game is paused, it seems that all input is blocked and no signals propagate anymore. Also, the text fields are uneditable. Each Input.Field for the player names is defined as follows:
playerOneName : String -> Element
playerOneName name =
field defaultStyle pOneName.handle identity nameOne
(Content name (Selection 0 0 Forward))
and then, in the view function
pOneNameField = playerOneName playerOne.settings.name
To me it seems like everything is correct. When editing the displayed field, pOneName.signal is changed, which causes (trough a series of liftings) a PlayerChanged event to be generated, which causes the model to be redrawn, which should show the new update. Somehow the Input.Field is still uneditable, however. Worse: even a simple NewGame event isn't generated anymore and events from the dropdowns are also not propagated: nothing changes.
newGameSignal : Signal Event
newGameSignal =
always NewGame <~ (keepIf identity False <| space)
If I start the game in playing mode (thus no input forms are shown), this works fine and I can reset the game. It seems like the inputs are blocking the event stream, but I can't figure out where its going wrong.
So, I fixed it.
Appearantly the
case (event, game.state) of
(NewGame, _) ->
...
(Tick t, Playing) ->
statement is blocking, so it didn't match Tick Time signals sent in the Paused and Ended states and blocked there. A simple
(_, _) -> game
case fixed everything, so my 960 lines of Elm don't go to waste!

Simple debugging in Haskell

I am new to Haskell. Previously I have programmed in Python and Java. When I am debugging some code I have a habit of littering it with print statements in the middle of code. However doing so in Haskell will change semantics, and I will have to change my function signatures to those with IO stuff. How do Haskellers deal with this? I might be missing something obvious. Please enlighten.
Other answers link the official doco and the Haskell wiki but if you've made it to this answer let's assume you bounced off those for whatever reason. The wikibook also has an example using Fibonacci which I found more accessible. This is a deliberately basic example which might hopefully help.
Let's say we start with this very simple function, which for important business reasons, adds "bob" to a string, then reverses it.
bobreverse x = reverse ("bob" ++ x)
Output in GHCI:
> bobreverse "jill"
"llijbob"
We don't see how this could possibly be going wrong, but something near it is, so we add debug.
import Debug.Trace
bobreverse x = trace ("DEBUG: bobreverse" ++ show x) (reverse ("bob" ++ x))
Output:
> bobreverse "jill"
"DEBUG: bobreverse "jill"
llijbob"
We are using show just to ensure x is converted to a string correctly before output. We also added some parenthesis to make sure the arguments were grouped correctly.
In summary, the trace function is a decorator which prints the first argument and returns the second. It looks like a pure function, so you don't need to bring IO or other signatures into the functions to use it. It does this by cheating, which is explained further in the linked documentation above, if you are curious.
Read this. You can use Debug.Trace.trace in place of print statements.
I was able to create a dual personality IO / ST monad typeclass, which will print debug statements when a monadic computation is typed as IO, them when it's typed as ST. Demonstration and code here: Haskell -- dual personality IO / ST monad? .
Of course Debug.Trace is more of a swiss army knife, especially when wrapped with a useful special case,
trace2 :: Show a => [Char] -> a -> a
trace2 name x = trace (name ++ ": " ++ show x) x
which can be used like (trace2 "first arg" 3) + 4
edit
You can make this even fancier if you want source locations
{-# LANGUAGE TemplateHaskell #-}
import Language.Haskell.TH
import Language.Haskell.TH.Syntax as TH
import Debug.Trace
withLocation :: Q Exp -> Q Exp
withLocation f = do
let error = locationString =<< location
appE f error
where
locationString :: Loc -> Q Exp
locationString loc = do
litE $ stringL $ formatLoc loc
formatLoc :: Loc -> String
formatLoc loc = let file = loc_filename loc
(line, col) = loc_start loc
in concat [file, ":", show line, ":", show col]
trace3' (loc :: String) msg x =
trace2 ('[' : loc ++ "] " ++ msg) x
trace3 = withLocation [| trace3' |]
then, in a separate file [from the definition above], you can write
{-# LANGUAGE TemplateHaskell #-}
tr3 x = $trace3 "hello" x
and test it out
> tr3 4
[MyFile.hs:2:9] hello: 4
You can use Debug.Trace for that.
I really liked Dons short blog about it:
https://donsbot.wordpress.com/2007/11/14/no-more-exceptions-debugging-haskell-code-with-ghci/
In short: use ghci, example with a program with code called HsColour.hs
$ ghci HsColour.hs
*Main> :set -fbreak-on-exception
*Main> :set args "source.hs"
Now run your program with tracing on, and GHCi will stop your program at the call to error:
*Main> :trace main
Stopped at (exception thrown)
Ok, good. We had an exception… Let’s just back up a bit and see where we are. Watch now as we travel backwards in time through our program, using the (bizarre, I know) “:back” command:
[(exception thrown)] *Main> :back
Logged breakpoint at Language/Haskell/HsColour/Classify.hs:(19,0)-(31,46)
_result :: [String]
This tells us that immediately before hitting error, we were in the file Language/Haskell/HsColour/Classify.hs, at line 19. We’re in pretty good shape now. Let’s see where exactly:
[-1: Language/Haskell/HsColour/Classify.hs:(19,0)-(31,46)] *Main> :list
18 chunk :: String -> [String]
vv
19 chunk [] = head []
20 chunk ('\r':s) = chunk s -- get rid of DOS newline stuff
21 chunk ('\n':s) = "\n": chunk s
^^

Resources