Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Henning Thielemann

On Thu, 11 Jan 2007, John Ky wrote:

 Does anyone know where I can find a simple UDP client/server written in
 Haskell?

There is some support as part of a SuperCollider wrapper:
 http://www.slavepianos.org/rd/sw/sw-69/Sound/OpenSoundControl/UDP.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Yitzchak Gale

Iavor Diatchki wrote:

The state transformer inherits its behavior from
the underlying monad.


Ross Paterson wrote:

This (like StateT) gives you strictness in the pair, but doesn't give
the strictness in the state that the original poster wanted.


I think it does - if you run his program with State Int
replaced by StateT Int Identity, it now runs in constant memory.


Once we have this kind of strictness, then the programmer
has control over the state.


That is true for MTL as well.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HaskellForge?

2007-01-11 Thread tphyahoo

I think people want something like CPAN. This implies a centralized
official repository, somewhere that isn't going to go away, ever, because
too many people would scream. It should probably be mirrored, too, like with
cpan.

Maybe darcs.haskell.org is ok for this roll already. Not sure. (Still a
haskell nube.)

Cheapo repo hosting is for projects where the owners don't feel secure
enough, or don't want the responsibility, of committing to the official
repo.

Committing to the social repo gets you status, but it's work too because of
maintenance, bug reports, etc. So, like with cpan, some will, some won't.

Module chasing should carry on in the context of that repo. External
dependency chasing -- like you need to install some c library... well, I'm
not sure. 

Right everyone?
-- 
View this message in context: 
http://www.nabble.com/HaskellForge--tf2935549.html#a8276650
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Yitzchak Gale

Josef Svenningsson wrote:

Take the state monad for example. Should it be
strict or lazy in the state that it carries
around? What about the value component?
...both strict and lazy variants are useful.


I wrote:

Are those really needed?



...it wouldn't be very convenient, would it?
Sometimes I find that I want strict state by
default and then I don't want to sprinkle my
code with seqs.


I don't think that is so inconvenient. Why do we
need to define getStrict, putStrict, getsStrict,
etc., when it is perhaps even more clear to write
get $!, put $!., (gets . ($!)), etc.?.

The same goes for Iavor's monad library.


Now, the challenge here is to design a library
which doesn't explode in size from all the
various possibilities for strictness or
laziness.


I am now pretty convinced that the only thing we
need is two versions of each monad, varying only
the strictness of =.

Then, of course, we will need runFoo for each, and
evalFoo and execFoo for each state monad.

And adaptors that allow you to run a lazy
calculation inside a strict one and vice-versa. So
we need an asStrict function and an asLazy
function for each lazy/strict pair of monads.

I think that is all we need. Not too bad.

I am very impressed that we get most of that
almost for free in Iavor's library.


The same challenge exists in many of the Data.*
libraries. I think this is very important.


I am now a bit more optimistic. Has anyone looked
through them?


http://www.cs.chalmers.se/~josefs/monadlib/
...instantiating this with different pair types
with different strictness properties will give
us total control over strictness for state and
value.


Hmm. Your current implementation doesn't seem to
do it that way. You use tuples for both the lazy
version and the strict version, and each defines
its own Monad instance for all Pair types. So it
is impossible to use both in the same module, even
with hiding.

I tried to work on this a little. I defined a
strict Pair type and tried to find a single Monad
instance that will give the right strictness for
both if you just vary between lazy and strict
pairs.

We need that both of the following converge
in constant stack space:

take 100 $ evalState (repeatM $ modify (+1)) 0
execStateStrict (replicateM_ 10 $ modify (+1)) 0

(You can verify that this is true if you use the
standard evalState, and replace execStateStrict
with runIdentity . execStateT.)

I was unable to hit upon the right combination of
seqs in the Monad instance. Is it really possible?

Of course, you could use a newtype of tuples and
define separate Monad instances. But then we are
not gaining anything over just defining the lazy
and strict monads directly.

Regards,
Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Yitzchak Gale wrote:
 You're right, it is not in the docs. I don't think anyone would
 have planned it that way. StateT is strict only because there
 happens to be a line in a do-expression that looks like:
   (a, s') - runStateT m s
 The tuple pattern-match causes the strictness.
 That appears accidental, so it seems to be just an honest bug.

I agree that this is an accident, but the bug is in lazy State, for
three reasons:

- Being strict in the (result,state) pair does not for the evaluation of
  either result or state.  Not being strict could only ever be useful
  for a following action that made no use of either state or result, and
  I have a hard time imagining why you'd ever want to write such a
  beast, let alone in monadic style.  In fact, an unboxed tuple would be
  even better.

- Assuming that the State monad is lazy in the tuple, and you need to be
  strict in the state component, you are hosed.  No amount of 'seq' will
  help you.  On the other hand, were it strict and you needed it to be
  lazy, you could achieve that by manually boxing the data involved.

- (=) should also be head strict in the state component.  Again, if
  this is wrong, you can repair it.  If laziness turns out wrong, you
  can't.  Moreover, for most data types that you want to build lazily,
  especially lists, head strictness doesn't make a difference, as long
  as the tail is lazily evaluated.  For data where you need strictness,
  such as integers or tuples of them, having strictness available make
  all the difference.

I'd be fine with laziness being configurable, of course, but if it
isn't, I want strict state.  Come to think of it, it's probably just a
bad idea that _|_ and (_|_,_|_) are different things.


-Udo
-- 
The Seventh Commandments for Technicians:
Work thou not on energized equipment, for if thou dost, thy
fellow workers will surely buy beers for thy widow and console
her in other ways.


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Udo Stenzel
Ross Paterson wrote:
 This (like StateT) gives you strictness in the pair, but doesn't give
 the strictness in the state that the original poster wanted.

I think the OP wanted both.  If State is lazy in the pair, a long chain
of the form (a = (b = (c = ... = z))) gets build up and blows
the stack if it finally turns out that yes, all these steps are needed.
Worse than that, there's no way to correct this without changing the
definition of (=).

Laziness in the state component is annoying at times, but not as bad.
You can recover strictness by writing

put $! x
get = (put $!) . f

instead of

put x
modify f

provided that (=) is already strict in the pair.  (It gets even more
ugly if the state is a Data.Map that needs to be updated strictly, in
which Data.Map.update also doesn't work, even combined with the above
modifications.)


-Udo
-- 
The only problem with seeing too much is that it makes you insane.
-- Phaedrus


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Dan Mead

I think he meant something more along the lines of (or exactly) this, but in
Haskell

http://java.sun.com/docs/books/tutorial/networking/sockets/clientServer.html

I for one would also be interested in reading a tutorial like this using the
ghc libs

-Dan

On 1/11/07, Henning Thielemann [EMAIL PROTECTED] wrote:



On Thu, 11 Jan 2007, John Ky wrote:

 Does anyone know where I can find a simple UDP client/server written in
 Haskell?

There is some support as part of a SuperCollider wrapper:
http://www.slavepianos.org/rd/sw/sw-69/Sound/OpenSoundControl/UDP.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HaskellForge?

2007-01-11 Thread Yitzchak Gale

tphyahoo wrote:

I think people want something like CPAN. This implies a centralized
official repository


I agree.

I think we also need a notion of a canonical
standard package for each popular category.

True, it is sometimes nice to have a lot of alternatives to choose
from. And to be able to specify the resulting package dependencies.

But other times that is not good. If you need to include a certain
functionality in your program, sometimes the most important
factors are that it is least likely to cause package conflicts for the
widest possible audience, or that the widest possible audience will
easily understand how it works, or that it will integrate well
with a wide variety of other services.

In a CPAN-like world that can be very difficult.

-Yitz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HaskellForge?

2007-01-11 Thread Seth Gordon
Yitzchak Gale wrote:
 tphyahoo wrote:
 
 I think people want something like CPAN. This implies a centralized
 official repository
 
 
 I agree.
 
 I think we also need a notion of a canonical
 standard package for each popular category.

For some categories, it might be better to have a canonial standard
*typeclass* and let various packages derive from that class.

Cf. the Python DB-API (http://www.python.org/dev/peps/pep-0249/) and
WSGI (http://www.python.org/dev/peps/pep-0333/).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Can't figure out how to show for type Int - (Int, Int)

2007-01-11 Thread Tom Titchener

Typing up and running (via Hugs) the examples in Wadler's excellent Monads for 
functional programming (here: 
http://homepages.inf.ed.ac.uk/wadler/papers/marktoberdorf/baastad.pdf) I hit 
the inevitable show function error:

ERROR - Cannot find show function for:
*** Expression : eval answer
*** Of type: Int - (Int,Int)

I can find lots of nice text about extending data for show (including the 
miraculous Deriving) but... I'm showing my Haskell newbie roots by utterly 
failing to understand how to do this of a higher-order type (my best guess 
for the right term for the type Int - (Int, Int)).

It'd be a big help if somebody could tell me either:


a)  It's obvious, you moron, just insert Haskell code here

or


b)  It's impossible, you moron, you're trying to violate the insert 
Haskell rule here

Here' my code:

data Term = Con Int | Div Term Term
type M a = State - (a, State) -- higher-order type, e.g. function type
type State = Int -- type synonym
eval :: Term - M Int
eval (Con a) x = (a, x)
eval (Div t u) x = let (a, y) = eval t x in
let (b, z) = eval u y in
(a `div` b, z + 1)
answer, error :: Term
answer = (Div(Div(Con 1972)(Con 2))(Con 23))
error = (Div(Con 1)(Con 0))

I get the ERROR message when I type eval answer at the Hugs prompt.

Thanks!

Tom Titchener

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can't figure out how to show for type Int - (Int, Int)

2007-01-11 Thread Henning Thielemann

On Thu, 11 Jan 2007, Tom Titchener wrote:

 Here' my code:
 
 data Term = Con Int | Div Term Term
 type M a = State - (a, State) -- higher-order type, e.g. function type
 type State = Int -- type synonym
 eval :: Term - M Int
 eval (Con a) x = (a, x)
 eval (Div t u) x = let (a, y) = eval t x in
 let (b, z) = eval u y in
 (a `div` b, z + 1)
 answer, error :: Term
 answer = (Div(Div(Con 1972)(Con 2))(Con 23))
 error = (Div(Con 1)(Con 0))
 
 I get the ERROR message when I type eval answer at the Hugs prompt.

'eval' requires two arguments, the second one is hidden in (M Int) which 
expands to (State - (a, State)). That is, you must call

eval answer 42

or so.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] mapTuple

2007-01-11 Thread Marco Túlio Gontijo e Silva
Hello,

is there a way to defined something as a map to use in tuples? I tried
this:

mapTuple f (a, b) = (f a, f b)

But the type inferred to it is not as generic as I wanted:

mapTuple :: (t - t1) - (t, t) - (t1, t1)

Then I tried a different, but not much, implementation:

mapTuple' f g (a, b) = (f a, g b)
mapTuple f = mapTuple' f f

But the inferred type was the same.

Is there a way to define a function in which I can be able to do
something as this?

mapTuple show (string, True)

-- 
malebria
Marco Túlio Gontijo e Silva
Correio (MSN): [EMAIL PROTECTED]
Jabber (GTalk): [EMAIL PROTECTED]
Telefone: 33346720
Celular: 98116720
Endereço:
  Rua Paula Cândido, 257/201
  Gutierrez 30430-260
  Belo Horizonte/MG Brasil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread minh thu

2007/1/11, Marco Túlio Gontijo e Silva [EMAIL PROTECTED]:

Hello,

is there a way to defined something as a map to use in tuples? I tried
this:

mapTuple f (a, b) = (f a, f b)

But the type inferred to it is not as generic as I wanted:

mapTuple :: (t - t1) - (t, t) - (t1, t1)

Then I tried a different, but not much, implementation:

mapTuple' f g (a, b) = (f a, g b)
mapTuple f = mapTuple' f f

But the inferred type was the same.

Is there a way to define a function in which I can be able to do
something as this?

mapTuple show (string, True)



Hi,

you might want invistigate heterogeneous lists : in your case, it's
heterogeneous typle.
There's a page lying on the wiki I think... It involves typeclasses
and type quantifiers.

Ciao,
minh thu
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread Marco Túlio Gontijo e Silva
Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
 you might want invistigate heterogeneous lists : in your case, it's
 heterogeneous typle.

But aren't tuples always heterogeneous?

Regards.

-- 
malebria
Marco Túlio Gontijo e Silva
Correio (MSN): [EMAIL PROTECTED]
Jabber (GTalk): [EMAIL PROTECTED]
Telefone: 33346720
Celular: 98116720
Endereço:
  Rua Paula Cândido, 257/201
  Gutierrez 30430-260
  Belo Horizonte/MG Brasil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Gregory Wright


Hi John,

On Jan 11, 2007, at 1:58 AM, John Ky wrote:


Hello,

Does anyone know where I can find a simple UDP client/server  
written in Haskell?


Something along the lines of an echo server would do.

Thanks

-John



Try:

--
-- UDPEchoServer.hs: Exactly what the name says, a datagram echo server.
--


module Main (main) where

import Network.Socket
import System.Posix.Directory
import System.Posix.Files
import System.Posix.IO
import System.Posix.Process
import System.Exit


echoPort = 9900
maxline = 1500

--
-- The daemon infrastructure
--

main :: IO ()
main = do
  pid - forkProcess child
  exitImmediately ExitSuccess


child :: IO ()
child = do
  -- Set up the working directory, mask and standard i/o
  -- for a daemon process (these will be inherited by
  -- the forked process):

  changeWorkingDirectory /
  setFileCreationMask 0

  mapM_ closeFd [stdInput, stdOutput, stdError]
  nullFd - openFd /dev/null ReadWrite Nothing  
defaultFileFlags

  mapM_ (dupTo nullFd) [stdInput, stdOutput, stdError]

  closeFd nullFd

  createSession -- This child becomes a process and session
-- group leader. This prevents the child of
-- this process (the daemon) from
-- ever getting a controlling terminal.
  pid' - forkProcess echoserver

  exitImmediately ExitSuccess

--
-- The echo server daemon
--

echoserver :: IO ()
echoserver = do
  withSocketsDo $ do
  sock - socket AF_INET Datagram 0
  bindSocket sock (SockAddrInet echoPort iNADDR_ANY)
  socketEcho sock


socketEcho :: Socket - IO ()
socketEcho sock = do
  (mesg, recv_count, client) - recvFrom sock maxline
  send_count - sendTo sock mesg client
  socketEcho sock



 
---



On my OS X/ppc 10.4.8 system, the above builds with ghc 6.6 and if I  
open one

terminal with

gregory-wrights-powerbook-g4-17 nc -u 127.0.0.1 9900

and another with

gregory-wrights-powerbook-g4-17 nc -ul -p 9900 127.0.0.1

whatever I type into the first terminal appears on the second.  You  
may have to
consult your documentation for the options to your version of nc (or  
netcat,

if you use that instead).

I was also able to see that the server returned packets using hping3.

Needless to say, the above is just an example, and is by no means  
bulletproof.
I think I adapted it from something I found on the old wiki and  
updated it

to work with the current libraries.

Best Wishes,
Greg




 
___

Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread Gregory Wright


Hi John,

On Jan 11, 2007, at 10:35 AM, Gregory Wright wrote:



Hi John,

On Jan 11, 2007, at 1:58 AM, John Ky wrote:


Hello,

Does anyone know where I can find a simple UDP client/server  
written in Haskell?


Something along the lines of an echo server would do.

Thanks

-John



Try:




snip

For testing, you need only use

gregory-wrights-powerbook-g4-17 nc -ul -p 9900 127.0.0.1

and whatever you type should be echoed.  My original description
of how to test:


On my OS X/ppc 10.4.8 system, the above builds with ghc 6.6 and if  
I open one

terminal with

gregory-wrights-powerbook-g4-17 nc -u 127.0.0.1 9900

and another with

gregory-wrights-powerbook-g4-17 nc -ul -p 9900 127.0.0.1

whatever I type into the first terminal appears on the second.  You  
may have to
consult your documentation for the options to your version of nc  
(or netcat,

if you use that instead).


is wrong.  (It will copy from one terminal to the other when the  
daemon is not present.)


Best,
Greg

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread minh thu

2007/1/11, Marco Túlio Gontijo e Silva [EMAIL PROTECTED]:

Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
 you might want invistigate heterogeneous lists : in your case, it's
 heterogeneous typle.

But aren't tuples always heterogeneous?


You're right but the fact you apply a function on both element of the
tuple constrains them to have the same type. Thus the problem is
reminiscent of heterogeneous lists:
how can you make (i.e. wrap) two values of different type so they have
(after being wrapped) the same type ?

I couldnt find the page I was refering but found this one:
http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types
Look at the part on heterogeneous list, the examples are the thing you
want (but for a list, not for a tuple).

Oh two things: 1/ I'm a bad haskell programmers since I have not
enough experience (so maybe I'm throwing you in the bad direction but
I prefer to answer so you not have to wait to long...); 2/ It's a bit
of a habit here to answer with quite involved material even when a
noob asks something (which I don't know if you are or not). Thus maybe
the real answer to your question is wether what you ask for is really
the root of the problem (I can't answer for you).

Another way to do what you want if you just want to use the 'show'
function above on some types (and not every instance of Show) is to
wrap each type individually in a variant type something like this:
data MyShowable = S String | B Bool
myShow :: MyShowable - String

Optionnaly you can then make MyShowable an instance of Show.
This way is much more 'basic level' haskell than the wiki page above.

Cheers,
mt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Using PAPI to measure performance with CPU events

2007-01-11 Thread Alexey Rodriguez Yakushev

Dear all,

I have added a page to the GHC commentary explaining how to use the  
PAPI library together with GHC to gather performance information from  
your CPU (cache misses, branch misprediction). At present only cache  
miss information is supported in a platform independent way (though  
not tested). Also, this implementation separates the performance  
information for the garbage collector and the mutator so it is quite  
useful if you are implementing an optimisation.


The page also has some patches to use PAPI on the nofib suite. These  
patches are eventually going to make it into the HEAD, but I thought  
someone might find them useful meanwhile.


Cheers,

Alexey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: State monad strictness - how?

2007-01-11 Thread apfelmus
 Unfortunately, the current situation is that State is only
 available as a lazy monad, and StateT is only available
 as a strict monad.

 I agree with you that both lazy and strict monads are important and
 that we should have both options in a monad library.
 
 But the fun doesn't end there. There are other strictness properties
 to consider. Take the state monad for example. Should it be strict or
 lazy in the state that it carries around? What about the value
 component? I think the answer to these questions are the same as for
 monadic strictness above: both strict and lazy variants are useful. 

Sorry guys, but it looks like there are monstrous misconceptions of
strictness: there is no such thing as a strict or a lazy monad.
There are only functions strict in arguments and thus one can only ask
in which arguments (=) is strict or how the strictness properties of
the result (x = y) are obtained from those of x and y. As it turns
out, the details are subtle.


Let's make an attempt to define strict in the state. One might say
that this refers to a monad (SState s a) with the property that for all
(x :: State s a), the semantic function (runState x :: s - (a,s)) is
strict, i.e.

runState x _|_ = _|_

Thus, (x) evaluates the state to WHNF (weak head normal form) before it
returns a result. Note that this definition strict in the state
*cannot* be applied to an arbitrary instance (m) of the class
(MonadState) because the class does not offer any hints about the
semantic function (runState). One cannot state this property in terms of
(put),(get),(return) and (=) alone.

The current implementation of (Control.Monad.State.State s a) is not
strict in the state. Here, we have for example

modify f = get = put . f

runState (modify (+1)) _|_
  = ((\s - (s,s)) = (\n - \s - ((),n+1))) _|_
  = ((),_|_+1)
  = ((),_|_)

which returns the value () but gives an undefined state. This is also
the source of Dean's space leak (and stack overflow). Performing graph
reduction to WHNF on

  flip runState undefined . sequence_ . replicate 100 $ modify (+1)

yields the pair

  ((), (... (((undefined + 1) + 1) + 1) ... + 1))

Clearly, the second component needs much memory to hold the 100
numbers. Evaluating it to WHNF form will result in a stack
overflow even before (undefined) raises an exception. But the first
component is simply ().


So far, so good. An implementation of strict in the state would be

newtype SState s a = S { runSState :: s - (a,s) }

instance Monad (SState s) where
return a = S $ \s - s `seq` (a, s)
m = k  = S $ \s - let
(a, s') = runSState m s
in runSState (k a) s'

instance MonadState s (SState s) where
get = \s - s `seq` (s,s)
put s = \s' - s' `seq` ((),s)

We assume that the constructor (S) is hidden to the user so that he can
only build monadic actions from (return), (=), (get) and (put). Note
that the (=) operation does not mention strictness at all. Given our
assumption, we know by induction that (m) and (k a) are strict in the
state and it follows that (=) must be strict in the state, too. A
quick check confirms

   runSState (modify (+1)) _|_ = _|_

Marvelous, let's try

 flip runSState undefined . sequence_ . replicate 100 $ modify (+1)
 *** Exception: stack overflow

What happened? It's a very good exercise to perform graph reduction by
hand on this expression to see what's going on. For simplicity, you may
want to get your hands dirty on

modify (+1)  modify (+1)  modify (+1)  return ()

The result is in essence a concatenation of strict functions like in

f = (+1) . (+1) . (+1) . (+1) ... (+1)

While the entire function (f) is strict as well, the intermediate
results are not evaluated eagerly enough, resulting in a stack overflow.

A concatenation of strict functions is amenable to strictness analysis.
So, I strongly suspect that Dean's

   tick' = get = (put $!) . (+1)

will yield a favorable result with optimization turned on -O. But a
priori, the problem must be remedied by changing the definition of (=)
to force the intermediate accumulating parameter, like in

m = k  = S $ \s - s `seq` let
 (a, s') = runSState m s
 in runSState (k a) $! s'

The point is that the previous definition of (=) could also be used to
combine monadic action not strict in the state and must perform lazy
evaluation to achieve the non-strict semantics in that case, too. In
contrast, this definition of (m = k) will always return a monadic
action strict in the state, regardless of the strictness of (m) and (k).

Accidentally, the definition of (=) for (StateT) forces the pair
constructor:

instance (Monad m) = Monad (StateT s m) where
return a = StateT $ \s - return (a, s)
m = k  = StateT $ \s - do
(a, s') - runStateT m s
runStateT (k a) s'

In case (m) and (k) are strict in the state, this will force the
intermediate state (s) and Dean's (tick' :: 

[Haskell-cafe] Re: Using PAPI to measure performance with CPU events

2007-01-11 Thread Alexey Rodriguez Yakushev

The URL might be useful to some :)

http://hackage.haskell.org/trac/ghc/wiki/PAPI


On Jan 11, 2007, at 17:10, Alexey Rodriguez Yakushev wrote:


Dear all,

I have added a page to the GHC commentary explaining how to use the  
PAPI library together with GHC to gather performance information  
from your CPU (cache misses, branch misprediction). At present only  
cache miss information is supported in a platform independent way  
(though not tested). Also, this implementation separates the  
performance information for the garbage collector and the mutator  
so it is quite useful if you are implementing an optimisation.


The page also has some patches to use PAPI on the nofib suite.  
These patches are eventually going to make it into the HEAD, but I  
thought someone might find them useful meanwhile.


Cheers,

Alexey


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread Arthur van Leeuwen


On 11-jan-2007, at 16:30, Marco Túlio Gontijo e Silva wrote:


Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:

you might want invistigate heterogeneous lists : in your case, it's
heterogeneous typle.


But aren't tuples always heterogeneous?


Yes, and precisely therein lies the problem. There is no way
for the compiler to infer that in

tupleMap f (a, b) = (f a, f b)

the type of f should be polymorphic. If you want it to be,
explicitly require it to be so:

tupleMap :: (forall a b . a - b) - (b,c) - (d,e)
tupleMap f (a,b) = (f a, f b)

However, this will still not allow you to write

tupleMap show (string,3)

as you require f to be fully polymorphic, and not constrained by any
context.

With regards, Arthur.

--  

  /\/ |   [EMAIL PROTECTED]   | Work like you don't need  
the money
/__\  /  | A friend is someone with whom | Love like you have never  
been hurt
/\/__ | you can dare to be yourself   | Dance like there's nobody  
watching




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread David House

On 11/01/07, Marco Túlio Gontijo e Silva [EMAIL PROTECTED] wrote:

is there a way to defined something as a map to use in tuples? I tried
this:

mapTuple f (a, b) = (f a, f b)

But the type inferred to it is not as generic as I wanted:

mapTuple :: (t - t1) - (t, t) - (t1, t1)


Let's think about what type we might want to give this. Here's a first attempt:

mapTuple :: (a - c) - (a, b) - (c, d)
mapTuple f (x, y) = (f x, f y)

But this won't typecheck, because we can only apply the function to
the first element in the tuple from the type that we have. In other
words, we don't know that we can pass values of type b into f. We
could say:

mapTuple :: (a - c) - (a, a) - (c, c)

But this isn't as polymorphic as you'd like. An alternative is sum types:

mapTuple :: (Either a b - c) - (a, b) - (c, c)
mapTuple f (x, y) = (f $ Left x, f $ Right y)

Note that we can't do:

mapTuple :: (Either a b - Either c d) - (a, b) - (c, d)

Because we don't know that feeding a value of type c into f will yield
a value of type d; f (Left x) might return a Right-tagged value. We
could perhaps do this:

mapTuple :: (Either a b - (c, d)) - (a, b) - (c, d)
mapTuple f (x, y) = (fst $ f $ Left x, snd $ f $ Right y)

And a function would then return both a value of type c and d
(possibly one of them being undefined). However, it doesn't really
seem satisfactory to impose this constraint on our arguments. Instead,
it seems we want to supply two functions:

mapTuple :: (a - b) - (c - d) - (a, b) - (c, d)

And this appears now as a the classic f × g operation over pairs,
implemented as (***) in Control.Arrow:

(***) :: (a - b) - (c - d) - (a, b) - (c, d)
(f *** g) (x, y) = (f x, g y)

(Actually the original is a little lazier, using irrefutable patterns
on the pair.) Then you can do:

(show *** show) (string, True)

And I suspect that's the best you'll get. There may be a wild solution
involving typeclasses and existentials, but this doesn't seem
altogether too bad.

--
-David House, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple

2007-01-11 Thread Marco Túlio Gontijo e Silva
Em Qui, 2007-01-11 às 16:51 +0100, minh thu escreveu: 
 2007/1/11, Marco Túlio Gontijo e Silva [EMAIL PROTECTED]:
  Em Qui, 2007-01-11 às 16:14 +0100, minh thu escreveu:
   you might want invistigate heterogeneous lists : in your case, it's
   heterogeneous typle.
 
  But aren't tuples always heterogeneous?
 
 You're right but the fact you apply a function on both element of the
 tuple constrains them to have the same type. Thus the problem is
 reminiscent of heterogeneous lists:
 how can you make (i.e. wrap) two values of different type so they have
 (after being wrapped) the same type ?
 
 I couldnt find the page I was refering but found this one:
 http://en.wikibooks.org/wiki/Haskell/Existentially_quantified_types
 Look at the part on heterogeneous list, the examples are the thing you
 want (but for a list, not for a tuple).
 
 Oh two things: 1/ I'm a bad haskell programmers since I have not
 enough experience (so maybe I'm throwing you in the bad direction but
 I prefer to answer so you not have to wait to long...); 2/ It's a bit
 of a habit here to answer with quite involved material even when a
 noob asks something (which I don't know if you are or not). Thus maybe
 the real answer to your question is wether what you ask for is really
 the root of the problem (I can't answer for you).
 
 Another way to do what you want if you just want to use the 'show'
 function above on some types (and not every instance of Show) is to
 wrap each type individually in a variant type something like this:
 data MyShowable = S String | B Bool
 myShow :: MyShowable - String
 
 Optionnaly you can then make MyShowable an instance of Show.
 This way is much more 'basic level' haskell than the wiki page above.

Thanks for your answers.

I found the page of heterogeneous collections in haskell wiki:

http://haskell.org/haskellwiki/Heterogenous_collections

But my point was trying to do this without having to convert it to a
homogeneous tuple by using Dynamic.

I read a little of the wiki page, and it gave me some ideas:

(with ghci -fglasgow-exts)
let mapTuple :: forall c d e f. (forall a b. a - b) - (c, d) - (e,
f); mapTuple f (x, y) = (f x, f y)

works fine, but when I run:

Prelude mapTuple show (string, True)

interactive:1:9:
Couldn't match expected type `b' (a rigid variable)
   against inferred type `String'
  `b' is bound by the polymorphic type `forall a b. a - b'
at interactive:1:0-29
In the first argument of `mapTuple', namely `show'
In the expression: mapTuple show (string, True)
In the definition of `it': it = mapTuple show (string, True)
Prelude

And:

Prelude mapTuple head ([string], [True])

interactive:1:9:
Couldn't match expected type `a' (a rigid variable)
   against inferred type `[a1]'
  `a' is bound by the polymorphic type `forall a b. a - b'
at interactive:1:0-33
  Expected type: a - b
  Inferred type: [a1] - a1
In the first argument of `mapTuple', namely `head'
In the expression: mapTuple head ([string], [True])
Prelude

This seemed to work:

Prelude mapTuple (const undefined) (string, True)
(*** Exception: Prelude.undefined
Prelude

The problem is it only works with forall a b. a - b functions. I tried
with exits, but I got an error:

Prelude let mapTuple :: forall c d e f. (exists a b. a - b) - (c, d)
- (e, f); mapTuple f (x, y) = (f x, f y)
interactive:1:43: parse error on input `.'
Prelude

Thanks for any help.

-- 
malebria
Marco Túlio Gontijo e Silva
Correio (MSN): [EMAIL PROTECTED]
Jabber (GTalk): [EMAIL PROTECTED]
Telefone: 33346720
Celular: 98116720
Endereço:
  Rua Paula Cândido, 257/201
  Gutierrez 30430-260
  Belo Horizonte/MG Brasil

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread Josef Svenningsson

On 1/11/07, Yitzchak Gale [EMAIL PROTECTED] wrote:

Josef Svenningsson wrote:
 Take the state monad for example. Should it be
 strict or lazy in the state that it carries
 around? What about the value component?
 ...both strict and lazy variants are useful.

I wrote:
 Are those really needed?

 ...it wouldn't be very convenient, would it?
 Sometimes I find that I want strict state by
 default and then I don't want to sprinkle my
 code with seqs.

I don't think that is so inconvenient. Why do we
need to define getStrict, putStrict, getsStrict,
etc., when it is perhaps even more clear to write
get $!, put $!., (gets . ($!)), etc.?.

The same goes for Iavor's monad library.


Indeed. I'm embarrassed that I've never realized this before. I
suppose I though the tuple solution was so elegant that I never
realized there was a simpler solution at hand.


 Now, the challenge here is to design a library
 which doesn't explode in size from all the
 various possibilities for strictness or
 laziness.

I am now pretty convinced that the only thing we
need is two versions of each monad, varying only
the strictness of =.

Then, of course, we will need runFoo for each, and
evalFoo and execFoo for each state monad.

And adaptors that allow you to run a lazy
calculation inside a strict one and vice-versa. So
we need an asStrict function and an asLazy
function for each lazy/strict pair of monads.

I think that is all we need. Not too bad.

I am very impressed that we get most of that
almost for free in Iavor's library.


Yes, it seems quite feasible.


 http://www.cs.chalmers.se/~josefs/monadlib/
 ...instantiating this with different pair types
 with different strictness properties will give
 us total control over strictness for state and
 value.

Hmm. Your current implementation doesn't seem to
do it that way. You use tuples for both the lazy
version and the strict version, and each defines
its own Monad instance for all Pair types. So it
is impossible to use both in the same module, even
with hiding.


The way I enable laziness in a strict monad and vice versa is to use a
non-standard bind operator, strictBind or lazyBind. But that's not
really scalable. The whole architecture that I used in my library
isn't really all that good. The reason I came up with it was to solve
a completely different problem which doesn't really apply to this
library anyway. The library design you outline above is indeed the way
to go.


I tried to work on this a little. I defined a
strict Pair type and tried to find a single Monad
instance that will give the right strictness for
both if you just vary between lazy and strict
pairs.

We need that both of the following converge
in constant stack space:

take 100 $ evalState (repeatM $ modify (+1)) 0
execStateStrict (replicateM_ 10 $ modify (+1)) 0

(You can verify that this is true if you use the
standard evalState, and replace execStateStrict
with runIdentity . execStateT.)

I was unable to hit upon the right combination of
seqs in the Monad instance. Is it really possible?

Of course, you could use a newtype of tuples and
define separate Monad instances. But then we are
not gaining anything over just defining the lazy
and strict monads directly.


I'm not sure exactly what you're trying to achieve here. If the tuple
type you have is strict in both components then you're never going to
get these examples to work. However, if you choose the lazy state
monad and choose tuples carefully then both example can be made to
terminate. Here's an example:
ex1 = take 100 $ evalState
 ((repeatM $ modify (+1))::StateP StrictLeft Int [()])
 0
ex2 = execStateStrict
 ((replicateM_ 10 $ modify (+1)) :: StateTP StrictLeft Int Identity ())
 0

The first example also terminates with the all lazy pair (,), the
importance is the laziness of the right component.

Cheers,

Josef
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] an advanced foldification problem

2007-01-11 Thread Seth Gordon
I have a data type Group, representing a group of geographic
information that is all referring to the same location, and a function
mergeGroups that tries to merge two groups:

mergeGroups :: Group - Group - Maybe Group

Then I have a function mergeGroupToList that tries to merge its first
argument with every element of the second argument:

mergeGroupToList :: Group - [Group] - [Group]
mergeGroupToList g [] = [g]
mergeGroupToList g1 (g2:gs) =
case (mergeGroups g1 g2) of
Nothing - g2 : (mergeGroupToList g1 gs)
Just g3 - mergeGroupToList g3 gs

How can I rewrite mergeGroupToList in terms of foldr?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some way to reverse engineer lambda expressions out of the debugger?

2007-01-11 Thread Malcolm Wallace
Bulat Ziganshin [EMAIL PROTECTED] wrote:

 tphyahoo wrote:
 
  *UnixTools explodeLambda( map (*) [1,2] )
 [(\x - 1*x),(\x - 2*x)]

Have a play with this, from Claus Reinke:
http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/R.hs


Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] an advanced foldification problem

2007-01-11 Thread Henning Thielemann

On Thu, 11 Jan 2007, Seth Gordon wrote:

 I have a data type Group, representing a group of geographic
 information that is all referring to the same location, and a function
 mergeGroups that tries to merge two groups:
 
 mergeGroups :: Group - Group - Maybe Group
 
 Then I have a function mergeGroupToList that tries to merge its first
 argument with every element of the second argument:
 
 mergeGroupToList :: Group - [Group] - [Group]
 mergeGroupToList g [] = [g]
 mergeGroupToList g1 (g2:gs) =
 case (mergeGroups g1 g2) of
 Nothing - g2 : (mergeGroupToList g1 gs)
 Just g3 - mergeGroupToList g3 gs

Is mapAccumL also allowed?

Untested but type-checked:

mergeGroupToList g0 gs =
  let (mergedG, unmergedGs) =
 mapAccumL (\g1 g - maybe (g1, Just g) (\g3 - (g3, Nothing)) 
(mergeGroups g1 g)) g0 gs
  in  catMaybes unmergedGs ++ [mergedG]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some way to reverse engineer lambda expressions out of the debugger?

2007-01-11 Thread Thomas Hartman

Looks very nice!

However, I'm doing my learning on ghci and got an error when I tried to load it.

Is this hugs only, or should I try harder?

2007/1/11, Malcolm Wallace [EMAIL PROTECTED]:

Bulat Ziganshin [EMAIL PROTECTED] wrote:

 tphyahoo wrote:

  *UnixTools explodeLambda( map (*) [1,2] )
 [(\x - 1*x),(\x - 2*x)]

Have a play with this, from Claus Reinke:
http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/R.hs


Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] some way to reverse engineer lambda expressionsout of the debugger?

2007-01-11 Thread Claus Reinke

Looks very nice!


thanks!-) 


it is far from a full-blown solution to the question in the subject, but it has 
its uses.


However, I'm doing my learning on ghci and got an error when I tried to load it.

Is this hugs only, or should I try harder?


I was using Hugs when I wrote that, but it works in GHC almost as well. the
error message really ought to point to the option needed, which is 
-fglasgow-exts

if you don't want to set the options by hand, just add the following pragma to 
the top of R.hs:


{-# OPTIONS_GHC -fglasgow-exts #-}

more annoying is that ghci will ignore the default directive, so you'll need to
give explicit types when you want representations:

   *Main foldr (+) 0 [1..4]
   10
   *Main foldr (+) 0 [1..4] :: R Int
   (1 + (2 + (3 + (4 + 0
   *Main map (*) [1,2]

   interactive:1:0:
   No instance for (Show (t - t))
 arising from use of `print' at interactive:1:0-12
   Possible fix: add an instance declaration for (Show (t - t))
   In the call (print it)
   In the expression: print it
   In a 'do' expression: print it
   *Main map (*) [1,2] :: [R Int - R Int]
   [\x-(1 * x),\x-(2 * x)]

claus


2007/1/11, Malcolm Wallace [EMAIL PROTECTED]:

Bulat Ziganshin [EMAIL PROTECTED] wrote:

 tphyahoo wrote:

  *UnixTools explodeLambda( map (*) [1,2] )
 [(\x - 1*x),(\x - 2*x)]

Have a play with this, from Claus Reinke:
http://www.cs.kent.ac.uk/people/staff/cr3/toolbox/haskell/R.hs


Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Resending: [Haskell-cafe] MissingH: profiler support?

2007-01-11 Thread Chris Eidhof

Hey,

does anyone know about this? Resending as I got no replies (yet) ;)

Thanks,
-chris

On 8 Jan, 2007, at 23:13 , Chris Eidhof wrote:


Hey all,

I'm trying to profile my application, which makes use of MissingH.  
But when compiling with -prof -auto-all, I get the following error:



Language.hs:8:7:
Could not find module `Data.String':
  Perhaps you haven't installed the profiling libraries for  
package MissingH-0.18.0?

  Use -v to see a list of the files searched for.


When compiling without those options, everything works just fine. I  
built missingh from source, and added -prof -auto-all to GHCPARMS,  
and did a ./setup configure,make,install and still no result. Does  
anyone know what could be wrong? I'd really like to keep using  
MissingH and having profiling support at the same time.


Thanks,
-chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] building hare on ghc-6.6

2007-01-11 Thread Yang

how do i build hare on ghc-6.6? after removing all references to
package lang from myghc--make, i get:

RefacUtils.hs:54:5: parse error on input `HasModName'

this just seems like a normal class being exported.

the makefile proceeds past this to build a bunch of other files fine.
if i ignore this and try loading the emacs file and entering
haskell-refac-mode on a .hs buffer i get:

Can't exec program: /home/yang/tmp/pkg/pure/todo/HaRe_20012006/refactorer/pfe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] an advanced foldification problem

2007-01-11 Thread Spencer Janssen

Take this obscure function:
\begin{code}
func :: (a - a - Maybe a) - a - [a] - [a]
func f s0 xs0 = foldr (\x xs s - maybe (xs s) ((x:) . xs) (f s x))  
return xs0 s0

\end{code}

And mergeGroupToList becomes:
\begin{code}
mergeGroupToList g xs = func mergeGroups g xs
\end{code}


Cheers,
Spencer Janssen

On Jan 11, 2007, at 11:37 AM, Seth Gordon wrote:

I have a data type Group, representing a group of geographic
information that is all referring to the same location, and a function
mergeGroups that tries to merge two groups:

mergeGroups :: Group - Group - Maybe Group

Then I have a function mergeGroupToList that tries to merge its  
first

argument with every element of the second argument:

mergeGroupToList :: Group - [Group] - [Group]
mergeGroupToList g [] = [g]
mergeGroupToList g1 (g2:gs) =
case (mergeGroups g1 g2) of
Nothing - g2 : (mergeGroupToList g1 gs)
Just g3 - mergeGroupToList g3 gs

How can I rewrite mergeGroupToList in terms of foldr?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapTuple (intersection types?)

2007-01-11 Thread Greg Buchholz
Udo Stenzel wrote:
 Marco T?lio Gontijo e Silva wrote:
  is there a way to defined something as a map to use in tuples? I tried
  this:
  
  mapTuple f (a, b) = (f a, f b)
  
  But the type inferred to it is not as generic as I wanted:
  
  mapTuple :: (t - t1) - (t, t) - (t1, t1)
 
 What you seem to want to do is impossible.  Just want type would you
 want to assign to mapTuple?  I bet you can't even express that in
 natural language, no wonder it's impossible in Haskell.

Maybe some of the type experts could pipe up, but couldn't you 
express that as an intersection type?  

mapTuple :: ((a - b) ^ (c - d)) - (a,c) - (b,d)


http://www.cs.cmu.edu/~rwh/theses/pierce.pdf

Greg Buchholz

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Monad Set via GADT

2007-01-11 Thread Benjamin Franksen
Jim Apple wrote:
 On 1/3/07, Roberto Zunino [EMAIL PROTECTED] wrote:
 1) Why the first version did not typececk?
 1) Class constraints can't be used on pattern matching. They ARE
 restrictive on construction, however. This is arguably bug in the
 Haskell standard. It is fixed in GHC HEAD for datatypes declared in
 the GADT way, so as not to break H98 code:

http://article.gmane.org/gmane.comp.lang.haskell.cvs.all/29458/match=gadt+class+context

To quote from there: I think this is stupid, but it's what H98 says.

Maybe it is time to consider it deprecated to follow the Haskell 98
standard /to the letter/. The above is an example where the default
(without flags) should (arguably) be the 'fixed' standard. We would need an
equivalent of gcc's -pedantic flag, meaning Follow the Haskell 98 standard
to the letter, even on issues where the standard is generally considered
bad.

I hope this will be handled in a better way with Haskell'. It should be
possible to revise the standard (every few years or so, /very/
conservatively i.e. no extensions, etc) so that we can eliminate 'bugs'
from the language spec.

Cheers
Ben

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] advice on architecting a library (and haskell software in general)

2007-01-11 Thread Yang

hi all, i'm looking for advice on how to architect a simple widget
library for vty/hscurses, but these beginner-level questions should
apply to haskell applications in general. input/requests on any aspect
of my design would be greatly appreciated - in return perhaps you'll
get something you'd actually want to use!

i have studied in detail various haskell curses/vty apps, including
yi, hmp3, riot, and hscurses.widgets/contactmanager. my immediate goal
is to produce a set of composable widgets and a flexible framework
that - as much as possible - reduces the amount of code a user has to
write. my eventual goal is to make a functional gui library, along the
lines of fruit/wxfruit/fg. to this end i've also read their
literature, but i still do not understand enough about
arrows/yampa/afrp.

i currently have a tree of widgets, some of which can receive focus.
this allows them to alter the program's key handling, but in a certain
order based on the hierarchy. e.g., in my program, at the top-level,
hitting either 'q' or 'f12' quits the program. when we focus on a
container, pressing 'tab' will cycle focus among the subwidgets. when
we focus on a text box, the key bindings layer, so that 'q' inserts a
character into the text box, and 'f12' still exits and 'tab' still
cycles focus.

here's a simplified synopsis of the types (omits details like layout):

class Widget w where output :: Bool {- whether we have focus -} - w - Output
data Output = Output Image (Maybe CursorPos) KeyHandler
type Image = [[(Char,Attr)]] -- Attr is just the text decoration (colors)
type CursorPos = (Int,Int)
type KeyHandler = ???

i'm guessing the most flexible type for KeyHandler could be Key - IO
(), but is this really the only/best approach? (every time i fall back
to IO, i feel i'm missing something/a puppy dies/etc.)

currently, this is what i have:

type KeyHandler = Key - AppState - AppState -- maps to a state updater
data AppState = AppState { rootWidget :: Widget, actualAppState :: ..., ... }

but this has a number of apparent issues, including:

- no decoupling of UI and app - that is, the key handlers that the
widgets return have complete knowledge of the application state. so
for instance, this particular text box knows that its key handler
should be:

handler key state =
 let oldPos = cursorPos $ someTextBox $ rootWidget $ state
 in case key of
  Left - state { rootWidget { someTextBox { cursorPos = oldPos - 1 } } }
  ...

- on key press, can't save to a file or otherwise do anything in IO.

- this isn't going to scale - as my AppState grows and grows, we're
throwing away and reconstructing a lot of state. and the coding style
it demands is pretty clumsy, as demonstrated above.

but if we switch to IO ():

- still doesn't help decouple the library from the app. the above
example key handling code snippet would be the same (i.e. still very
clumsy), except that we'd be reading/writing the state from/to an
IORef or MVar.

- certainly, not all actions need IO. in fact, my current application
is just a viewer, and thus needs no IO at all.

- requires a global IORef or MVar

- i don't know how to address the performance problem without
resorting to sprinkling IORefs or MVars everywhere in the state
structure, thus strangling the app into IO everywhere

other open questions:

- how should the top-most code work? currently, my app's main has a
tiny event loop that feeds keys through a Chan to a State-ful function
([Key] - State AppState [Image]) and then to the final drawing
function ([Image] - IO ()). however, depending on the resolutions to
the above issues, this may radically change.

- how should i compose the various key handlers? this, again, will depend.

related work:

yi/hmp3 also have one large piece of state in a global mvar (allows
multiple threads to update it/trigger a redraw, instead of only
redrawing in response to key events), with no attempt to decouple the
UI and app parts of that state. event handling is done by a lexer that
matches regex key patterns to IO () - this doesn't couple key handling
with the UI components, and is thus not composable. (i thought the
idea of using a lexer as the state automata was good - there may be
some way to make this more composable, too, if the regex ever fails.)

riot's UI code operates mostly in StateT Riot IO (), where Riot is
again a monolithic application state. again, no attempt at decoupling
or composability is made. hscurses.widgets operates mostly in IO (),
and 'activating' (focusing) on widgets hands over the event loop
completely.



i hope i explained my design problems clearly. i've used haskell a
bunch for various small text-processing scripts, but decided to try to
use it for a real application that has little to do with parsing or
other purported strengths of the language. i believe other new
haskellers may relate to some of these issues.

thanks!

yang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org

Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread John Ky

Hi,

What's wrong with my UDP client?

echoClient :: IO ()
echoClient = withSocketsDo $ do
   putStrLn [a]
   sock - socket AF_INET Datagram 0
   putStrLn [b]
   connect sock (SockAddrInet 9900 iNADDR_ANY)
   putStrLn [c]
   n - send sock hi
   putStrLn [d]
   return ()

I get:

*Main echoClient
[a]
[b]
*** Exception: connect: failed (Cannot assign requested address
(WSAEADDRNOTAVAI
L))

Thanks

-John


On 1/12/07, Gregory Wright [EMAIL PROTECTED] wrote:



Hi John,

On Jan 11, 2007, at 10:35 AM, Gregory Wright wrote:


 Hi John,

 On Jan 11, 2007, at 1:58 AM, John Ky wrote:

 Hello,

 Does anyone know where I can find a simple UDP client/server
 written in Haskell?

 Something along the lines of an echo server would do.

 Thanks

 -John


 Try:



snip

For testing, you need only use

gregory-wrights-powerbook-g4-17 nc -ul -p 9900 127.0.0.1

and whatever you type should be echoed.  My original description
of how to test:

 On my OS X/ppc 10.4.8 system, the above builds with ghc 6.6 and if
 I open one
 terminal with

 gregory-wrights-powerbook-g4-17 nc -u 127.0.0.1 9900

 and another with

 gregory-wrights-powerbook-g4-17 nc -ul -p 9900 127.0.0.1

 whatever I type into the first terminal appears on the second.  You
 may have to
 consult your documentation for the options to your version of nc
 (or netcat,
 if you use that instead).

is wrong.  (It will copy from one terminal to the other when the
daemon is not present.)

Best,
Greg


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MissingH: profiler support?

2007-01-11 Thread Spencer Janssen
The typical way to add profiling support to a Cabal lib is to add -p  
at configure time (ie runhaskell Setup.hs configure -p).  Have you  
tried this?



Cheers,
Spencer Janssen

On Jan 8, 2007, at 4:13 PM, Chris Eidhof wrote:


Hey all,

I'm trying to profile my application, which makes use of MissingH.  
But when compiling with -prof -auto-all, I get the following error:



Language.hs:8:7:
Could not find module `Data.String':
  Perhaps you haven't installed the profiling libraries for  
package MissingH-0.18.0?

  Use -v to see a list of the files searched for.


When compiling without those options, everything works just fine. I  
built missingh from source, and added -prof -auto-all to GHCPARMS,  
and did a ./setup configure,make,install and still no result. Does  
anyone know what could be wrong? I'd really like to keep using  
MissingH and having profiling support at the same time.


Thanks,
-chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] State monad strictness - how?

2007-01-11 Thread John Meacham
incidentally, I made a very strict and unboxed version of the RWS monad,
since it is a darn useful one in jhc. right now, it only implements the
things I needed, but it might be useful to include somewhere common and
expanded on

http://repetae.net/dw/darcsweb.cgi?r=jhc;a=headblob;f=/Util/RWS.hs

John
-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] MapTuple is possible and easy

2007-01-11 Thread oleg

Marco Tu'lio Gontijo e Silva wrote:
 is there a way to defined something as a map to use in tuples?

Yes, it is: and it is quite easy and straightforward.

Udo Stenzel
 since c would be a variable that ranges over type classes, and that
 doesn't exist.

Of course it does: please see below (as well as several earlier posts
on the Haskell list showing that Haskell classes *are* first-class).

Here's the definition of mapTuple

 mapTuple l (x,y) = (apply l x, apply l y)

and here its inferred type:

 *MapTuple :t mapTuple
 mapTuple :: (Apply l b y1, Apply l a y) = l - (a, b) - (y, y1)

Our mapTuple applies to (in general) heterogeneous tuples and gives
(in general) a heterogeneous tuple.

Here's the complete code and the tests.

{-# OPTIONS -fglasgow-exts #-}

module MapTuple where


class Apply l x y | l x - y where
  apply:: l - x - y

data SHow = SHow

instance Apply SHow String String where
apply _ = show

instance Apply SHow Int String where
apply _ = show

instance Apply SHow Bool String where
apply _ = show

mapTuple l (x,y) = (apply l x, apply l y)

-- Here, the result is a homogeneous tuple
test1 = mapTuple SHow (a,(1::Int))
test2 = mapTuple SHow ((1::Int),b)
test3 = mapTuple SHow (True,b)

-- ANother operation: SUcc

data SUcc = SUcc

instance Apply SUcc String String where
apply _ x = x ++ x


instance Apply SUcc Int Int where
apply _ = succ


instance Apply SUcc Bool Bool where
apply _ = not


-- Here, the result is a heterogeneous tuple (as is the argument)
testH1 = mapTuple SUcc (a,(1::Int))
testH2 = mapTuple SUcc ((1::Int),b)
testH3 = mapTuple SUcc (True,b)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] UDP client/server

2007-01-11 Thread John Ky

Nevermind,

I just got the client to work:

echoClient :: IO ()
echoClient = withSocketsDo $ do
   sock - socket AF_INET Datagram 0
   n - sendTo sock hi (SockAddrInet echoPort 0x0107f)
   return ()

Thanks everyone for your help.

-John

On 1/12/07, John Ky [EMAIL PROTECTED]  wrote:Hi,

What's wrong with my UDP client?

echoClient :: IO ()
echoClient = withSocketsDo $ do
   putStrLn [a]
   sock - socket AF_INET Datagram 0
   putStrLn [b]
   connect sock (SockAddrInet 9900 iNADDR_ANY)
   putStrLn [c]
   n - send sock hi
   putStrLn [d]
   return ()

I get:

*Main echoClient
[a]
[b]
*** Exception: connect: failed (Cannot assign requested address
(WSAEADDRNOTAVAI
L))

Thanks

-John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] CTRL+C in ghci.exe

2007-01-11 Thread John Ky

Hi,

Is it possible to use CTRL+C or equivalent to interrupt a computation or I/O
and return to the ghci prompt?

Thanks

-John
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CTRL+C in ghci.exey

2007-01-11 Thread Stefan O'Rear
On Fri, Jan 12, 2007 at 05:07:04PM +1100, John Ky wrote:
 Hi,
 
 Is it possible to use CTRL+C or equivalent to interrupt a computation or I/O
 and return to the ghci prompt?

Yes.

[EMAIL PROTECTED]:~/lb-sorear$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
 / /_\// /_/ / /  | |  GHC Interactive, version 6.7, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude [0..]
[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,
32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,
61,62,63,64,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,
90,91,92,93,94,95,96,97,98,99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,1
14,115,116,117,118,119,120,121,122,123,124,125,126,127,128,129,130,131,132,133,134,135,
136,137,138,139,140,141,142,143,144,145,146,147,148,149,150,151,152,153,154,155,156,157
,158,159,160,161,162,163,164,165,166,167,168,169,170,171,172,173,174,175,176,177,178,17
9,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,200,2
01,202,203,204,205,206,207,208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,
223,224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244
,245,246,247,248,249,250,251,252,253,254,255,256,257,258,259,260,261,262,263,264,265,26
6,267,268,269,270,271,272,273,274,275,276,277,278,279,280,281,282,283,284,285,286,287,2
88,289,290,291,292,293,294,295,296,297,298,299,300,301,302,303,304,305,306,307,308,309,
310,311,312,313,314,315,316,317,318,319,320,321,322,323,324,325,326,327,328,329,330,331
,332,333,334,335,336,337,338,339,340,341,342,343,344,345,346,347,348,349,350,351,352,35
3,354,355,356,357,358,35Interrupted.
Prelude
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] CTRL+C in ghci.exey

2007-01-11 Thread John Ky

Hi Stefan,

It doesn't work for me.  I'm running GHC 6.6 on Windows XP.  The computation
stops, but I don't get my prompt back.

C:\ghci
  ___ ___ _
 / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.6, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude [1..]
[1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,3
0,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,
57,58,59,60,61,62,63,64,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83
,84,85,86,87,88,89,90,91,92,93,94,95,96,97,98,99,100,101,102,103,104,105,106,107
,108,109,110,111,112,113,114,115,116,117,118,119,120,121,122,123,124,125,126,127
,128,129,130,131,132,133,134,135,136,137,138,139,140,141,142,143,144,145,146,147
,148,149,150,151,152,153,154,155,156,157,158,159,160,161,162,163,164,165,166,167
,168,169,170,171,172,173,174,175,176,177,178,179,180,181,182,183,184,185,186,187
,188,189,190,191,192,193,194,195,196,197,198,199,200,201,202,203,204,205,206,207
,208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,223,224,225,226,227
,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244,245,246,247
,248,249,250,251,252,253,254,255,256,257,258,259,260,261,262,263,264,265,266,267
,268,269,270,271,272,273,274,275,276,277,278,279,280,281,282,283,284,285,286,287
,288,289,290,291,292,293,294,295,296,297,298,299,300,301,302,303,304,305,306,307
,308,309,3

Thanks

-John

On 1/12/07, Stefan O'Rear [EMAIL PROTECTED] wrote:


On Fri, Jan 12, 2007 at 05:07:04PM +1100, John Ky wrote:
 Hi,

 Is it possible to use CTRL+C or equivalent to interrupt a computation or
I/O
 and return to the ghci prompt?

Yes.

[EMAIL PROTECTED]:~/lb-sorear$ ghci
   ___ ___ _
  / _ \ /\  /\/ __(_)
/ /_\// /_/ / /  | |  GHC Interactive, version 6.7, for Haskell 98.
/ /_\\/ __  / /___| |  http://www.haskell.org/ghc/
\/\/ /_/\/|_|  Type :? for help.

Loading package base ... linking ... done.
Prelude [0..]

[0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,

32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,

61,62,63,64,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,

90,91,92,93,94,95,96,97,98,99,100,101,102,103,104,105,106,107,108,109,110,111,112,113,1

14,115,116,117,118,119,120,121,122,123,124,125,126,127,128,129,130,131,132,133,134,135,

136,137,138,139,140,141,142,143,144,145,146,147,148,149,150,151,152,153,154,155,156,157

,158,159,160,161,162,163,164,165,166,167,168,169,170,171,172,173,174,175,176,177,178,17

9,180,181,182,183,184,185,186,187,188,189,190,191,192,193,194,195,196,197,198,199,200,2

01,202,203,204,205,206,207,208,209,210,211,212,213,214,215,216,217,218,219,220,221,222,

223,224,225,226,227,228,229,230,231,232,233,234,235,236,237,238,239,240,241,242,243,244

,245,246,247,248,249,250,251,252,253,254,255,256,257,258,259,260,261,262,263,264,265,26

6,267,268,269,270,271,272,273,274,275,276,277,278,279,280,281,282,283,284,285,286,287,2

88,289,290,291,292,293,294,295,296,297,298,299,300,301,302,303,304,305,306,307,308,309,

310,311,312,313,314,315,316,317,318,319,320,321,322,323,324,325,326,327,328,329,330,331

,332,333,334,335,336,337,338,339,340,341,342,343,344,345,346,347,348,349,350,351,352,35
3,354,355,356,357,358,35Interrupted.
Prelude

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] restricted existential datatypes

2007-01-11 Thread oleg

Misha Aizatulin wrote
   I am using existential boxes like
  data Box cxt = forall a . Sat (cxt a) = Box a
   here Sat is taken from [1]:
  class Sat a where dict :: a
   The result is a box type which can have variable context imposed on
 its contents. What I noticed is that sometimes I want to write functions
 that operate on the Box and make use of some part of the context without
 knowing the context completely. Such a function would look something
 like this:

  f :: (Contains cxt ShowCxt) = Box cxt - String
  f (Box a) = show a

It seems what you'd like is an opaque datum that responds to
(generally open) set of messages giving a reply dependent on a
message. Sounds like an object, doesn't it? Why does it have to be an
existential? True, existentials (that is, type abstraction) is one way
to implement objects. There are other ways.

Let's consider a very simple example:

 data Box = forall a . Show a  = Box a
 f (Box a) = show a

Now, the *only* meaningful thing we can do with the value `a' after 
unboxing is to pass it to the function `show'. Right? One may wonder
why not to perform this application to show right upfront:

 data Box1 = Box1 String
 box a = Box1 (show a)

This is _precisely_ equivalent to the above. Thanks to lazy
evaluation, the application `show a' won't be evaluated unless we
really need its value. The obvious benefit of Box1 is the simplicity
of it: no existentials. 

The value 'Box1' is an object that responds to only one message,
`show'. We'd like to have several messages, and we'd like to have the
set of messages open. There are two choices: HList or the
typeclasses. Both do the same thing, only the heterogeneous set of
dictionaries is explicit in the former approach and implicit in the
latter. Given below is the example. The box data constructor can be
hidden in a module; its details are not important anyway. What is
important is the membership in the Boxable class. The code below
works with GHC 6.4.1 (no advanced versions required) and even in Hugs.


{-# OPTIONS -fglasgow-exts #-}
module RestrictedEx where

-- Box labeled l responding to a message msg gives the result x
class Boxable l msg x | l msg - x where
box_value :: l - msg - x

-- A few message labels
data SHow = SHow
data CastToInt = CastToInt
data Print = Print

-- Create one box
data MyBox1 = MyBox1 String

-- Define its response to messages

instance Boxable MyBox1 SHow String where
box_value (MyBox1 s) _ = s

instance Boxable MyBox1 Print (IO ()) where
box_value (MyBox1 s) _ = putStrLn s

-- A function that takes any box that can be shown
f1 :: Boxable b SHow String = b - String
f1 b = box_value b SHow
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe