Re: [Haskell-cafe] enforcing strictness on arbitrary subexpressions

2006-02-17 Thread Matthias Fischmann


Thanks Udo, that helped a lot.

I added the link to haskell.org.  I couldn't find a proper place to
put it, so I added a page 'By topic' (still quite empty) linked from
the main page.  (I hope that wasn't against any rules I missed; if
anybody objects please feel free to remove it.)

cheers,
matthias



On Thu, Feb 16, 2006 at 01:10:14PM +0100, Udo Stenzel wrote:
 To: Matthias Fischmann [EMAIL PROTECTED]
 Cc: haskell-cafe@haskell.org
 From: Udo Stenzel [EMAIL PROTECTED]
 Date: Thu, 16 Feb 2006 13:10:14 +0100
 Subject: Re: [Haskell-cafe] enforcing strictness on arbitrary subexpressions
 
 Matthias Fischmann wrote:
  I want to force evaluation on an arbitrary expression.
  [...]
 
  main :: IO ()
  main = do
 hPutStr stdout veryLongString  -- lazy
 veryLongString `seq` hPutStr stdout veryLongString  -- still lazy?
 (StrictThingy veryLongString) `seq` hPutStr stdout veryLongString  
  -- strict (or at least i hope it is)
 
 The last line is actually equivalent to the second.  Strict data
 constructors are defined in term of seq, and seq only forces the
 evaluation of the outermost constructor.  So after seq'ing a string, it
 is either empty or has at least one element, but that element and the
 whole tail are still unevaluated.  You have to recurse into the string
 to evaluate everything:
 
  hPutStr stdout $ foldr seq veryLongString veryLongString
 
 There is no primitive to do this for arbitrary data types, but the
 DeepSeq type class comes close.  You can find DeepSeq and some more
 hints on strict evaluation at
 http://users.aber.ac.uk/afc/stricthaskell.html.
 
 
 Udo.
 -- 
 Today is the tomorrow you worried about yesterday.


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


[Haskell-cafe] descriptive symbols, was: monad combinator

2006-02-17 Thread Christian Maeder

Tomasz Zielonka wrote:

On Thu, Feb 16, 2006 at 04:36:06PM +0100, Christian Maeder wrote:

Udo Stenzel wrote:

(*) :: Monad m = m a - m b - m a
m * n = do a - m ; n ; return a
Right, that one is really useful. I named it (), though, conforming to 
 (=) versus (=).


But = first executes the second argument...


... so much to striking symbolic identifiers. (In fact, I've never used 
=.)


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


[Haskell-cafe] HaXml: ampersand in attribute value

2006-02-17 Thread Koen . Roelandt
HaXml seems to choke on finding an ampersand in an attribute value. Is 
this normal? Is there any workaround?

Cheers,

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


Re: [Haskell-cafe] Code completion? (IDE)?

2006-02-17 Thread Marc Weber
On Thu, Feb 16, 2006 at 09:50:51AM -0300, Thiago Arrais wrote:
 On 2/16/06, Thiago Arrais [EMAIL PROTECTED] wrote:
  Just take a look at the latest integration build that you are able to find 
  at
 
  http://eclipsefp.sourceforge.net/download
 
 There is also a screenshot at
 
 http://eclipsefp.sourceforge.net/images/first-content-assist.png

Is this content aware?
Doing this kind of complition is easy to achieve in vim, too.

I tried downloading, eclipse and the latest EcplipseFP zip file.
I couldn't use the standard installer (Help- Add Features ..) because
it didn't find anything..

But now I don't know how to switch to haskell mode or wether it's
properly installed.

But I think I can't use it because Eclipse is slow compared to vim and
at the moment I'm running Windows and colinux on the same system (using
colinux) with 512 RAM.. When using Eclipse swapping starts.. but if you
get this working for jEdit.. you may make me using it ..

I think my way to go is: using already existing haskell parsers and add
haskell script support to vim.. Using hs-plugins it shouldn't be that
hard.. But I have to learn that stuff first.

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


Re: [Haskell-cafe] Code completion? (IDE)?

2006-02-17 Thread Ketil Malde
Marc Weber [EMAIL PROTECTED] writes:

 I tried downloading, eclipse and the latest EcplipseFP zip file.
 I couldn't use the standard installer (Help- Add Features ..) because
 it didn't find anything..

Strange, that worked for me.

From my quick look, Eclipse looks like a workable candidate.  Since I
have the Emacs key combinations pretty much hard-wired in my hands, I
was pleased to see there was an Emacs mode, and pleasantly surprised
that unlike some Emacs modes, it actually seemed to be fairly faithful
and complete.

However, I got a bit lost in the various menus, and having no previous
experience with it, I don't know whether any problems are due to bugs
or incompletenesses in EclipseFP, or my lack of experience with
Eclipse itself.  So at the moment, I'm still using Emacs.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] HaXml: ampersand in attribute value

2006-02-17 Thread Malcolm Wallace

[EMAIL PROTECTED] wrote:
HaXml seems to choke on finding an ampersand in an attribute value. Is 
this normal? Is there any workaround?


Yes, it is expected.  An ampersand indicates the start of a reference, 
e.g. lt; or #20;  If there is no semicolon to indicate the end of the 
reference, then it is a parse error.  The XML specification is quite 
clear that neither  nor  are valid standalone characters in an 
attribute value.


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


[Haskell-cafe] Re: Associated Type Synonyms question

2006-02-17 Thread Stefan Wehr
Martin Sulzmann [EMAIL PROTECTED] wrote::

 Stefan Wehr writes:
  [...]
  Manuel (Chakravarty) and I agree that it should be possible to
  constrain associated type synonyms in the context of class
  definitions. Your example shows that this feature is actually
  needed. I will integrate it into phrac within the next few days.
  

 By possible you mean this extension won't break any
 of the existing ATS inference results?

Yes, although we didn't go through all the proofs.

 You have to be very careful otherwise you'll loose decidability.

Do you have something concrete in mind or is this a more general
advice?

Stefan

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


[Haskell-cafe] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Peter
Hello,

For the purpose of familiarizing myself with Haskell, and also because I
love Haskell :),
I am trying to re-make a script that I made in Python that sends a
request to a server and extracts the list of email addresses from a
Mailman web-page by using an XML Parser on the page's HTML that has been
converted to XHTML by HTML Tidy.

However, I cannot seem to figure out a way to get the state of a Monad;
Specifically I cannot get the value of an IO String Monad.

I have read some tutorials on Monads but I guess I must have missed
something.

I have read that the = operator is the only way to extract the state
of an action as a string, and pipe it to a function. So far so good.
But, That does not seem to work, because as I understand the =
operator, it expects the function on the right hand side to return an IO
Monad, which completely defeats the purpose here.

So, How am I supposed to get the value of an IO Monad, such as IO
String, without returning an IO Monad?

If this is of any help, here is the function I am stuck on:
recv_headers' :: Socket.Socket - String - IO [[String]]
recv_headers' sock bulk
| received == = error Connection died unexpectedly.
| received == \n
   endswith bulk \r\n\r = return [[foo, bar]]
| otherwise = recv_headers' sock (bulk ++ received)
where received = (Socket.recv sock 1)
--- End code ---

And here is the (expected) error I get from trying to compare IO
String to String:
MemberBackup.hs:29:18:
Couldn't match `IO String' against `[Char]'
  Expected type: IO String
  Inferred type: [Char]
In the second argument of `(==)', namely `'
In a pattern guard for
   the definition of `recv_headers'':
received == 
Failed, modules loaded: none.
--- End error ---

Thanks for the help,
Peter

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


[Haskell-cafe] haskell question

2006-02-17 Thread IBRAHIM MOSHAYA

please can you help me with this function:

Significant Figures
I need to write a function to return a given number (1st argument) to a 
given number of significant figures
(2nd argument). The function should be called sigFig and have a type 
signature of the form:

sigFig :: (???) = a - Int - a
For instance:
*Main sigFig 123.456 2
120.0
*Main sigFig 123.456 4
123.5
*Main sigFig 0.987 2
0.99
*Main sigFig 0.432 2
0.43
The type variable a will need to be constrained, but you should aim for the 
most general implementation you
can (replacing ??? above with the appropriate constraint(s)). You may make 
free use of Prelude functions.
Referring to [Jon03] you may wish to consider the use of functions / 
operators including:

/, div, mod, ^, ^^, **, round, fromIntegral, realToFrac

thanks alot


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


Re: [Haskell-cafe] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Marc Weber
You can access IO values only from within do blocks (see any tutorial,
previous posts or google).
It looks like this then:
do=
  myvalue - functionwhichreturnsIOValue
  dosomethingwith myvalue

Due to monads you don't have to leave the IO monad this way.
Oh. Have to go now.

do is translated into = syntax, see do expansion.

Hope this did help else wait for another longer answer ;-)

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


Re: [Haskell-cafe] HaXml: ampersand in attribute value

2006-02-17 Thread Lennart Augustsson

But speaking of HaXml bugs, I'm pretty sure HaXml doesn't handle
% correctly.  It seem to treat % specially everywhere, but I think
it is only special inside DTDs.  I have many XML files produced by
other tools that the HaXml parser fails to process because of this.

-- Lennart

Malcolm Wallace wrote:

[EMAIL PROTECTED] wrote:
HaXml seems to choke on finding an ampersand in an attribute value. Is 
this normal? Is there any workaround?


Yes, it is expected.  An ampersand indicates the start of a reference, 
e.g. lt; or #20;  If there is no semicolon to indicate the end of the 
reference, then it is a parse error.  The XML specification is quite 
clear that neither  nor  are valid standalone characters in an 
attribute value.


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] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Ketil Malde
Peter [EMAIL PROTECTED] writes:

 So, How am I supposed to get the value of an IO Monad, such as IO
 String, without returning an IO Monad?

Short answer: you don't.  IO is a one way street.  

Build your application top down in the IO monad (starting with
'main'), and bottom up with pure code, and hope you can make them meet
somewhere in the middle. :-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] haskell question

2006-02-17 Thread Ketil Malde
IBRAHIM MOSHAYA [EMAIL PROTECTED] writes:

 I need to write a function to return a given number

Homework assignment?

Perhaps if you get stuck, you can post your best current effort, and
people will be able to nudge you in the right direction?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Lemmih
On 2/17/06, Peter [EMAIL PROTECTED] wrote:
 Hello,

 For the purpose of familiarizing myself with Haskell, and also because I
 love Haskell :),
 I am trying to re-make a script that I made in Python that sends a
 request to a server and extracts the list of email addresses from a
 Mailman web-page by using an XML Parser on the page's HTML that has been
 converted to XHTML by HTML Tidy.

 However, I cannot seem to figure out a way to get the state of a Monad;
 Specifically I cannot get the value of an IO String Monad.

 I have read some tutorials on Monads but I guess I must have missed
 something.

 I have read that the = operator is the only way to extract the state
 of an action as a string, and pipe it to a function. So far so good.
 But, That does not seem to work, because as I understand the =
 operator, it expects the function on the right hand side to return an IO
 Monad, which completely defeats the purpose here.

 So, How am I supposed to get the value of an IO Monad, such as IO
 String, without returning an IO Monad?

 If this is of any help, here is the function I am stuck on:
 recv_headers' :: Socket.Socket - String - IO [[String]]
 recv_headers' sock bulk
 | received == = error Connection died unexpectedly.
 | received == \n
endswith bulk \r\n\r = return [[foo, bar]]
 | otherwise = recv_headers' sock (bulk ++ received)
 where received = (Socket.recv sock 1)

Try:

recv_headers' sock bulk
  = do received - Socket.recv sock 1
   case received of
  - error ...
 \n | endswith bulk \r\n\r - ...
 _ - recv_headers' sock (bulk ++ received)

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


Re: [Haskell-cafe] library sort

2006-02-17 Thread Radu Grigore
On 2/16/06, Jared Updike [EMAIL PROTECTED] wrote:
 If you need an easier way to search the Haskell APIs, use Hoogle:

Hoogle is very nice. Thanks to everyone who answered my question about
finding a sort library function.

--
regards,
  radu
http://rgrig.blogspot.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Daniel Fischer
Hi,

Am Freitag, 17. Februar 2006 14:42 schrieb Peter:
 Hello,

 For the purpose of familiarizing myself with Haskell, and also because I
 love Haskell :),

very good!

 I am trying to re-make a script that I made in Python that sends a
 request to a server and extracts the list of email addresses from a
 Mailman web-page by using an XML Parser on the page's HTML that has been
 converted to XHTML by HTML Tidy.

 However, I cannot seem to figure out a way to get the state of a Monad;
 Specifically I cannot get the value of an IO String Monad.

 I have read some tutorials on Monads but I guess I must have missed
 something.

 I have read that the = operator is the only way to extract the state
 of an action as a string, and pipe it to a function. So far so good.
 But, That does not seem to work, because as I understand the =
 operator, it expects the function on the right hand side to return an IO
 Monad, which completely defeats the purpose here.

I find do-notation often more readable, then you write val - action and 
val is an ordinary value, you can use afterwards (within the same do-block, of 
course)


 So, How am I supposed to get the value of an IO Monad, such as IO
 String, without returning an IO Monad?

 If this is of any help, here is the function I am stuck on:
 recv_headers' :: Socket.Socket - String - IO [[String]]
 recv_headers' sock bulk

 | received == = error Connection died unexpectedly.
 | received == \n

endswith bulk \r\n\r = return [[foo, bar]]

 | otherwise = recv_headers' sock (bulk ++ received)

 where received = (Socket.recv sock 1)
 --- End code ---

This should do it:

recv_headers' :: Socket.Socket - String - IO [[String]]
recv_headers' sock bulk
 = do
 { received - Socket.recv sock 1
 ; case received of
  - error Connection died unexpectedly.
 \n | endswith bulk \r\n\r - return [[foo, bar]]
 _  - recv_headers' sock (bulk ++ received)
 }

at least, it compiles.

 And here is the (expected) error I get from trying to compare IO
 String to String:
 MemberBackup.hs:29:18:
 Couldn't match `IO String' against `[Char]'
   Expected type: IO String
   Inferred type: [Char]
 In the second argument of `(==)', namely `'
 In a pattern guard for
the definition of `recv_headers'':
 received == 
 Failed, modules loaded: none.
 --- End error ---

 Thanks for the help,
 Peter


Cheers,
Daniel
-- 

In My Egotistical Opinion, most people's C programs should be
indented six feet downward and covered with dirt.
-- Blair P. Houghton

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


Re: [Haskell-cafe] Re: Associated Type Synonyms question

2006-02-17 Thread Claus Reinke

Something more controversial.
Why ATS at all? Why not encode them via FDs?


Funny you should say that, just when I've been thinking about 
the same thing. That doesn't mean that ATS aren't a nice way 
to describe some special cases of FDs, but my feeling is that
if ATS can't be encoded in FDs, then there is something 
wrong with _current_ FD versions that should be fixed.


I'd love to hear the experts' opinions about this claim!-)

The main argument for ATS is that the extra parameter for the
functionally dependend type disappears, but as you say, that
should be codeable in FDs. I say should be, because that does
not seem to be the case at the moment.

My approach for trying the encoding was slightly different from
your's, but also ran into trouble with implementations.

First, I think you need a per-class association, so your T a b
would be specific to C. Second, I'd use a superclass context
to model the necessity of providing an associated type, and
instance contexts to model the provision of such a type. No
big difference, but it seems closer to the intension of ATS:
associated types translate into type association constraints.

(a lot like calling an auxiliary function with empty accumulator,
to hide the extra parameter from the external interface)


Example

-- ATS
class C a where
 type T a
 m :: a-T a
instance C Int where
 type T Int = Int
 m _ = 1


-- alternative FD encoding attempt

class CT a b | a - b
instance CT Int Int

class CT a b = C a where
   m :: a- b

instance CT Int b = C Int where 
   m _ = 1::b



-- FD encoding
class T a b | a-b 
instance T Int Int


class C a where
 m :: T a b = a-b

instance C Int where
 m _ = 1

-- general recipe:
-- encode type functions T a via type relations T a b
-- replace T a via fresh b under the constraint C a b


referring to the associated type seems slightly awkward 
in these encodings, so the special syntax for ATS would 
still be useful, but I agree that an encoding into FDs should

be possible.


The FD program won't type check under ghc but this
doesn't mean that it's not a legal FD program.


glad to hear you say that. but is there a consistent version
of FDs that allows these things - and if not, is that for lack
of trying or because it is known not to work?

Cheers,
Claus


It's wrong to derive certain conclusions
about a language feature by observing the behavior
of a particular implementation!

Martin


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


Re: [Haskell-cafe] Re: Associated Type Synonyms question

2006-02-17 Thread Ross Paterson
On Fri, Feb 17, 2006 at 01:26:18PM +, Stefan Wehr wrote:
 Martin Sulzmann [EMAIL PROTECTED] wrote::
  By possible you mean this extension won't break any
  of the existing ATS inference results?
 
 Yes, although we didn't go through all the proofs.
 
  You have to be very careful otherwise you'll loose decidability.

The paper doesn't claim a proof of decidability (or principal types),
but conjectures that it will go through.

Apropos of that, I tried translating the non-terminating FD example from
the FD-CHR paper (ex. 6) to associated type synonyms (simplified a bit):

data T a = K a;

class C a where {
type S a;
r :: a - S a;
}

instance C a = C (T a) where {
type S (T a) = T (S a);
r (K x) = K (r x);
}

f b x = if b then r (K x) else x;

Phrac infers

f :: forall a . (S (T a) = a, C a) = Bool - a - T (S a)

The constraint is reducible (ad infinitum), but Phrac defers constraint
reduction until it is forced (as GHC does with ordinary instance
inference).  We can try to force it using the MR, by changing the
definition of f to

f = \ b x - if b then r (K x) else x;

For this to be legal, the constraint must be provable.  In the
corresponding FD case, this sends GHC down the infinite chain of
reductions, but Phrac just gives up and complains about deferred
constraints being left over after type inference.  I don't think this
is right either, as in other cases the constraint will reduce away
to nothing.

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


[Haskell-cafe] Re: HaXml: ampersand in attribute value

2006-02-17 Thread Koen . Roelandt
 But speaking of HaXml bugs, I'm pretty sure HaXml doesn't handle
 % correctly.  It seem to treat % specially everywhere, but I think
 it is only special inside DTDs.  I have many XML files produced by
 other tools that the HaXml parser fails to process because of this.

I had a similar problem where the parser choked on % signs in attribute 
values in the XML file. I solved it by playing around in Lex.hs. I could 
check for the (ugly) solution...

 Yes, it is expected.  An ampersand indicates the start of a reference, 
 e.g. lt; or #20;  If there is no semicolon to indicate the end of the 
 reference, then it is a parse error.  The XML specification is quite 
 clear that neither  nor  are valid standalone characters in an 
 attribute value.

Which is exactly the problem. The  is part of a reference, namely euml;.

Regards,

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


Re: [Haskell-cafe] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Udo Stenzel
Peter wrote:
 So, How am I supposed to get the value of an IO Monad, such as IO
 String, without returning an IO Monad?

You read correctly, this is impossible.  You already got some valid
answers, and here's another variant that preserves most of the nice
guarded expressions:


recv_headers' :: Socket.Socket - String - IO [[String]]
recv_headers' sock bulk = Socket.recv sock 1 = dispatch
  where dispatch = error Connection died unexpectedly.
dispatch \n | endswith bulk \r\n\r = return [[foo, bar]]
dispatch _ = recv_headers' sock (bulk ++ received)

 
Udo.
-- 
Gadgets are not necessarily an improvement, vide the succession:
Blackboard - Overhead Projector - PowerPoint
-- E. W. Dijkstra


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


Re: [Haskell-cafe] HaXml: ampersand in attribute value

2006-02-17 Thread Malcolm Wallace

Lennart Augustsson wrote:
 But speaking of HaXml bugs, I'm pretty sure HaXml doesn't handle
 % correctly.  It seem to treat % specially everywhere, but I think
 it is only special inside DTDs.  I have many XML files produced by
 other tools that the HaXml parser fails to process because of this.

I believe I fixed at least one bug to do with % characters around
version 1.14.  But that is the development branch in darcs, not formally
released yet.  Nevertheless, if you know of such bugs, do report them;
even better if you can send a small test case.

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


Re: [Haskell-cafe] Badly designed Parsec combinators?

2006-02-17 Thread Jan-Willem Maessen


On Feb 16, 2006, at 7:32 PM, John Meacham wrote:


...

  Again that doesn't compile, because when requires a ()-returning
monad as its second parameter, but the string parser returns  
String.
Same thing with if-then-else, when used to switch IO actions and  
such:
the IO actions must fully match in type, even if the returned  
value will

be discarded, and again that can be trivially resolved by adding the
return ().


This is a straight up bug in the definition of when I hope we fix. it
should have type

when :: Bool - IO a - IO ()
when = ...


Arguably this could be made true of *every* function which presently  
takes m () as an argument.  That is, we could systematically go  
through the libraries and convert every function of type:


f :: (Monad m) =  - m () - ...

into

f :: (Monad m) =  - m otherwiseUnusedTypeVariable - ...

This would basically eliminate the need for ignore.  I can see  
taste arguments in either direction, but really the language ought to  
pick an alternative and use it everywhere (including for ).


-Jan-Willem Maessen



John


--
John Meacham - ⑆repetae.net⑆john⑈
___
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] Infinite loop?

2006-02-17 Thread rgo
Hi all,
my program probably goes into infinite loop... But i cannot understand where 
and why.

code:

import System.Directory

data MyFile = MyDir {
dir_name :: String,
dir_files :: [MyFile]
}
| MyFile {
file_name :: String
}

read_dir_entries :: [FilePath] - IO [MyFile]
read_dir_entries [] = return []
read_dir_entries (name:names) = do
isdir - doesDirectoryExist name;
entry - if isdir
then read_dir name
else return (MyFile {file_name = name});
entries - read_dir_entries names;
return (entry:entries)


read_dir :: FilePath - IO MyFile
read_dir name = do 
content - getDirectoryContents name;
files - read_dir_entries content;
return MyDir {
dir_name = name,
dir_files = files
}

instance Show MyFile where
show (MyDir {dir_name = name, dir_files = files}) = 
\n ++ name ++ :\n ++ show files
show (MyFile {file_name = name}) = \t ++ name ++ \n

main = do
cwd - getCurrentDirectory;
dir - read_dir cwd;
print dir;
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infinite loop?

2006-02-17 Thread Jon Fairbairn
On 2006-02-17 at 20:12GMT rgo wrote:
 Hi all,
 my program probably goes into infinite loop... But i cannot understand where 
 and why.

getDirectoryContents will include . and .., so if you
follow those, you're bound to loop.

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


Re: [Haskell-cafe] Infinite loop?

2006-02-17 Thread Jared Updike
Yep. change one line to:

   entry - if isdir  name /= .  name /= ..

and it does in fact work.

  Jared.

On 2/17/06, Jon Fairbairn [EMAIL PROTECTED] wrote:
 On 2006-02-17 at 20:12GMT rgo wrote:
  Hi all,
  my program probably goes into infinite loop... But i cannot understand 
  where and why.

 getDirectoryContents will include . and .., so if you
 follow those, you're bound to loop.

 --
 Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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



--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Infinite loop?

2006-02-17 Thread Jon Fairbairn
On 2006-02-17 at 09:22PST Jared Updike wrote:
 Yep. change one line to:
 
entry - if isdir  name /= .  name /= ..
 
 and it does in fact work.

Only if no-one has been tricky with symbolic links.

-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


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


[Haskell-cafe] Problems instancing a class

2006-02-17 Thread Juan Carlos Arevalo Baeza

  So, consider this code:

import Data.HashTable as HT

class MyClass a where
   htLookup :: a - String - IO String

type Context = HT.HashTable String String

instance MyClass Context where
   htLookup h var =
   do  result - HT.lookup h var
   case result of
   Nothing - return 
   Just s - return s

  This doesn't compile. GHC says:

Illegal instance declaration for `MyClass Context'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
In the instance declaration for `MyClass Context'

  If I use data instead of type, it works:

data Context = C (HT.HashTable String String)

instance MyClass Context where
   htLookup (C h) var =
   do  result - HT.lookup h var
   case result of
   Nothing - return 
   Just s - return s

  Why? What's going on here?

JCAB

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


Re: [Haskell-cafe] Problems instancing a class

2006-02-17 Thread Jared Updike
 type introduce a type synonym, and Haskell98 forbids these in
 instances, so GHC complains. GHC also lifts this restriction when
 invoked with -fglasgow-exts .
 http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#type-synonyms


Flexible Instances will probably be added to HaskellPrime:
  http://hackage.haskell.org/trac/haskell-prime/wiki/FlexibleInstances

This page:

http://cvs.haskell.org/Hugs/pages/users_guide/class-extensions.html#FLEXIBLE-INSTANCES

says that ultimately you would turn the type language pretty much into
Prolog (which would allow more expressive power---and less
inconvenience as we both would like--but make general type checking
undecidable). Instead they do a more conservative extension with a
fixed depth of constraints it will check so the compiler will
terminate.

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


Re: [Haskell-cafe] Problems instancing a class

2006-02-17 Thread Juan Carlos Arevalo Baeza

Gerrit van den Geest wrote:

Mark
Mark Jones has (some time ago) also written a very detailed e-mail 
about this topic:


http://www.haskell.org/pipermail/haskell/2000-October/006128.html


  I really don't understand anything spoken about in this message. I 
guess I need it translated into plain English :)


  I'd contend that, if Haskell is so good (and I believe it is), it 
should be more accessible to your average Joe, even if some might disagree.



Grt


type introduce a type synonym, and Haskell98 forbids these in
instances, so GHC complains. GHC also lifts this restriction when
invoked with -fglasgow-exts .
http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#type-synonyms 



  Thanx all for the replies. And here I thought I was compiling with 
extensions enabled. Blame it on using a compile script. Not that I had 
made the connection with this error...


  What really got me is that if I don't use a type synonym:

instance MyClass (HT.HashTable String String) where
   htLookup h var =
   do  result - HT.lookup h var
   case result of
   Nothing - return 
   Just s - return s

  it still complains:

Illegal instance declaration for `MyClass (HashTable String String)'
   (The instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
In the instance declaration for `MyClass (HashTable String String)'

  even though the documentation in GHC states that HashTable is 
declared as data.


  I haven't had time to read all the documentation you guys have 
forwarded to me, but still, I have one question. I was reading here:


http://hackage.haskell.org/trac/haskell-prime/wiki/TypeSynonymInstances

  and it says The proposal is to allow type synonyms (fully applied, 
as ever) in instance heads. These would be fully expanded before any 
other restrictions on instance heads were checked, which is what sounds 
logical to me. And then it says Not very useful without either 
FlexibleInstances /trac/haskell-prime/wiki/FlexibleInstances or 
UndecidableInstances /trac/haskell-prime/wiki/UndecidableInstances. I 
don't understand why. This extension would not depend on those other 
more involved extensions. Later down it says Cons - Since constraints 
on the instance head refer to the expanded type, errors can be more 
obscure. Is that the reason? Because the other extensions would make 
errors clearer?


  I'd like to ask someone in the know to provide a good example that 
shows the reasons behind those statements are there. Preferably added to 
the Wiki :)


  How exactly is type undecidable if this is allowed? I found here:

http://hackage.haskell.org/trac/haskell-prime/wiki/FlexibleInstances

  an example of a non-terminating instance:

instance C b b = C (Maybe a) b

  I don't see how/where/when this would be non-terminating. I mean... 
if you now define an instance C Int Int, then you actually also have 
C (Maybe Int) Int, C (Maybe (Maybe Int)) Int and so on, I can see 
that. But how exactly is that a problem? Can you show me a use of C that 
cannot work with that instance?


  Thanx!

JCAB

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


Re: [Haskell-cafe] Infinite loop?

2006-02-17 Thread rgo
On Fri, 17 Feb 2006 17:19:53 +
Jon Fairbairn [EMAIL PROTECTED] wrote:

 On 2006-02-17 at 20:12GMT rgo wrote:
  Hi all,
  my program probably goes into infinite loop... But i cannot understand 
  where and why.
 
 getDirectoryContents will include . and .., so if you
 follow those, you're bound to loop.
 
 -- 
 Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk
 
 

Thanks.
It's the third time in my life when do this error. :-[

here working code:

import System.Directory

data MyFile = MyDir {
dir_name :: FilePath,
dir_files :: [MyFile]
}
| MyFile {
file_name :: FilePath
}

read_dir_entries :: FilePath - [FilePath] - IO [MyFile]
read_dir_entries _ [] = return []
read_dir_entries dirname (name:names) = do
isdir - doesDirectoryExist name;
entry - if (isdir  (name /= .)  (name /= ..))
then read_dir (dirname ++ / ++ name)
else return (MyFile {file_name = name});
entries - read_dir_entries dirname names;
return (entry:entries)

read_dir :: FilePath - IO MyFile
read_dir name = do 
content - getDirectoryContents name;
files - read_dir_entries name content;
return MyDir {
dir_name = name,
dir_files = files
}

instance Show MyFile where
show (MyDir {dir_name = name, dir_files = files}) = 
\n ++ name ++ :\n ++ show files
show (MyFile {file_name = name}) = \t ++ name ++ \n

main = do
cwd - getCurrentDirectory;
dir - read_dir cwd;
print dir;
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Unexpected results with simple IO

2006-02-17 Thread Cale Gibbard
That doesn't happen for me at all, it works just fine. Maybe it's
something wrong with your terminal? You could possibly try playing
with the buffering settings on stdout, using hSetBuffering in
System.IO.

 - Cale

On 17/02/06, Maurício [EMAIL PROTECTED] wrote:
Dear Haskell users,

I have a problem using IO. The small test program below asks the user
 to guess from a list of random numbers between 1 and 10. Everything
 works well excepts for one problem: all the messages (Guess a
 number..., Right... and Wrong...) are printed after the program
 finishes, i.e., I have to use it blind. I'm afraid I misunderstand
 something important about lazyness or monads... What am I doing wrong?

Thanks,
Maurício

 module Main where
 import Random

 main = do
 r_gen - getStdGen --random generator
 let r_list = (randomRs (1,10) r_gen) --random list
 guess_loop (r_list)

 guess_loop (r:r_others) = do
 putStrLn Guess a number between 1 and 10:
 n - readLn
 if n==r
then do
   putStrLn Right! :)
   return ()
else do
   putStrLn Wrong... :(
   guess_loop r_others

 ___
 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] Problems instancing a class

2006-02-17 Thread Benjamin Franksen
On Friday 17 February 2006 21:03, Juan Carlos Arevalo Baeza wrote:
What really got me is that if I don't use a type synonym:

 instance MyClass (HT.HashTable String String) where
 htLookup h var =
 do  result - HT.lookup h var
 case result of
 Nothing - return 
 Just s - return s

it still complains:

 Illegal instance declaration for `MyClass (HashTable String String)'
 (The instance type must be of form (T a b c)
  where T is not a synonym, and a,b,c are distinct type variables)
 In the instance declaration for `MyClass (HashTable String String)'

even though the documentation in GHC states that HashTable is
 declared as data.

(Guessing) Maybe because 'String' is not a type variable?

How exactly is type undecidable if this is allowed? I found here:

 http://hackage.haskell.org/trac/haskell-prime/wiki/FlexibleInstances

an example of a non-terminating instance:

 instance C b b = C (Maybe a) b

I don't see how/where/when this would be non-terminating. I
 mean... if you now define an instance C Int Int, then you actually
 also have C (Maybe Int) Int, C (Maybe (Maybe Int)) Int and so on,
 I can see that. But how exactly is that a problem? Can you show me a
 use of C that cannot work with that instance?

What is (or better: might be) non-terminating is the process (algorithm) 
of /type inference/. This:

http://www.haskell.org//pipermail/haskell-prime/2006-February/000609.html

message contains a detailed explanation.

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


[Haskell-cafe] Re: Unexpected results with simple IO

2006-02-17 Thread Maurício
  You're right... I was running the example in rxvt, in cygwin. Now I 
tried in Windows command shell and it works.


  Thanks,
  Maurício

Cale Gibbard wrote:

That doesn't happen for me at all, it works just fine. Maybe it's
something wrong with your terminal? You could possibly try playing
with the buffering settings on stdout, using hSetBuffering in
System.IO.

 - Cale

On 17/02/06, Maurício [EMAIL PROTECTED] wrote:


  Dear Haskell users,

  I have a problem using IO. The small test program below asks the user
to guess from a list of random numbers between 1 and 10. Everything
works well excepts for one problem: all the messages (Guess a
number..., Right... and Wrong...) are printed after the program
finishes, i.e., I have to use it blind. I'm afraid I misunderstand
something important about lazyness or monads... What am I doing wrong?

  Thanks,
  Maurício

module Main where
import Random

main = do
   r_gen - getStdGen --random generator
   let r_list = (randomRs (1,10) r_gen) --random list
   guess_loop (r_list)

guess_loop (r:r_others) = do
   putStrLn Guess a number between 1 and 10:
   n - readLn
   if n==r
  then do
 putStrLn Right! :)
 return ()
  else do
 putStrLn Wrong... :(
 guess_loop r_others

___
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] (Newbie Question) How to get the value of an IO String Monad?

2006-02-17 Thread Cale Gibbard
Hi,

Apart from the other posts, you might also want to read
http://www.haskell.org/hawiki/IntroductionToIO which is a quick intro
to the way IO is handled in Haskell and
http://www.haskell.org/hawiki/UsingIo which covers similar ground, but
which also goes into a number of other common questions.

 - Cale

On 17/02/06, Peter [EMAIL PROTECTED] wrote:
 Hello,

 For the purpose of familiarizing myself with Haskell, and also because I
 love Haskell :),
 I am trying to re-make a script that I made in Python that sends a
 request to a server and extracts the list of email addresses from a
 Mailman web-page by using an XML Parser on the page's HTML that has been
 converted to XHTML by HTML Tidy.

 However, I cannot seem to figure out a way to get the state of a Monad;
 Specifically I cannot get the value of an IO String Monad.

 I have read some tutorials on Monads but I guess I must have missed
 something.

 I have read that the = operator is the only way to extract the state
 of an action as a string, and pipe it to a function. So far so good.
 But, That does not seem to work, because as I understand the =
 operator, it expects the function on the right hand side to return an IO
 Monad, which completely defeats the purpose here.

 So, How am I supposed to get the value of an IO Monad, such as IO
 String, without returning an IO Monad?

 If this is of any help, here is the function I am stuck on:
 recv_headers' :: Socket.Socket - String - IO [[String]]
 recv_headers' sock bulk
 | received == = error Connection died unexpectedly.
 | received == \n
endswith bulk \r\n\r = return [[foo, bar]]
 | otherwise = recv_headers' sock (bulk ++ received)
 where received = (Socket.recv sock 1)
 --- End code ---

 And here is the (expected) error I get from trying to compare IO
 String to String:
 MemberBackup.hs:29:18:
 Couldn't match `IO String' against `[Char]'
   Expected type: IO String
   Inferred type: [Char]
 In the second argument of `(==)', namely `'
 In a pattern guard for
the definition of `recv_headers'':
 received == 
 Failed, modules loaded: none.
 --- End error ---

 Thanks for the help,
 Peter

 ___
 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] Re: (Newbie Question) How to get the value of an IO String Monad

2006-02-17 Thread Peter
Hello All,

Thanks Cale, Udo, Daniel, Lemmih, Ketil, and Marc for your very helpful
posts, and Haskell resources.

Every post really helped a lot.

Thanks for all the help,
Peter

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