Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  problems with wxHaskell installation (Miguel Negrao)
   2. Re:  problems with wxHaskell installation (Brandon Allbery)
   3. Re:  How to solve this using State Monad? (Ertugrul S?ylemez)
   4. Re:  problems with wxHaskell installation (Miguel Negrao)
   5. Re:  How to solve this using State Monad? (Ozgur Akgun)
   6.  State and GUI's / external interfaces / events (Henry Lockyer)


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

Message: 1
Date: Mon, 28 May 2012 20:20:21 +0100
From: Miguel Negrao <miguel.negrao-li...@friendlyvirus.org>
Subject: Re: [Haskell-beginners] problems with wxHaskell installation
To: beginners@haskell.org
Message-ID: <8e5a9b9e-b6d9-441c-b9b8-76222be11...@friendlyvirus.org>
Content-Type: text/plain; charset=windows-1252


A 28/05/2012, ?s 19:44, Heinrich Apfelmus escreveu:

> Miguel Negrao wrote:
>> When I try to install wx after updating cabal it is failing on version 
>> 0.90..0.1:
>> miguelnegrao@Mac-Miguel:~$ cabal install wx
>> Resolving dependencies...
>> Configuring wx-0.90.0.1...
>> Preprocessing library wx-0.90.0.1...
>> Building wx-0.90.0.1...
>> [ 1 of 16] Compiling Graphics.UI.WX.Types ( src/Graphics/UI/WX/Types.hs, 
>> dist/build/Graphics/UI/WX/Types.o )
>> [ 2 of 16] Compiling Graphics.UI.WX.Attributes ( 
>> src/Graphics/UI/WX/Attributes.hs, dist/build/Graphics/UI/WX/Attributes.o )
>> [ 3 of 16] Compiling Graphics.UI.WX.Layout ( src/Graphics/UI/WX/Layout.hs, 
>> dist/build/Graphics/UI/WX/Layout.o )
>> [ 4 of 16] Compiling Graphics.UI.WX.Classes ( src/Graphics/UI/WX/Classes.hs, 
>> dist/build/Graphics/UI/WX/Classes.o )
>> [ 5 of 16] Compiling Graphics.UI.WX.Media ( src/Graphics/UI/WX/Media.hs, 
>> dist/build/Graphics/UI/WX/Media.o )
>> [ 6 of 16] Compiling Graphics.UI.WX.Events ( src/Graphics/UI/WX/Events.hs, 
>> dist/build/Graphics/UI/WX/Events.o )
>> [ 7 of 16] Compiling Graphics.UI.WX.Window ( src/Graphics/UI/WX/Window.hs, 
>> dist/build/Graphics/UI/WX/Window.o )
>> src/Graphics/UI/WX/Window.hs:134:52:
>>   Not in scope: `textCtrlChangeValue'
>> cabal: Error: some packages failed to install:
>> wx-0.90.0.1 failed during the building phase. The exception was:
>> ExitFailure 1
>> Does this mean that the package that was pushed to cabal has an
>> actual  error ? How do I "use the latest patch level releases? of the 
>> packages ?
> 
> Jeremy forgot to narrow the version dependencies of the family of wx 
> packages, not every combination that cabal accepts will actually work. The 
> effect is that you have to reinstall the packages in the right order and with 
> the right version number to get it to work. The following should do the trick
> 
>    cabal install wxdirect-0.90.0.1
>    cabal install wxc-0.90.0.3
>    cabal install wxcore-0.90.0.1
>    cabal install wx-0.90.0.1
> 
> The last number in the version number indicates bug fixes, that's why I refer 
> to it as "patch-level?.

Ah, ok. I ran all those commands, but with --reinstall since some were already 
installed, in that order. Everything installed correctly.

Now when I try to compile a hello world program * I get :

ghc test.hs
[1 of 1] Compiling Main             ( test.hs, test.o )
Linking test ...
ld: warning: ignoring file 
/System/Library/Frameworks//QuickTime.framework/QuickTime, file was built for 
unsupported file format which is not the architecture being linked (x86_64)
ld: warning: could not create compact unwind for _ffi_call_unix64: does not use 
RBP or RSP based frame
Undefined symbols for architecture x86_64:
  "_wxListItemAttr_CreateEx", referenced from:
      _sUn6_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _sUng_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_Create", referenced from:
      
_wxcorezm0zi90zi0zi1_GraphicsziUIziWXCoreziWxcClassesAL_listItemAttrCreate1_info
 in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_CreateWithCb", referenced from:
      _sW0i_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _sW0E_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_Create", referenced from:
      _sWbY_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _sWcg_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_SetTextColour", referenced from:
      _s15xV_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_SetFont", referenced from:
      _s15BK_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s15BO_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_SetBackgroundColour", referenced from:
      _s15Gu_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_HasTextColour", referenced from:
      _s1BbT_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2Jq5_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_HasFont", referenced from:
      _s1Bdd_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2JnT_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_HasBackgroundColour", referenced from:
      _s1Bex_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2JlH_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_GetTextColor", referenced from:
      _s1BfQ_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2JjR_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_GetFont", referenced from:
      _s1Bh9_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2Ji1_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListItemAttr_GetBackgroundColor", referenced from:
      _s1Bis_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2Jgb_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_SetOnGetItemTextCallback", referenced from:
      _s1BB6_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2IKc_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_SetOnGetItemImageCallback", referenced from:
      _s1BCC_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2IIo_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_SetOnGetItemColumnImageCallback", referenced from:
      _s1BE8_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2IGA_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrlVirtual_SetOnGetItemAttrCallback", referenced from:
      _s1BFE_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2IEM_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrl_RefreshItem", referenced from:
      _s1C5g_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2HVB_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrl_IsVirtual", referenced from:
      _s1C6N_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2HTp_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
  "_wxListCtrl_GetItemFont", referenced from:
      _s1Cz0_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
      _s2H2z_info in libHSwxcore-0.90.0.1.a(WxcClassesAL.o)
ld: symbol(s) not found for architecture x86_64
collect2: ld returned 1 exit status

*module Main where
import Graphics.UI.WX

main :: IO ()
main
  = start hello

hello :: IO ()
hello
  = do f    <- frame    [text := "Hello!"]
       quit <- button f [text := "Quit", on command := close f]
       set f [layout := widget quit]

best,
Miguel




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

Message: 2
Date: Mon, 28 May 2012 15:28:32 -0400
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] problems with wxHaskell installation
To: Miguel Negrao <miguel.negrao-li...@friendlyvirus.org>
Cc: beginners@haskell.org
Message-ID:
        <CAKFCL4VdE9SUtWbdAKXABW373d=wOs4WXRscuPSzQv-==s4...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Mon, May 28, 2012 at 3:20 PM, Miguel Negrao <
miguel.negrao-li...@friendlyvirus.org> wrote:

> Now when I try to compile a hello world program * I get :
>
> ghc test.hs
>

If this is not ghc 7.4.1, you need --make there for it to follow and link
the required system libraries.


> ld: warning: ignoring file
> /System/Library/Frameworks//QuickTime.framework/QuickTime, file was built
> for unsupported file format which is not the architecture being linked
> (x86_64)
>

And this sounds like you have a version of the C wx libraries that is not
for 64-bit architectures.

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120528/ec5a1871/attachment-0001.htm>

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

Message: 3
Date: Mon, 28 May 2012 22:49:58 +0200
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: beginners@haskell.org
Message-ID: <20120528224958.0f253...@tritium.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

Hello there kak,

kak dod <kak.dod2...@gmail.com> wrote:

> So, you Monad gurus over here can consider me a block-head, but let me
> assure you people that I am a sincere person trying to learn this
> beautiful but difficult concept.

no worries.  Monads aren't particularly complicated.  The common mistake
is to try to understand "monads" instead of particular monads.  If you
understand Maybe, Either, State and Reader, you effectively understand
what monads are about.

State monads are best understood by looking at their definition:

    newtype State s a = State (s -> (a, s))

For every type 's' the type 'State s' is a monad, a so-called state
monad.  It represents a function from a value of type 's' (commonly
called the "state") to a tuple of two values, the result and a new value
of type 's'.

Whenever you have a function of this type:

    myFunc :: S -> (A, S)

you could just as well write it as:

    myFunc :: State S A

They are entirely equivalent, except that the State variant encapsulates
the function in a newtype constructor.  Now just go ahead and write the
Monad instance for the State type yourself.  Remember that State is a
family of monads, not a monad itself:

    instance Monad (State s)

Now to your actual problem:  I doubt that you really want a state monad.
As said, a state monad is just the type for functions of the above type.
It is well possible to encode DFAs that way, but it will be inconvenient
and probably not what you want.

I would go for a different approach:  There is an arrow that is exactly
for this kind of computations:  the automaton arrow.  Its definition is
this:

    newtype Auto a b = Auto (a -> (b, Auto a b))

It takes an input value of type 'a' and gives a result of type 'b' along
with a new version of itself.  Here is a simple counter:

    counter :: Int -> Auto Int Int
    counter x = Auto (\dx -> (x, counter (x + dx)))

In the first instant this automaton returns the argument (x).  The next
automaton will be counter (x + dx), where dx is the automaton's input.

What is useful about the automaton arrow is that it encodes an entirely
different idea of state:  local state.  Every automaton has its own
local state over which it has complete control.  There is an equivalent
way to define the automaton arrow:

    data Auto a b = forall s. Auto ((a, s) -> (b, s))

You can see how this looks a lot like state monads, but the state is
local to the particular automaton.  You can then connect automata
together using Category, Applicative and/or Arrow combinators.

The automaton arrow is implemented in the 'arrows' library.  It has a
slightly scarier type, because it is an automaton transformer.  In that
library the type Auto (->) is the automaton arrow.


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120528/628e5472/attachment-0001.pgp>

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

Message: 4
Date: Mon, 28 May 2012 21:37:59 +0100
From: Miguel Negrao <miguel.negrao-li...@friendlyvirus.org>
Subject: Re: [Haskell-beginners] problems with wxHaskell installation
To: beginners@haskell.org
Message-ID: <72dfdce7-99be-4004-9f21-c889a1497...@friendlyvirus.org>
Content-Type: text/plain; charset=windows-1252


A 28/05/2012, ?s 20:28, Brandon Allbery escreveu:

> On Mon, May 28, 2012 at 3:20 PM, Miguel Negrao <
> miguel.negrao-li...@friendlyvirus.org> wrote:
> 
>> Now when I try to compile a hello world program * I get :
>> 
>> ghc test.hs
>> 
> 
> If this is not ghc 7.4.1, you need --make there for it to follow and link
> the required system libraries.
> 
> 
>> ld: warning: ignoring file
>> /System/Library/Frameworks//QuickTime.framework/QuickTime, file was built
>> for unsupported file format which is not the architecture being linked
>> (x86_64)
>> 
> 
> And this sounds like you have a version of the C wx libraries that is not
> for 64-bit architectures.

Ok, can?t seem to make it work with ghc, but it is working from inside 
EclipseFP, which means that wxHaskell should be correctly installed now.  Good 
enough for me.

Thanks for the help,
Miguel


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

Message: 5
Date: Mon, 28 May 2012 21:39:37 +0100
From: Ozgur Akgun <ozgurak...@gmail.com>
Subject: Re: [Haskell-beginners] How to solve this using State Monad?
To: kak dod <kak.dod2...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <calzazpa9q+3m9hdmp6esvqh-om9dhh+bmg4ufszpq41t-e2...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi,

On 28 May 2012 19:49, kak dod <kak.dod2...@gmail.com> wrote:

> I wrote a recursive program to do this without using any monads. I simply
> send the entire dfa, the input string and its partial result in the
> recursive calls.
>

Can you post your solution so we can modify it to use the state monad?
Maybe that will be of some help.


-- 
Ozgur Akgun
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120528/e6ff3717/attachment-0001.htm>

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

Message: 6
Date: Tue, 29 May 2012 01:15:13 +0100
From: Henry Lockyer <henry.lock...@ntlworld.com>
Subject: [Haskell-beginners] State and GUI's / external interfaces /
        events
To: Beginners@haskell.org
Message-ID: <c5b21232-5cfd-4ae1-9b31-25c95713c...@ntlworld.com>
Content-Type: text/plain; charset=us-ascii

Hi all,
I'm trying to straighten out my basic understanding around state-based IO 
handling in Haskell.

I've been reading around in several places but it hasn't clicked yet, and the 
input buffer is now cluttered with 
new things to assimilate ;-)

The basic question is about what ways there are to implement state-based 
decisions, where an external event of some kind 
results in some Haskell function/s being called depending on the particular 
event and the current state, then
perhaps some new external action initiated, and new state set.  Basic state 
machine type of logic.

As a starting point I include down at the bottom of this mail a little example 
program which implements something 
like this for terminal IO.  The state/logic could be made arbitrarily more 
complex.
It's a simple 'event loop' that blocks on getChar until a Char is input, with a 
separate pure event/state query function.

One could also implement the per-Char state-based handling using the State 
monad by mapping over 
the Char inputs as a string, for example something like:

main = do hSetBuffering stdin NoBuffering
          interact \str -> evalState ( mapM charfunc str ) initstate
            where charfunc :: Char -> State Char Char
                      . . .
I'm not sure how I would implement the exit case if I used this approach for 
the 'aha!' game below though.

Anyway, a few interrelated questions running out from this general starting 
point:

1. I've not really played with monad transformers yet, but I  guess one could 
use monad transformers to 
   make a combined IO/State monad as an alternative to the basic solution down 
below.  
   Assuming there is no lurking problem with doing that, does it help? 
   (I can't see much advantage, in this case where explicitly manipulating the 
state at each step is the main activity.)

2. The 'event loop' in IO in the example below drives the state 
lookup/branching logic, but how can you separate
    the sequential state logic from the polling process?   This is really the 
nub of my question.
    I'm not familiar with the FFI or the GUI libraries, so with apologies in 
advance for misunderstanding it all...
     say for example we want to implement a Haskell program that responds to 
events arriving as external 
     function calls via the FFI where the state-based logic is in Haskell but 
the events are not polled for, they
     just arrive (for example could be driven by some main loop in external 
functionality, eg. GUI). 
     We want the Haskell implementation to respond in a sequential state-based 
manner so that if
     the external events/calls 'a', 'a', 'h' arrive this could produce 
different responses (to the second and third events)
     compared to the event sequence 'a', 'h', 'a'. 
     How/can you do this in Haskell?
     The events could come from some completely independent and/or 
uncontrollable sources but we require the
     Haskell program to respond according to arrival sequence.   
     My intuition says that this is not possible if the events arrive simply as 
independent function calls on an
     external interface, but that they must be collected somehow into a single 
sequential 
     entity such as a file, list, 'stream' or somesuch and then they can be 
mapped over or some kind of read loop can 
     pull them off in sequence as in the example below.   But I am probably 
wrong :)     ?

3. What state/event handling model do the GUI solutions like whhaskell or 
gtk2hs use? I read that they use callbacks,
    which makes sense, but does it mean that the callbacks must be manipulated 
(or some associated widget attributes) so as
    to encode the state back into the GUI at every step?  In other words the 
first 'a' in the above "aah" vs "aha" example
    would have to, as a minimum, initiate a change in the callback/attributes 
of the 'a' generator so that the second
    'a' will actually be a different 'a' ( 'a2' perhaps) or carry some 
additional parameter info so that the correct function in the
    receiving Haskell is invoked?  This could be horrible if there are, say, 50 
different widgets that could generate the next event
    and they would all have to be updated to reflect each state change.  I feel 
it must be better than this somehow..  
    So how does it work?   

Any help appreciated.
Thanks/ Henry

--
-- "aha!" 
--
-- An exciting game that requires the string "aha!" to
-- be entered in order to reach the exit.
--

import System.IO

type MyState = Char

initstate, exitstate :: MyState
initstate = 'a'
exitstate = 'z'

main :: IO ()
main = do hSetBuffering stdin NoBuffering
          stateIO initstate
 
stateIO :: MyState -> IO ()
stateIO s = do c_in <- getChar
               let (c_out, s') = stateMC c_in s
               putStrLn $ ' ':c_out:[]
               if s' /= exitstate then stateIO s' 
                                  else putStrLn "Bye..."

stateMC :: Char -> MyState -> (Char, MyState)
stateMC 'a' 'a' = ('Y', 'b')
stateMC 'h' 'b' = ('Y', 'c')
stateMC 'a' 'c' = ('Y', 'd')
stateMC '!' 'd' = ('*', 'z')
stateMC  _   _  = ('N', 'a')




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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 47, Issue 26
*****************************************

Reply via email to