[Haskell-cafe] FW: Treating command-line arguments as a Haskell expression

2007-12-24 Thread Simon Peyton-Jones
Would someone familiar with the command-line-parsing libraries care to help 
Krassimir?

Thanks

Simon
-Original Message-
From: Krassimir Krustev [mailto:[EMAIL PROTECTED]
Sent: 23 December 2007 11:38
To: Simon Peyton-Jones
Subject: Treating command-line arguments as a Haskell expression

Dear Dr. Jones:

I've been pulling my hair over the Christmas Holidays trying to figure
the following:

I want to call a function from within Haskell module so that the name
of this function corresponds to my first command-line argument and the
rest rest of the  command-line arguments are would become themselves
the argument to this function.

Coundn't figure this out. It is my first week with Haskell.

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


[Haskell-cafe] Printing and Referential transparency excuse

2007-12-24 Thread Cristian Baboi
While reading the Haskell language report I noticed that function type is  
not an instance of class Read.


I was told that one cannot define them as an instance of class Show  
without breaking referential transparency or printing a constant.


  f :: (a-b)-String
  f x = bla bla bla

How can I define a function to do the inverse operation ?
  g :: String - ( a - b )

This time I cannot see how referential transparency will deny it.
What's the excuse now ?

I'm at the begining of chapter 7, but I have the feeling I'll not find the  
answer in there.



Thank you.


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


[Haskell-cafe] Re: Printing and Referential transparency excuse

2007-12-24 Thread apfelmus

Cristian Baboi wrote:
While reading the Haskell language report I noticed that function type 
is not an instance of class Read.


I was told that one cannot define them as an instance of class Show 
without breaking referential transparency or printing a constant.


  f :: (a-b)-String
  f x = bla bla bla

How can I define a function to do the inverse operation ?
  g :: String - ( a - b )

This time I cannot see how referential transparency will deny it.
What's the excuse now ?


The new excuse is that a better name for  g  is

  full-fledged-compiler :: String - (Int - Int)

(the function returned by  g  better not have a polymorphic type). Which 
programming language should the argument  String  be written in?



Regards
apfelmus

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


RE: [Haskell-cafe] A Foldable binary search tree

2007-12-24 Thread Simon Peyton-Jones
|  data (Ord a) = BST a = Empty | BST (BST a) a (BST a)
|
| Experience has taught me to _never_ put class contexts on data
| definitions.

Correct.  Haskell-98 contexts on data-type declarations are a mis-feature of 
Haskell, which I resisted at the time but failed to eliminate.

As others have pointed out, GHC allows you to put a context on any data 
constructor.  I prefer this where syntax:

data BST a where
  Empty :: BST a
  BST :: Ord a = BST a - a - BST a - BST a

but the other (existential-like) syntax also works:

data BST a = Empty | Ord a = BST (BST a) a (BST a)

The constructors have the signature they advertise.  When you use BST as a 
constructor, you must supply an Ord context.  But when you pattern-match on it, 
you *get* an Ord context.  For example

f :: a - BST a - Bool
f x Empty = False
f x (BST t1 y t2) = xy

Note the absence of an Ord context on f.

This works properly when combined with GADTs.  The uniform rule is: you must 
supply the context when you use the constructor as a function, and you bring 
the context into scope when you pattern match on the constructor.

Having this context on data constructors work right all the time is 
relatively new.  Previously it really only worked for existentials; but now 
there are no restrictions on the contexts you write on data constructors.

The Haskell 98 behaviour remains when you use the Haskell-98 syntax.

| I would accept this pain if it meant I could write:
|
| insert :: a - BST a - BST a

And so you can!  But to get this, you'll have to write an Ord context on the 
Empty constructor too.

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


Re: [Haskell-cafe] FW: Treating command-line arguments as a Haskell expression

2007-12-24 Thread Max Vasin
2007/12/24, Simon Peyton-Jones [EMAIL PROTECTED]:
 Would someone familiar with the command-line-parsing libraries care to help 
 Krassimir?

AFAIU Krassimir's needs, hs-plugins will help him (function eval).

-- 
WBR,
Max Vasin

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


Re: [Haskell-cafe] Haskell performance

2007-12-24 Thread Peter Lund
On Sun, 2007-12-23 at 11:52 +, Ian Lynagh wrote:
 On Thu, Dec 20, 2007 at 10:58:17AM +, Malcolm Wallace wrote:
  
  Nobench does already collect code size, but does not yet display it in
  the results table.  I specifically want to collect compile time as well.
  Not sure what the best way to measure allocation and peak memory use
  are?
 
 This:
 http://lists.osuosl.org/pipermail/darcs-devel/2006-January/004016.html
 should be Haskell-implementation-independent, but is probably
 Linux-specific. Adapting it to other Unix-like OSes is probably easy,
 but I have no idea about Windows.

Very nice.

A short-term improvement would perhaps be to use ptrace() to also sample
the program counter register?

On a longer-term scale, I wonder how hard it would be to implement a
valgrind skin to get much more precise heap-use information...

-Peter

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


Re: [Haskell-cafe] Functions are first class values in C

2007-12-24 Thread Antti-Juhani Kaijanaho
On Sat, Dec 22, 2007 at 05:25:26PM +0300, Miguel Mitrofanov wrote:
 That's not C.
 That's the C preprocessor, which is a textual substitution macro 
 language.

 Well, the preprocessor is part of the language in a way. These two come
 together.

 No. In fact, these are even two different programs, see man cpp.

No, in fact, preprocessing is an integral part of translating a C
program, see the standard.  The standard allows implementing the
translation phases 1-6 (the so-called preprocessing phases) as a
separate program, but there is no requirement to do that.

It is true, however, that preprocessing used to be (in pre-standard
days) separate from the language.  This has not been true for decades.

That said, this is all irrelevant to the question of whether C allows
first-class functions.  I'm sure we all are capable of writing Haskell
programs that do not have simple and readable translations to C :)

-- 
Antti-Juhani Kaijanaho, Jyväskylä, Finland
http://antti-juhani.kaijanaho.fi/newblog/
http://www.flickr.com/photos/antti-juhani/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functions are first class values in C

2007-12-24 Thread Miguel Mitrofanov
 It is true, however, that preprocessing used to be (in pre-standard
 days) separate from the language.  This has not been true for decades.

Well, I've seen cpp to be used as a preprocessor not for C sources but for 
something else.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Paulo J. Matos
On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote:

 -- this should work too
 parseHeader3 :: BS.ByteString - Maybe (Int, Int)
 --note accurate type signature, which helps us use Maybe failure-monad,
 --although losing your separate error messages

Oh gee, I just noticed that my type sig is in fact not correct. How
come GHC doesn't complain?

 parseHeader3 bs = do
(x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
(y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
return (x, y)

What happens then if the first BS.readInt return Nothing???

 --or to be clearer without syntactic sugar, that is
 parseHeader3 bs =
(BS.readInt $ BS.dropWhile (not . isDigit) bs)
  = \(x, rest) -
 (BS.readInt $ BS.dropWhile (not . isDigit) rest)
= \(y, _) -
   return (x, y)

 Isaac



 Paulo J. Matos wrote:
  On Dec 23, 2007 12:32 PM, Paulo J. Matos [EMAIL PROTECTED] wrote:
  Hello all,
 
  It is either too difficult to get two integers of a bytestring, in
  which case something should be done to ease the process or I should
  learn much more Haskell. I guess the latter is the correct guess.
 
  I have a bytestring containing two naturals. I was to get them as
  efficiently as possible. Here's my code:
 
  Just tried a better one, what do you think of this:
  parseHeader2 :: BS.ByteString - (Int, Int)
  parseHeader2 bs =
  case (BS.readInt $ BS.dropWhile (not . isDigit) bs) of
Nothing - error Couldn't find first natural.
Just (x, rest) -
case (BS.readInt $ BS.dropWhile (not . isDigit) rest) of
  Nothing - error Couldn't find second natural.
  Just (y, _) - (x, y)
 
  parseHeader :: BS.ByteString - (Int, Int)
  parseHeader bs =
  let first = BS.readInt $ BS.dropWhile (not . isDigit) bs
  in
if(isNothing first)
then
error Couldn't find first natural.
else
let second = BS.readInt $ BS.dropWhile (not . isDigit) $
  snd $ fromJust first
in
  if(isNothing second)
  then
  error Couldn't find second natural.
  else
  (fst $ fromJust first, fst $ fromJust second)
 
  This seems to work:
  parseHeader $ BS.pack hello 252 359
  (252,359)
 
  Is there a better way?
 
  Cheers,
 
  --
  Paulo Jorge Matos - pocm at soton.ac.uk
  http://www.personal.soton.ac.uk/pocm
  PhD Student @ ECS
  University of Southampton, UK
 
 
 
 







-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Paulo J. Matos
On Dec 24, 2007 11:55 AM, Paulo J. Matos [EMAIL PROTECTED] wrote:
 On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote:
 
  -- this should work too
  parseHeader3 :: BS.ByteString - Maybe (Int, Int)
  --note accurate type signature, which helps us use Maybe failure-monad,
  --although losing your separate error messages

 Oh gee, I just noticed that my type sig is in fact not correct. How
 come GHC doesn't complain?

  parseHeader3 bs = do
 (x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
 (y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
 return (x, y)

 What happens then if the first BS.readInt return Nothing???


Ok, got it, I'm not returning a maybe. That's it then.
Still, the first question remains... what happens to (x, rest) if
BS.readInt returns Nothing.

-- 
Paulo Jorge Matos - pocm at soton.ac.uk
http://www.personal.soton.ac.uk/pocm
PhD Student @ ECS
University of Southampton, UK
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Chaddaï Fouché
2007/12/24, Paulo J. Matos [EMAIL PROTECTED]:
 On Dec 24, 2007 11:55 AM, Paulo J. Matos [EMAIL PROTECTED] wrote:
  On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote:
  
   -- this should work too
   parseHeader3 :: BS.ByteString - Maybe (Int, Int)
   --note accurate type signature, which helps us use Maybe failure-monad,
   --although losing your separate error messages
 
  Oh gee, I just noticed that my type sig is in fact not correct. How
  come GHC doesn't complain?
 

Your type is correct.

   parseHeader3 bs = do
  (x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
  (y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
  return (x, y)
 
  What happens then if the first BS.readInt return Nothing???
 

 Ok, got it, I'm not returning a maybe. That's it then.
 Still, the first question remains... what happens to (x, rest) if
 BS.readInt returns Nothing.


Your function return a Maybe (Int,Int), (x,y) is of type (Int,Int).
If readInt return a nothing, the whole funtion will return a Nothing
per (=) instance definition.

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


Re: [Haskell-cafe] Re: Printing and Referential transparency excuse

2007-12-24 Thread Cristian Baboi
On Mon, 24 Dec 2007 11:27:11 +0200, apfelmus [EMAIL PROTECTED]  
wrote:



Cristian Baboi wrote:



 How can I define a function to do the inverse operation ?
  g :: String - ( a - b )
 This time I cannot see how referential transparency will deny it.
What's the excuse now ?


The new excuse is that a better name for  g  is



   full-fledged-compiler :: String - (Int - Int)


(the function returned by  g  better not have a polymorphic type). Which  
programming language should the argument  String  be written in?


Cobol, what else ?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Printing and Referential transparency excuse

2007-12-24 Thread Chaddaï Fouché
2007/12/24, Cristian Baboi [EMAIL PROTECTED]:
 On Mon, 24 Dec 2007 11:27:11 +0200, apfelmus [EMAIL PROTECTED]
 wrote:

  Cristian Baboi wrote:

   How can I define a function to do the inverse operation ?
g :: String - ( a - b )
   This time I cannot see how referential transparency will deny it.
  What's the excuse now ?

It seems to me that referential transparency as well as the
executable don't embed it's source aren't simple excuses, though you
don't seem to understand that Haskell isn't an interpreted language...

Similarly, the languages that offer an eval() as it is mostly called
are always interpreted, most other languages push this capability (if
they have it at all) on libraries, in Haskell you can try to use
hs-plugins for example.

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


Re: [Haskell-cafe] FW: Treating command-line arguments as a Haskell expression

2007-12-24 Thread Yitzchak Gale
Simon Peyton-Jones:
 Would someone familiar with the command-line-parsing libraries
care to help Krassimir?

I agree with Max that it looks like the problem is
not doing any fancy command-line parsing
(if that is indeed the issue, then please post more
information about what the problem is).
Rather, how to run a function whose name
and arguments are given as strings from
the command line.

Max gave one answer. Another approach,
if appropriate, would be to use GHCi.
You could do that using the GHC API:

http://haskell.org/haskellwiki/GHC/As_a_library

(search for runStmt)

Or you could do it using GHCi from the command line
and the shell. This is a bit of a hack, but you can get it
working in minutes, without installing anything extra.
Here's how:

The trick is to pass information into GHCi via
environment variables, using the .ghci file and
the :def command.

Place something like the following in the file .ghci
in the same directory with your program:

:def getEnv 
(\[v,e]-System.Environment.getEnvironment=return.maybe((concat[let
,v,=]++).show).lookup e).words
:getEnv func FUNC
:getEnv args ARGS
:def run const(return$unwords[func,args])
:run
:quit

(Watch out for word-wrap in this email message - there needs
to be a space after the word let , and every line begins
with :)

Write a simple shell script that arranges for the
name of the function and arguments to be in
the environment variables FUNC and ARGS,
and then calls ghci. Something like this
(assuming you are on something Unix-like):

#!/bin/bash

export FUNC=$1
shift
export ARGS=$*
ghci YourProgram.hs

This obviously would have to be tweaked to
your specific needs. For example, you'll get
the GHCi welcome message at the beginning
of your output. So your shell script will have
to filter that out if it is not acceptable.

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


Re: [Haskell-cafe] Functions are first class values in C

2007-12-24 Thread Antti-Juhani Kaijanaho
On Mon, Dec 24, 2007 at 02:12:30PM +0300, Miguel Mitrofanov wrote:
  It is true, however, that preprocessing used to be (in pre-standard
  days) separate from the language.  This has not been true for decades.
 
 Well, I've seen cpp to be used as a preprocessor not for C sources but for 
 something else.

And I'm sure you've heard people cursing cpp for being too C centric :)
In any case, it doesn't matter.  The question was, if the C preprocessor
was part of the C language, not whether C is the only thing it's used
for.

-- 
Antti-Juhani Kaijanaho, Jyväskylä, Finland
http://antti-juhani.kaijanaho.fi/newblog/
http://www.flickr.com/photos/antti-juhani/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FW: Treating command-line arguments as a Haskell expression

2007-12-24 Thread Sterling Clover
As the previous answers show, hooking dynamic evaluation, or a subset  
thereof, into Haskell is not a particularly easy task. If this is  
just a program to get up-and-running with understanding Haskell,  
probably best not to delve into this sorts of stuff? A simpler  
solution, albeit one which requires some boilerplate, would be to  
ensure that either all the functions you dispatch to call getArgs  
themselves (i.e. are of type IO ()) or simply take a list of  
remaining parameters (i.e. are of type [String] -IO ()) and then  
pull them out of either a list or a map. Something resembling this  
approach is, for example, here: http://haskell.org/haskellwiki/ 
Simple_unix_tools


--S

P.S. using Template Haskell to solve this would be a fairly  
interesting exercise as well, I suspect.

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


Re: [Haskell-cafe] FW: Treating command-line arguments as a Haskell expression

2007-12-24 Thread Neil Mitchell
Hi

 I want to call a function from within Haskell module so that the name
 of this function corresponds to my first command-line argument and the
 rest rest of the  command-line arguments are would become themselves
 the argument to this function.

While you can do this, you probably don't actually want to.

You probably have one of two scenarios in mind:

1) You want to test the program. Use ghci or hugs for this, which lets
you type in expressions and then evaluates them.

2) You only intend their to be a subset of functions which can be
invoked. With higher order functions this is easy:

functions = [(foo,foo), (bar,bar)]

main = do
   (name:cmds) - getArgs
   case lookup name functions of
 Nothing - putStrLn Function not found
 Just f - f cmds

Thanks

Neil

Note to the mailing list: When someone says it is their first week of
Haskell, answers should probably include phrases like pattern match
or higher order - not Template Haskell, hs-plugins, HList, GADT's
etc!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Isaac Dupree

Paulo J. Matos wrote:

On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote:

-- this should work too
parseHeader3 :: BS.ByteString - Maybe (Int, Int)
--note accurate type signature, which helps us use Maybe failure-monad,
--although losing your separate error messages


Oh gee, I just noticed that my type sig is in fact not correct. How
come GHC doesn't complain?


well, it is correct for Haskell if you want program failure for parse 
failure... it's just not a _total_ function unless you use Maybe (which 
determines whether you can have the code that uses parseHeader decide 
what to do in the case of a failure)





parseHeader3 bs = do
   (x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
   (y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
   return (x, y)


What happens then if the first BS.readInt return Nothing???


--or to be clearer without syntactic sugar, that is
parseHeader3 bs =
   (BS.readInt $ BS.dropWhile (not . isDigit) bs)
 = \(x, rest) -
(BS.readInt $ BS.dropWhile (not . isDigit) rest)
   = \(y, _) -
  return (x, y)


when the first one returns Nothing, the whole expression becomes Nothing 
without examining the later parts of computation (as Chaddaï said)


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


Re: [Haskell-cafe] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Brandon S. Allbery KF8NH


On Dec 24, 2007, at 13:18 , Isaac Dupree wrote:


Paulo J. Matos wrote:
On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED]  
wrote:

parseHeader3 bs = do
   (x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
   (y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
   return (x, y)

What happens then if the first BS.readInt return Nothing???
when the first one returns Nothing, the whole expression becomes  
Nothing without examining the later parts of computation (as  
Chaddaï said)


One thng that's not obvious here is that pattern match failure  
translates to a call to fail, which in the definition of Monad for  
Maybe becomes Nothing.


(Hm.  Isaac:  I thought that translation only happened for the do  
sugar, and in the direct case you must do it yourself or Haskell  
raises the incomplete pattern match exception?)


--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTECTED]
system administrator [openafs,heimdal,too many hats] [EMAIL PROTECTED]
electrical and computer engineering, carnegie mellon universityKF8NH


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


Re: [Haskell-cafe] Peyton Jones' Beautiful Concurrency .. i.e. Software Transactional Memory ...

2007-12-24 Thread Ryan Ingram
{- compile with ghc --make stm.hs -}
module Main where
import Control.Concurrent.STM

type Account = TVar Int

withdraw :: Account - Int - STM ()
withdraw acc amount = do
bal - readTVar acc
writeTVar acc (bal - amount)

main = do
account - atomically $ newTVar 100
atomically $ withdraw account 50
value - atomically $ readTVar account
print value


On 12/23/07, Galchin Vasili [EMAIL PROTECTED] wrote:

 Hello,

  My brain is a out to lunch. I have read the paper Beautiful
 Concurrency (as well as a bunch of gaming papers regarding multi cores).
 I am playing with the Account example in the paper. In the paper, the
 alias type Account = TVar Int is used.  I want to actually apply the
 function withdraw to an example Account parameter. I keep getting a type
 check error. Can someone give me a concrete example of

  withdraw ..

 ??

 Kind regards, Vasya


 ___
 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] Re: Comments on reading two ints off Bytestring

2007-12-24 Thread Isaac Dupree

Brandon S. Allbery KF8NH wrote:


On Dec 24, 2007, at 13:18 , Isaac Dupree wrote:


Paulo J. Matos wrote:

On Dec 23, 2007 12:44 PM, Isaac Dupree [EMAIL PROTECTED] wrote:

parseHeader3 bs = do
   (x, rest) - BS.readInt $ BS.dropWhile (not . isDigit) bs
   (y, _) - BS.readInt $ BS.dropWhile (not . isDigit) rest
   return (x, y)

What happens then if the first BS.readInt return Nothing???
when the first one returns Nothing, the whole expression becomes 
Nothing without examining the later parts of computation (as Chaddaï 
said)


One thng that's not obvious here is that pattern match failure 
translates to a call to fail, which in the definition of Monad for 
Maybe becomes Nothing.


(Hm.  Isaac:  I thought that translation only happened for the do 
sugar, and in the direct case you must do it yourself or Haskell raises 
the incomplete pattern match exception?)


Tuple-matching never fails (except for _|_) -- there's only one 
constructor.  In this case it's only the intrinsic failure of 
BS.readInt.  You're thinking of something like


 do
   [a,b] - readListOfInts foo
   return (a+b)
--readListOfInts is a function I made up :: String - Maybe [Int]

which can fail
(1) if readListOfInts returns Nothing
(2) because of the do-notation, also if the list doesn't have exactly 
two elements in it.



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


Re: [Haskell-cafe] Comments on reading two ints off Bytestring

2007-12-24 Thread Conal Elliott
To clean up even more, use StateT B.ByteString Maybe.  Then the ByteString
threading will be invisible, leading to just liftM2 (,) readI readI, for
suitably defined readI.

On Dec 23, 2007 6:45 AM, Bryan O'Sullivan [EMAIL PROTECTED] wrote:

 Paulo J. Matos wrote:

  I guess the latter is the correct guess.

 Good guess!

 You can take advantage of the fact that the Maybe type is an instance of
 the Monad typeclass to chain those computations together, getting rid of
 all of the explicit case analysis.

 import qualified Data.ByteString.Char8 as B
 import Data.Char (isDigit)

 readTwoInts :: B.ByteString - Maybe ((Int, Int), B.ByteString)
 readTwoInts r = do
  (a, s) - B.readInt . B.dropWhile (not . isDigit) $ r
  (b, t) - B.readInt . B.dropWhile (not . isDigit) $ s
  return ((a, b), t)

 Let's try that in ghci:

  *Main readTwoInts (B.pack hello 256 299 remainder)
  Just ((256,299), remainder)

 The case analysis is still happening, it's just being done behind your
 back by the (=) combinator, leaving your code much tidier.  (And why
 is there no explicit use of (=) above?  Read about desugaring of do
 notation in the Haskell 98 report.)

 The learning you'll want to do, to be able to reproduce code such as the
 above, is about monads.

 Cheers,

b
 ___
 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] Trouble with types

2007-12-24 Thread Konstantin Vladimirov
Colleagues!

The essence of trouble may be given by code:

[haskell]
module TypeTrouble where

class FirstClass a where
firstFunction :: (SecondClass b) = a - b

class SecondClass a where
secondFunction :: a - Double

data FirstData = FirstData Double

data SecondData = SecondData Double

instance SecondClass SecondData where
secondFunction (SecondData d) = d

instance FirstClass FirstData where
firstFunction (FirstData d) = SecondData d
[/haskell]

I need, the firstFunction of FirstClass types to return a value of a
SecondClass type. For example SecondData for FirstData, but for some
FirstClass ThirdData, some SecondClass FourthData, etc.

GHC 6.8.1 produces an error:

[quote]
typetrouble.hs:17:31:
Couldn't match expected type `b' against inferred type `SecondData'
`b' is a rigid type variable bound by
the type signature for `firstFunction' at typetrouble.hs:4:31
In the expression: SecondData d
In the definition of `firstFunction':
firstFunction (FirstData d) = SecondData d
In the definition for method `firstFunction'
[/quote]

How can I make this idea work?

-- 
With best regards, Konstantin
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trouble with types

2007-12-24 Thread Stefan O'Rear
On Tue, Dec 25, 2007 at 08:11:34AM +0300, Konstantin Vladimirov wrote:
 [haskell]
 module TypeTrouble where
 
 class FirstClass a where
 firstFunction :: (SecondClass b) = a - b
 
 class SecondClass a where
 secondFunction :: a - Double
 [/haskell]
 
 I need, the firstFunction of FirstClass types to return a value of a
 SecondClass type. For example SecondData for FirstData, but for some
 FirstClass ThirdData, some SecondClass FourthData, etc.

The problem, as is often the case, is that that which is unwritten does
not resolve in the way you expect and require it to.

FirstClass' true signature is

class FirstClass a where
firstFunction :: a - forall b. SecondClass b = b

That is to say, any implementation of firstFunction must work for ANY
instance of SecondClass.  But you want SOME, not ANY.  And SOME
(normally notated exists tvar. tspec) is not supported in any known
dialect of Haskell.  It's possible to get fairly close with GHC
Haskell's fundeps / type families:

-- fundep version
class SecondClass b = FirstClass a b where
firstFunction :: a - b
-- type family version
class SecondClass (Cod a) = FirstClass a where
type Cod a :: *
firstFunction :: a - Cod a

It is almost certainly possible to accomplish your goals within
standard Haskell, but the best approach is not obvious at the current
level of detail.

Stefan


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


Re: [Haskell-cafe] Trouble with types

2007-12-24 Thread Antoine Latter
On Dec 25, 2007 12:11 AM, Konstantin Vladimirov
[EMAIL PROTECTED] wrote:

 class FirstClass a where
firstFunction :: (SecondClass b) = a - b


snip!


 instance FirstClass FirstData where
firstFunction (FirstData d) = SecondData d

The problem is that the type of firstFunction as producing a result of
type 'b', where 'b' is *any* type inahbiting the typeclass
SecondClass.

Your definition of firstFunction can produce only *one* of the
inhabitants of SecondClass.  You'd think this would be okay, seeing
as there is only one member of the typeclass, but because anyone can
come along and add a new typeclass instance, you're definition of
firstFunction needs to account for that.

If you're type-classes only ever have one instance, maybe it's easier
to not use them, and go with:

 convert :: FirstData - SecondData
 convert (FirstData d) = SecondData d

But I'm not sure if that suggestion is at all helpful.

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