[Haskell-cafe] Trying to experiment with tangible values using GuiTV

Martin Baldan martinobal at gmail.com
Tue Oct 4 00:28:15 CEST 2011


Hello all,

I'm very new to Haskell, but still I'd like to play with "tangible values",
which I find really intriguing. After getting some kind help in
haskell-beginners, I managed to compile and run a small example. Which is as
follows:

------------------


{-# LANGUAGE OverlappingInstances, UndecidableInstances
           , IncoherentInstances, FlexibleContexts
           , TypeSynonymInstances, FlexibleInstances
           , MultiParamTypeClasses
           #-}
-- For ghc 6.6 compatibility
{-# OPTIONS -fglasgow-exts -fallow-overlapping-instances
-fallow-incoherent-instances #-}


---- Some GuiTV examples.  See also the examples in TV.

import Data.List (sort)

-- my addition
import Data.Monoid
-- end my addition

import Interface.TV.UI
import Control.Arrow.DeepArrow
import Data.FunArr

-- TypeCompose
import Data.Title

-- To pick up the FunArr instance for OFun.
import Interface.TV.OFun()

reverseT :: CTV (String -> String)
reverseT = tv (oTitle "reverse" defaultOut) reverse

main = runUI reverseT


-----------------------

There were some warnings during compilation:

-----
[1 of 1] Compiling Main             ( myexample.hs, myexample.o )

myexample.hs:7:11:
   Warning: -fallow-overlapping-instances is deprecated: use
-XOverlappingInstances or pragma {-# LANGUAGE OverlappingInstances #-}
instead

myexample.hs:7:11:
   Warning: -fallow-incoherent-instances is deprecated: use
-XIncoherentInstances or pragma {-# LANGUAGE IncoherentInstances #-}
instead
Linking myexample ...
martin at martin-desktop:/media/
ext4logicaUnTera/cosas_linux/programs/haskell/TV/examples/src/miejemplo$
ghc --make myexample.hs

myexample.hs:7:11:
   Warning: -fallow-overlapping-instances is deprecated: use
-XOverlappingInstances or pragma {-# LANGUAGE OverlappingInstances #-}
instead

myexample.hs:7:11:
   Warning: -fallow-incoherent-instances is deprecated: use
-XIncoherentInstances or pragma {-# LANGUAGE IncoherentInstances #-}
instead

-----


When I run it, I get a little window with the "reverse" title and two
textboxes. However, when I write something in the upper box, nothing
happens. I must say that when I use runIO instead of runUI in this little
program, the interactive program does work. Only the GUI version doesn't.

So, the person who helped me (Brandon Allbery) said it's probably because of
a GuiTV being a bit too old. He recommended me to ask about the issue here,
at haskell-cafe.

Any suggestions? Maybe I should use GtkTV istead of GuiTV? Thanks in
advance!


  Martin O.B.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20111004/3871a18b/attachment.htm>


More information about the Haskell-Cafe mailing list