Re: [Haskell-cafe] formal methods functional programming

2006-01-15 Thread Hal Daume III
I confess I haven't really been following this discussion, but a friend of 
mine has a recent paper that might be of interest (though it deals with ML 
rather than Haskell)...

  http://math.andrej.com/2005/04/09/specifications-via-realizability/

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Problems with square root...

2005-12-21 Thread Hal Daume III
 Sigh... never fails. Spend an hour trying to solve a problem, and a 
 minute after you write to the list you find the solution. I need 
 brackets around sqrt. I'm surprised though. I don't understand why it 
 dosn't work without brackets.

because x y z parses as (x y) z, so round sqrt 2 parses as (round 
sqrt) 2 and round sqrt doesn't make sense.  x(y) doesn't mean 
necessarily apply y to x as it does in C.  parens only are used as they 
are in math to separate stuff.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Re: Tutorial uploaded

2005-12-21 Thread Hal Daume III
  As a newbie... I'll agree with Robin. I /did/ think that IO in
  Haskell was probably very difficult because it's covered in page 94.
  I skimmed through YAHT and IO is covered wyyy deep into the
  document. I haven't read that section yet, but there is a lot of
  content and to me it looked like it must be something difficult. I
  guess/hope that when I get around to reading it I'll find out that
  it's not as scary as it looks.
 
 Rest assured it is dead simple. Really. I would even argue that it is a 
 lot simpler than in many other languages.

I agree.  It's on page 31 in YAHT, and 1-11 are getting started with 
Hugs and so on.  One of the whole points of YAHT is to introduce it 
early.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Proposal for a first tutorial.

2005-12-20 Thread Hal Daume III
  Daniel -- can you tell me what was missing from YAHT that wasn't 
  sufficient for starting to use Haskell?  It was really intended to solve 
  these problems, at least partially, so if it's missing out, I'd like to 
  fix it!
 
 I haven't read it. I refuse to give out personal information to read a 
 tutorial.

I don't mean to be obnoxious, but given:

 This is a real problem for Haskell. I expect that a lot of people try 
 Haskell and give up because they can't even write the simplest function. 

and

 Thank you. I did find that page, and it was very easy to find. The 
 problem is that the content of that page, and its links, didn't show me 
 how to write a Haskell program (like you did).

and

 Well, I tried all three (Hugs, GHCI, GHC). The problem is that the 
 tutorials I found didn't tell me how to run a Haskell program once it 
 was written.

and

 Any of the following would be an apt solution:

 1) Update the tutorials linked to tell the user how to run a program.

and

 You see, as a site visitor, I have to assume that the tutorials you are 
 giving me are the ones you expect I should read.

and

 There's no way for a new user to figure out how to successfully run 
 the simplest Haskell program.

and

 I just Googled for Introduction to C. The first link was:
http://www.le.ac.uk/cc/tutorials/c/
 It includes a brief section on both MS Visual C++ and the Unix CC.

The fifth link for Haskell Tutorial is the pdf version of YAHT.

and

 I do suggest that the Learning Haskell page could be improved with a 
 brief (couple of paragraph) tutorial to get someone through Hello world. 
 Or perhaps update the tutorials to say that.

rant

(Please feel free to skip down to /rant)

It seems a bit unfair to say that there are no good ways of learning 
information about Haskell.  Yes, I'm shamelessly plugging my own tutorial, 
but that's because I think it's pretty good.  It also answers all of the 
questions you've posted to the list, I believe.  These sorts of questions 
come up *all the time*.  A quick perusal of the mailing list archives will 
show that.  This is part of the whole motivation for putting YAHT 
together: so all the nice Haskell people who do spend their time answering 
these questions repeatedly don't have to!

So basically what you're saying is: someone who wants to learn Haskell but
doesn't want to fill out a 10 second form can't find the information to do
so.  There's no requirement that the form be filled out correctly -- you
can enter whatever invalid information you want.  Also, as you can see
above, just searching for Haskell Tutorial will turn you up with a PDF
version freely.  If you spend another 30 seconds, you can find a version
translated into Portuguese or Chinese, if you prefer that.

I know your argument was that you should *have* to do that work, but it is
*your* choice not to fill out a silly little form that means nothing, and
if you don't want to do that, then you can find another way.  The tutorial
is mirrored like 100 times and it's not hard to find one of those.  The
amount of effort to find a non-formed version is  than the effort to
send lots of emails to the mailing list asking questions answered in the
first chapter.

/rant

But, yes, here's the solution:

  haskell.org people, please just link to the .pdf

I think this solution should please everyone.

 - Hal

p.s., I apologize for the rant.  Although I don't spend my time mailing on 
this list recently, I still read it regularly and have updated YAHT 
several times in the past year to improve it via user comments.  And 
everyone here has always been really friendly to me and other beginners, 
which is one of the many reasons why I like Haskell so much.  I just felt 
that the above quoted lines (among others) were a misrepresentation of the 
situation, and given that I put a non-trivial amount of effort into making 
the situation better, I got somewhat annoyed.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume


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


Re: [Haskell-cafe] Writing functions in Haskell.

2005-04-29 Thread Hal Daume III
 Hal:
 Char.toUpper and Char.isLower in Chapter 3 seem to be a perennial
 stumbling block for Hugs users -- could you suggest that Hugs users
 load Char and just say toUpper and isLower instead?

I just added a note about this :).  Though the tutorial is mirrored in so 
many places by now, I'm sure the questions will still arise.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Writing functions in Haskell.

2005-04-28 Thread Hal Daume III
Try:

module Test where
import Char
...


then you don't have to load it in Hugs.  When you load it, I think (could 
be wrong, I'm not a big hugs guy) it's clearing the fact that you loaded 
Test.



On Thu, 28 Apr 2005, Daniel Carrera wrote:

 Alright, I have what I believe must be a simple question. As one of the 
 exercises for the Haskell tutorial I got I have to implement an 
 alternative to the 'map' function.
 
 This is what I have:
 
 -
 my/prompt $ cat Test.hs
 module Test
  where
 
 my_map p [] = []
 my_map p (x:xs) = p x : my_map p xs
 my/prompt $ hugs
 
 [snip]
 
 Hugs.Base :l Test
 Test :also Char
 Char map toUpper Hello
 HELLO
 Char my_map toUpper Hello
 ERROR - Undefined variable my_map
 -
 
 I can define other functions now (e.g. Fibonacci, length of a list). So 
 I'm not sure why I'm doing wrong here. Even if my syntax is wrong in 
 some way, the function should be defined.
 
 I would be grateful if anyone could point out my error.
 
 Cheers,
 Daniel.
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Re: Processing of large files

2004-11-03 Thread Hal Daume III
you can steal my version of finitemap:

  http://www.isi.edu/~hdaume/haskell/FiniteMap.hs

which is based on the GHC version, but supports strict operations.  
the strict version of function f is called f'.  i've also added some ops i 
thought were missing.

On Wed, 3 Nov 2004, Scott Turner wrote:

 On 2004 November 03 Wednesday 09:51, Alexander Kogan wrote:
  merge' a x = (addToFM (+) $! a) x 1
  is not strict.
  Can I do something to make FiniteMap strict?
  Or the only way is to make my own StrictFiniteMap?
 
 You can replace
 addToFM_C (+) a x 1
 with
 let a' = addToFM_C (+) a x 1 in 
 lookupFM a' x `seq` a'
 or you can generalize that into your own strict version of addToFM_C.  It's a 
 little ugly, but probably gets the job done.
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: [Haskell-cafe] Writing binary files?

2004-09-11 Thread Hal Daume III
There's a Binary module that comes with GHC that you can get somewhere (I 
believe Simon M wrote it).  I have hacked it up a bit and added support 
for bit-based writing, to bring it more in line with the NHC module.  
Mine, with various information, etc., is available at:

  http://www.isi.edu/~hdaume/haskell/NewBinary/

On Sat, 11 Sep 2004, Ron de Bruijn wrote:

 Hi,
 
 I would like to write and read binary files in
 Haskell. I saw the System.IO module, but you need a
 (Ptr a) value for using that, and I don't need
 positions. I only want to read a complete binary file
 and write another binary file. 
 
 In 2001 somebody else came up with the same subject,
 but then there wasn't a real solution. Now, 3 years
 later, I can imagine there's *something*. 
 
 What's that *something*?
 
 Regards, 
   Ron
 
 
 
   
 __
 Do you Yahoo!?
 New and Improved Yahoo! Mail - Send 10MB messages!
 http://promotions.yahoo.com/new_mail 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: type of (/) ?

2003-12-09 Thread Hal Daume III
 ERROR U:\slav\FP\Avg.hs:11 - Type error in application
 *** Expression : accum list / length list
 *** Term   : accum list
 *** Type   : Float
 *** Does not match : Int
  
 Why accum list should match to Int?
 When I try to replace (length list) with number - it works.

length :: [a] - Int   -- this is your problem

use genericLength :: Num k = [a] - k instead

 
 my_avg list =  (accum list) / 5 --works fine
 

This works because '5' is translated to 'fromInteger 5', which can be a 
Float as desired.

 xx = 5
 my_avg list =  (accum list) / xx --doesn't work
 -- same message as above

This doesn't work because defaulting occurs and xx is given type Integer.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Resolving Ambiguous Types

2003-11-20 Thread Hal Daume III
This is the closed world assumption that you want to make.  Basically
the problem is, what if you write 'bar foo' and expect to get Zero, but
someone else writes another instance of Barable and imports your code.  
What should happen?  The open world assumption (the opposite) says that 
you never assume that you have all possible instances, and this is the 
assumption Haskell makes.

On Thu, 20 Nov 2003, Jared Warren wrote:

 Thanks to Tom Pledger, Brian Boutel, and Keith Wansbrough for helping me
 with my last type problem, but now I have another one: :)
 
 -
 
 I understand why it is impossible to infer the intermediate type in
 `show . read`, but I was hoping someone could help me grasp why this
 (and only this) is problematic:
 
  class Fooable a where foo :: a
  instance Fooable Char where foo = '0'
 
  class Barable a where bar :: a - String
  instance Barable Char where bar = const Zero
 
 `bar foo` generates an ambiguous type error; but anyone can
 deterministically see that there is only one intermediate type that
 satisfies the classes. Why can't the compiler figure it out?
 
 Are there any compiler directives, language extensions, or Template
 Haskell tricks I can use to make the compiler smarten up? (The
 requirements of my project rule out explicit type signatures.) If not,
 does anyone know if Chameleon's type system can avoid this problem?
 
 Thanks for your help, 
 ~ Jared Warren [EMAIL PROTECTED]
 Computing Science, Queen's University
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: record matching syntax forensics

2003-11-13 Thread Hal Daume III
Google for 'punning'.  It was removed from Haskell (I don't know why -- 
look at the list archives).  But that used to be legal.

On Thu, 13 Nov 2003, John Meacham wrote:

 so I noticed DrIFT was generating code like
 
 f Foo{bar} = ...
 as seemingly a shorthand for
 f Foo{bar = bar} = ...
 
 which does not seem to work with current compilers. I fixed this in
 2.0.2 but was curious why it was generating code like that in the first
 place. it appears to be illegal looking at the haskell report and I was
 uncertain who wrote the derive rules in the first place so thought I
 would ask here.
 John
 
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Programming style (or: too clever by half?)

2003-11-12 Thread Hal Daume III
this is the same as the function 'fromMaybe' in Data.Maybe.  the 'maybe' 
function in that library is also incredibly useful.

On Wed, 12 Nov 2003, Andrew Pimlott wrote:

 On Wed, Nov 12, 2003 at 02:54:32PM +, Graham Klyne wrote:
  I just spotted a possible idiom for something that seems to pop up from 
  time to time:
  
 foldr const
  
  But I can't help feeling that this code is perversely obscure.
 
 Clever.  I usually end up with something like
 
 listToMaybe list `orMaybe` default
 
 orMaybe (Just x) _  = x
 orMaybe Nothing  y  = y
 
 Andrew
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Trying to understand tuples and lists

2003-11-05 Thread Hal Daume III
Based on this and your previous post, I think you're not understanding 
what -/do are for.  I think you'll be better off forgetting them 
completely and using 'let/in' for now.

let (x,y) = head [...]
in  ...

is what you want.

On Wed, 5 Nov 2003, Karthik Kumar wrote:

 Hi, 
 I have a list of  tuples ( characters and numbers ) . 
 
 say, [('a', 1), ('b', 2)]
 I want to extract 'a' and 1 separately . 
 
 (x,y) - head  [('a', 1), ('b', 2)]
 
   This doesnt work but my idea is to get x contain the value 'a' and y
 contain the value 1 as the first tuple in the list. 
Which is the right way of doing this.  Thanks for your help. 
 
 Cheers
 Karthik.
 
 __
 Do you Yahoo!?
 Protect your identity with Yahoo! Mail AddressGuard
 http://antispam.yahoo.com/whatsnewfree
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Another Newbie question :)

2003-11-05 Thread Hal Daume III
Keith is entirely correct.

 You can see this from the definition of foldr:
 
 foldr :: (a - b - b) - b - [a] - b
 foldr f z   []   = z
 foldr f z (x:xs) = f x (foldr f z xs)
 
 where clearly every [] is replaced by z and every : by f.

I had heard this before when I was first beginning and didn't really find 
it clear :).  I think if you write foldr with f in infix notation it's a 
bit more clear:

 foldr f z   [] = z
 foldr f z   (x:xs) = x `f` foldr f z xs

or even write the second line as

 foldr f z   (x:xs) = x `f` xs'
   where xs' = foldr f z xs

I think in this case it's a bit more clear how f is replacing the :.

 - Hal


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


Re: Data types basics

2003-11-04 Thread Hal Daume III
Hi again,

On Wed, 5 Nov 2003, Patty Fong wrote:

 Hi to anyone reading this. i'm still strugling a bit with data type
 declarations.
 
 The was i understand it is that if i delcare a new data type:
 
 data myType = myType a | b | c

This isn't entirely correct.  The names of types have to begin with 
capital letters, as do constructors (more later).  So you would need this 
to be:

data MyType = MyType A | B | C

where A is an existing type.

This type now has three constructors:

  MyType :: A - MyType
  B :: MyType
  C :: MyType

It's perhaps a bit easier to understand when the names are different.

When we say:

data Foo = Bar Int | Baz String

this means that a Foo is of one of two forms (the | can be read as 
disjunction).  A value of type Foo is either of the form Bar x for some 
x which is an Int or Baz y for some y which is a String.

Bar and Baz are called constructors because they take arguments and 
construct a Foo.  So, in this case,

  Bar :: Int - Foo
  Baz :: String - Foo

are the two constructors.

Of course, you have have any number of constructors and each can have any 
number of arguments.

data Foo = Bar | Baz Int | Bazaa String Bool

Now there are three constructors:

  Bar :: Foo
  Baz :: Int - Foo
  Bazaa :: String - Bool - Foo

they can be recursive:

data Foo = Bar | Baz Int Foo

  Bar :: Foo
  Baz :: Int - Foo - Foo

and can have type variables, for instance:

data Foo a = Bar | Baz a

here, something of type Foo a is either of the form Bar or of the form 
Baz x for some x which is of type a.  This has constructors:

  Bar :: Foo a
  Baz :: a - Foo a

I hope this sheds some light on the issue...


-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Help ? :)

2003-11-03 Thread Hal Daume III
Hi,

You're pretty close, actually.  In general, remember the following:

'type' introduces a type synonym, which means that you're just renaming an
existing type, not creating a new one.  this means that you don't need
constructors.

'data' means that you're defining a new type; in order to do this, you
need to specify constructors.

for instance:

 type Position = Int

here, we've just given Int a new name, Position.

 data Bool = True | False

here we've defined a new type (Bool) with two constructors, True and
False.

or, if the constructors take arguments:

 data PairOfInts = PairOfInts Int Int

here, the type is called PairOfInts and the constructor is called
PairOfInts; the constructor takes two ints as arguments.

HTH,

 - Hal

--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

On Mon, 3 Nov 2003, Patty Fong wrote:

 
 Hello, I'm fairly new to haskell and functional programming and i'm still
 trying to get my head around certain concepts.
 
 I'm wondering if anyone can help me convert this abstract syntax into
 Haskel data and type declarations:
 
 prolog ::= (assertion .)*?xml:namespace prefix = o ns =
 urn:schemas-microsoft-com:office:office /
 
 assertion :: = structure | rule
 
 rule ::= structure :- structure(, structure)*
 
 structure ::= name [“(“ term (“,” term)* “)”]
 
 term ::= number | variable | structure
 
 variable ::= name
 
  
 
 name is simply a String and number an Int
 
  
 
 This was my attempt feeble attempt but i ran into numerous errors... :
 
  
 
 type Prolog = Assertion
 
 data Assertion = Structure | Rule
 
 type Rule = Structure Structure (Structure)
 
 type Structure = Name [ Term (Term)]
 
 data Term = Number | Variable | Structure
 
 type Variable = String
 
 type Name = String
 
 type Number = Int
 
  
 
 Any help would be appreciated
 
 TIA
 
 Patrick.
 
 
 
 Hot chart ringtones and polyphonics. Click here.
 

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


Re: Doubt regarding Types

2003-11-03 Thread Hal Daume III
Hi,

On Mon, 3 Nov 2003, Karthik Kumar wrote:
 -- Convert a string to an integer.
 -- This works perfectly fine. 
 atoi  :: [Char] - Int
 atoi (h : []) = if isDigit h then digitToInt h else 0
 atoi (h : t) =  if isDigit h then digitToInt h * ( 10 ^ length t) +
 atoi t else 0

you can use read for this.

 -- validateBoardSize
 -- To validate the board size
 validateBoardSize   :: Int - Bool
 validateBoardSize d = (d == 9 || d == 13 || d == 19 ) 

this looks fine

 getBoardSize :: IO Bool 
 -- TODO : What could be the type of getBoardSize 
 getBoardSize  = do c - getLine
validateBoardSize ( atoi c ) 
 
 ERROR test1.hs:21 - Type error in final generator
 *** Term   : validateBoardSize (atoi c)
 *** Type   : Bool
 *** Does not match : IO a

this is telling you something important.  it's saying that the final 
generator, validateBoardSize (atoi c) has type Bool, but it's expecting 
it to have type IO something.  You need to lift the pure Bool value into  
IO by saying return:

 getBoardSize = do
c - getLine
return (validateBoardSize (read c))

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Haskell Asignement not working

2003-10-29 Thread Hal Daume III
This looks like a syntax error to me.

On Tue, 28 Oct 2003, Rachel Reid wrote:

 bLine n )

What is the close parenthesis for (or is this a character encoding 
issue?)?  Definitely shouldn't be there...I'm guessing it should be 
something like 'k' or the like.

  |n==0 = )

Same comment.

  |n0 = `sideBySide` sb (bLine (n-1))

The `foo` notation is used to make a function (in your case sideBySide) 
into an infix function, so you can write x `foo` y.  but in your case 
you're not using it infix, so you don't want the ``s.

HTH,

 - Hal

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: random numbers

2003-10-24 Thread Hal Daume III
Hi!

 I'm very much a beginning programmer, studying Haskell. I have two
 questions -

Great!  Beginners are very welcome!

 Firstly, I am trying to generate random numbers in Haskell, but although I
 have found a 'random' library on www.zvon.org, I don't really know how to
 include library functions, and the documentation given doesn't really tell
 me the effective difference between all the functions provided in the
 library. In another interesting development, I couldn't find any mention
 of this library in haskell.org's list of libraries.

You want to put 'import Random' at the top of your program.  A bit of a 
warning, though: using random numbers isn't entirely straightforward in 
Haskell, due to the fact that it is a pure language (which means that you 
cannot have a function like 'randomInt :: () - Int' which will return a 
random integer -- this is because any call to this function must always 
return the same result).

 Secondly, but perhaps more importantly, is there a more 'beginnerish' list
 that I should be addressing this to? I've been following discussions on
 this one and they don't seem to be at quite this level.

This list is appropriate.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: parsing a file line by line

2003-10-16 Thread Hal Daume III
Take a look at the functions lines and words.

On 16 Oct 2003, Anagha   wrote:

 Hi ,
I am a new bie to haskell.
I need to read a file and get it contents line by line and then eventually word by 
word. 

I have written the code to read a file , but the returned value is all the lines in 
the file.
How do I parse this whole text message ( contents of the file) into individual lines ( 
that is parsing / splitting the whole text to get me one line at a time. 
Also once I get the individual line, I o parse it word by word.
I have a start  on this thing. by using the line function in haskell, but I have not 
managed to write it successfully.
Can anyone help me in this.

Below is the code to read a file. 
fileFun :: IO ()

fileFun = do
  putStr Please input a file name: 
  fname - getLine
  contents - readFile fname

How do I split the data returned in contents( Contents contains all the text in the 
file, which is given as input)

Thanks
Anagha







-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: putStr

2003-10-14 Thread Hal Daume III
In addition to what Keith said, it's also guarenteed that the trace is
evaluated as soon as the function is entered.

 - Hal

On Tue, 2003-10-14 at 02:36, Ferenc Wagner wrote:
 Hal Daume III [EMAIL PROTECTED] writes:
 
  f1 :: Int - Int
  f1 x 
| trace (The initial value is  ++ show x) False = undefined
| otherwise = f2 x
 
  In general, the 'trace ... False = undefined' thing is
  quite useful
 
 How is it better than
 
  f1 x = trace (The initial value is  ++ show x) $ f2 x
 
 ?
 
 Feri.
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: putStr

2003-10-13 Thread Hal Daume III
In general, you can't, not with these type signatures, since printing 
something is a side effect.

If this is only for debugging purposes, you might try using trace from 
IOExts.  You can use it in a nice fashion like:

 f1 :: Int - Int
 f1 x 
   | trace (The initial value is  ++ show x) False = undefined
   | otherwise = f2 x

In general, the 'trace ... False = undefined' thing is quite useful, but 
note that trace uses unsafePerformIO and very little is guarenteed about 
the output (especially the ordering might be different than you would 
expect...but it's usually fine for debugging purposes).   

On 13 Oct 2003, Jose Morais wrote:

 Hi,
 
   I am trying to something like
 
 f1 :: Int - Int
 f1 x = f2 x
 
 f2 :: Int - Int
 f2 x = 2 * x
 
 
   but before f2 returns its result I'd like it to print something like
 The initial value is  ++ show x.
 
   How could I do this?
 
 
   Thank you
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

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


Re: Type classes and code generation

2003-06-17 Thread Hal Daume III
(Moved to the Cafe)

 Yes, exactly.  Every class is translated to a data type declaration, 
 and every instance is translated to an element of that data type - a 
 dictionary.  (Note that you can't actually write those declarations in 
 Haskell 98 in general, because they can have polymorphic fields; but 
 this is a simple extension to the language).

Keith, could you elaborate on this parenthetical?  Under what
circumstances can you not create the dictionary datatype for a class in
Haskell 98 (where the class itself is H98 :P)?

 - Hal

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


Re: a readFile problem

2003-06-03 Thread Hal Daume III
It would probably be helpful if you were to post the code you have and
explain what part isn't working.  There's a function:

  readFile :: FilePath - IO String
  (FilePath is just a String)

which reads a file.  This should be what you need to solve this
exercise...

 - Hal

--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

On Mon, 2 Jun 2003, Naudts, Guido wrote:

 Hallo, 
 I have the following problem:
 my program asks the user for a command, when the command is executed a
 new command is asked (this is no problem ; an example is in the HUgs
 distribution namely Main.hs in the Prolog example.
 However one of the commands is: read filename
 i.e. read a file and display it. 
 I do not succeed in implementing this. 
 Could anyone give an example of: reading commands in a loop where one of
 the commands is the read command mentionned above. 
 Or is it not possible in Haskell? 
 I have already wated a lot of time on this, so if anyone gives me an
 answer I will be very gratefull.
 Greetings,

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


Re: instance declaration troubles

2003-03-07 Thread Hal Daume III
See my Double Argh message, but other than that, the only way is if you
redefine your Functor class to be a subclass of Get, which means you need
to define your own and cannot use the library one (unless something like
superclass is adopted...there's a recommendation out there for this
somewhere).  You need undecidable instances because in general something
like this is not decidable.  The way that undecidable instances deals with
the problem is that it sets a depth for instance reduction and if this
depth is hit, it just dies.

That said, undecidable instances sound very scary, but they're really
not.  You can google around for a conversation I had with SPJ about this a
while back, but something being an und instance is a compile time
property.  That is, if compilation succeeds, you don't have anything to
worry about and the worst that can happen at compilation time is that
you'll hit the bottom of this stack.

--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

On Fri, 7 Mar 2003, Nick Name wrote:

 Yes, I usually RTFM before posting, but you have misunderstood my
 question (however, thanks for always reading and answering newbie
 questions like mine); what I want to do is the 
 
 instance (Get a) = Functor a where
  fmap f x = mk (ls x = return . map f)
 
 Now, what I mean is: any type in Get class is also in Functor class,
 and I tell you how. But I need undecidable instances! Why? Is there a
 simple way to state this property, that the Get class is a subset of the
 Functor class?
 
 Vincenzo
 
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: speedup help

2003-03-03 Thread Hal Daume III
I think you would get a big speed-up if you got rid of all the rational
stuff and just used:

comb m n = fact m `div` (fact n * fact (m-n))

If that doesn't speed it up enouch, you can of course cache fact m in your
computation and do something like:

sumbn n = sum [ bournoulli i * fm `div` (fn * fact (m-n)) | i - [0..n-1]]
  where fm = fact m
fn = fact n

it is possible that the compiler is inlining the call the comb, in which
case this has already been done for you.  hard to say for sure.  putting
'{-# INLINE comb #-}' might help a lot.

From there, you should probably look at arrays if you can bound n.

--
 Hal Daume III   | [EMAIL PROTECTED]
 Arrest this man, he talks in maths.   | www.isi.edu/~hdaume

On Mon, 3 Mar 2003, Damien R. Sullivan wrote:

 So, I'm having to calculate 'n choose k' an awful lot.  At the moment I've got
 this:
 
 comb :: Integer - Integer - Integer
 comb m 0 = 1
 comb m n = (numerator(toRational (fact m) / toRational (fact n * fact (m-n
  
 where fact is a memoized factorial function.  It's not perfectly memoized,
 though; I use lists, since that's easier by default.  They should be arrays,
 and possibly just changing that would speed comb up a lot.  (Comb is currently
 40% of runtime, fact is 23%.)  But I think it should be possible to speed up
 comb itself, too.
 
 comb is only called from here:
 sumbn n = sum [ bernoulli i * fromIntegral(comb (n+1) i) | i - [0 .. n-1] ]
 
 
 Here was one try:
 
 fcomb :: Integer - Integer - Integer
 fcomb m 0 = 1
 fcomb m n = res 
 where
 res = last * (m-n+1) `div` n 
 last = res
 
 except, obviously, this doesn't work.  I hope it's clear what I'm trying to
 do, or what I would be in a more imperative language -- in C I'd probably have
 some static variable in fcomb.  I figure monads are needed, but I've been
 unable to figure them out enough to apply them here.  Will the monadism
 propagate all the way up and require changing lots of function types?  Bleah.
 I'm using ghc, can I sneak some mutable in here instead?
 
 Any advice?  Also on using arrays, where my parameters come off the command
 line.  I imagine in C++ I'd just precompute a bunch of tables and then just
 use those values in the actual algorithm.
 
 Thanks!
 
 -xx- Damien X-) 
 
 (if you're curious, this is for a class, but not a class on using Haskell.  I
 chose to use Haskell for this assignment after ghc -O, to my surprise,
 outperformed ocaml.  I suspect GMP deserves the real credit, but hey.)
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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


Re: a monadic if or case?

2003-02-20 Thread Hal Daume III
There is now a way to do this :).  What used to be the Haskell Array
Preprocessor is not the Haskell STate Preprocessor (STPP) and it supports
now many things:

  - sugared array reading/writing/updating
  - sugared hash table reading/writing/updating
  - monadic if
  - monadic case

Get it from http://www.isi.edu/~hdaume/STPP/

using stpp, you would write monadic case expressions as:

 mcase fun of
   Nothing - ...

etc, just as you wanted :).  mif works the same way (the 'm' prefix was
chosen to look like 'mdo').

Of course, it still supprots array reading/writing, such as:

  do a - newArray (0,100) 0
 a[|5|]  - 7
 a[|6|]  - 8
 a[|6|] - a[|5|] * 2 + a[|6|]

furthermore, it supports hash table reading/writing (based on the hash
table implementation found at http://www.isi.edu/~hdaume/haskell/Util), as
in:

  do ht - emptyHT
 ht{|hello|} - goodbye
 print ht{|hello|}

All of this works both in the IO monad and the ST monad.

Comments/Suggestions/Bug reports to me please.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

  mp - fun
  case mp of
Nothing - deal with error
Just p - do something with p
  
  where it would be much nicer to be able to just use
  
  caseM fun of
Nothing - deal with error
Just p - do something with p
  
  which would avoid confusion when reading the code as to whether the value
  mp may be used later in the function.  Any ideas how to do something like
  this?

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



Re: Exeption handling in GHC

2003-01-24 Thread Hal Daume III
You're probably using IO (or System.IO) try.  If you want imprecise
exceptions (I think that's the right name), you want to use
Control.Exception versions of try/catch/bracket/etc.

Prelude :m IO
Prelude IO :t try
forall a. IO a - IO (Either GHC.IOBase.Exception a)
Prelude IO try (error a)
*** Exception: a
Prelude IO :m Control.Exception
Prelude Control.Exception try (error a)
Prelude Control.Exception it
Left a


HTH

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 24 Jan 2003, Sarah Thompson wrote:

 Hi all,
 
 I'm trying to get exception handling working in GHC, but don't seem to be
 able to make it work. Am I likely to be missing a compiler switch, or
 something?
 
 Cutting things down to basics, I'd have thought that the following
 expression (typed at the ghci command prompt) should work:
 
   try (error x)
 
 but the result is
 
   *** Exception: x
 
 I seem to get the same problem with compiled code. Any ideas anyone?
 
 TIA,
 Sarah
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Lazy streams and unsafeInterleaveIO

2002-12-22 Thread Hal Daume III
 BTW, I already found a major problem with the code I attached earlier, 
 using unsafeInterleaveIO: Run in GHCi (as I had done), it works fine; 
 but compiled by GHC and run as an executable, it waits for input and 
 *then* displays the prompt after the user hits Enter ... not very 
 helpful. I didn't think it would do that, since (putStr ?   readLn) 
 seemed pretty explicit as to order of evaluation, but I guess that's 
 what I get for breaking referential transparency ...

You probably want to set the buffering otherwise.  GHCi automatically sets
the buffering to nobuffering when it starts, so this probably explains
why you don't experience the problem in GHCi.  Import IO and do something
like:

  hSetBuffering stdout NoBuffering -- or LineBuffering
  hSetBuffering stdin  NoBuffering

...something like that...

HTH

 - Hal

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



Re: Fail: loop ???

2002-12-20 Thread Hal Daume III
loop means that you have an infinite loop that the system was able to
detect at runtime.  basically what happens is you have some function which
is about to get evaluated.  this is essentially a node in a graph.  the
runtime system marks this node as i'm being evaluated.  however, during
the evaluation of this node, it try to evaluate itself, but now sees that
it is marked as i'm being evaluated and thus knows that this will be an
infinite loop.

so, yes, you have an infinite loop somehwere in your code.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 20 Dec 2002, Ingo Wechsung wrote:

 Dear Haskellers,
 
 when I execute a program made with GHC (standard Haskell only, no
 optimization) I get
 
 Fail:  loop
 
 I have -W on, but it only tells me about a single  overlapping pattern,
 which is ok.
 
 The same program crashes Hugs alltogether. 
 
 Any hints for what I should look in my sources?
 
 MfG Ingo
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: ffi

2002-12-12 Thread Hal Daume III
-fffi three fs

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Thu, 12 Dec 2002, Martin Huschenbett wrote:

  
  $ ghc -ffi -o myprog Main.hs cfile.o
  
 
 When I try this I also get an error:
 
 
 martin:~/work/prograemmelchen ghc -ffi -o myprog Main.hs cfile.o 
 ghc-5.02.2: unrecognised flag: -ffi
 Usage: For basic information, try the `--help' option.
 
 
 
 Do I use a wrong GHC version?
 
 THX, Martin.
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: ffi

2002-12-12 Thread Hal Daume III
Perhaps you need a newer version of GHC...i just noticed you have and
02...I think you need an 04 to get the new FFI...

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Thu, 12 Dec 2002, Martin Huschenbett wrote:

  -fffi three fs
 
 This time I also get an error:
 
 
 martin:~/work/prograemmelchen ghc -fffi -o myprog Main.hs cfile.o 
 ghc-5.02.2: unrecognised flag: -fffi
 Usage: For basic information, try the `--help' option.
 
 
 Main.hs looks like:
 
 module Main ( main ) where
 
 foreign import ccall cfun cfun :: IO ()
 
 main :: IO ()
 main = do
   cfun
 
 
 
 Is the error here?
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Editor Tab Expansion

2002-12-05 Thread Hal Daume III
 As far as I understand it, I have 2 options:
 
 1. Use braces and semicolons and ignore the layout rules.

This is one option.

 Just to be sure, can I really, really forget about layout if I write fully
 braced and semicolonoized code?

Yes.

 Besides, is there any reason why the syntax is LET { decl1; decl2; ... } IN
 expr when LET and IN are sufficient enough to enclose the declarations?

because you can say:

  let x = y
  z = q
  w = l
  in  ...

so it needs to know where the boundaries between declarations are, hence
the need for semicolons.  therefore, if you have embedded lets, you need
braces to delimit them:

  let x = let y = z
  q = r
  in  l
  in  q

would be ambiguous without layout/bracessemis.

 - Hal

p.s., I'm surprised you're having difficulty with tabs; a few people have
had such problems, but usually there's an easy fix in the editor.  I don't
really know enough about this to say one way or another thogh...

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



Re: someone help me

2002-11-30 Thread Hal Daume III
Looks like homework to me, but for 1 and 2 you might look at read/show,
head and (:[]); for 3, try executing the give action multiple times
seperately.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Sat, 30 Nov 2002, Nuno Silva wrote:

 
 I'm relatively new to haskell and have some questions:
 
 1- I want to convert an integer to a char( if I say  prelude convert 4 ... it 
should return prelude '4')
 
 2- and vice versa?
 
 3- I want to define a function that stores in a variable the following...
 
 pretended: (Int,Int,Int,Int)
 
 give :: IO Int
 give = randomRIO (0,9)
 
 main = do k - (give,give,give,give)
 
 actualy this isn't possible. but can someone please tell how to do this???
 
 thank you very much
 
  
 
  
 
 
 
 -
 Do you Yahoo!?
 Yahoo! Mail Plus - Powerful. Affordable. Sign up now

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



Re: storing to a file

2002-11-14 Thread Hal Daume III
There's been mention of a Binary module; there is also one in the GHC CVS
repository under (I think) compiler/ghc/utils/Binary.hs.  There is
currently discussion on the libraries list about getting a Binary module
into the standard libraries.  We are currently working out some details,
but it will probably closely resemble the GHC Binary module (which is a
conversion of the NHC Binary module).

That said, there was also a post about using plain text.  I tend to agree,
except for certain cases.  However, that is *not* to say that you should
necessarily use Show/Read.  For instance, say you want to write something
of type [[Int]] to a file.  I would strongly discourage using show/read on
this, because read will need to read *all the way* to the end before
returning anything, to make sure there's that last close-bracket.  For
this case, I would much prefer to use:

writeInts fn = writeFile fn . unlines . map (unwords . map show)
readInts fn = readFile fn = return . (map (map read . words) . lines)

The same applies to tuples, etc.  This *vastly* inproves the efficiency
and, for long lists, tends to make them more human-readable (IMO).

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On 14 Nov 2002, Johan Steunenberg wrote:

 Hello,
 
 I am new to haskell, and to functional programming, and wondering how to
 store a Double, or any non-char, to a file. Do I have to make a char
 array of the double and store that? Or is it preferred to use the show
 and read functions? 
 
 Thanks in advance,
 johan steunenberg
 
 
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: 1 line simple cat in Haskell

2002-11-13 Thread Hal Daume III
I'm not sure why someone hasn't suggested

  main = interact id

which I think would accomplis everything you want, and probably be a heck
of a lot faster, as (apparently) putChar and getChar are quire
inefficient.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 13 Nov 2002, William Lee Irwin III wrote:

 On Wed, Nov 13, 2002 at 03:29:53PM +0900, Ahn Ki-yung wrote:
  If you are steaming with compicated codes, then how about taking a break.
  Let's play with a simple cat.
  \begin{code}
  main = mapM (=putChar) getCharS where getCharS = getChar:getCharS
  \end{code}
 
 Why not this?
 
 main = mapM_ (\h - mapM_ putChar = hGetContents h) = mapM (flip openFile $ 
ReadMode) = getArgs
 
 
 Bill
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: producing and consuming lists

2002-11-05 Thread Hal Daume III
Hrm.  This is interesting.  So one option you already considered would be
to put the writing inside 'streams', which probably should be
disprefered.  Have you considered doing something like:

streams :: (Int - Bool, Int - Bool) - (Int,Int) -
   [(Maybe Int,Maybe Int)]
streams (p,q) (x,y)
| p x  p y = (Just x , Just y ) : xs
| p x= (Just x , Nothing) : xs
| p y= (Nothing, Just y ) : xs
| otherwise  = xs
where xs = streams (p,q) ((x+y),(y-x))

With this setup, I think you can write your own writefile function which
looks something like:

writeTwoFiles f1 f2 (p',q') stream = do
h1 - openFile f1 WriteMode
h2 - openFile f2 WriteMode
writeFiles' h1 h2 stream
hClose h1
hClose h2
where writeFiles' h1 h2 ((Just x,Just y):xs) 
  | p' x  p' y = do hPutStr h1 $ show x
  hPutStr h2 $ show y
  writeFiles' h1 h2 xs
  | p' x = do hPutSTr h1 $ show x
  writeFiles' h1 h2 (zip (map fst xs) (repeat
  Nothing)
  | p' y = do hPutSTr h2 $ show y
  writeFiles' h1 h2 (zip (repeat Nothing)
 (map snd xs))
  | otherwise = return ()
  writeFiles' h1 h2 ((Just x,Nothing):xs) = ...

where you essentially ignore the nothings.

I think, but I'm not sure, that this will allow the old stuff to be
garbage collected.  In practice, you don't get too much useless junk
generated because we don't append the (Nothing,Nothing) pair to the list
(erm, prepend).  But what's more important, I think you only evaluate
the same amount of each at any given time, thus allowing GC to gobble up
the old stuff.

An expert might be able to prove me wrong, though, or you could try this
and profile it and see if it works or not :)

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 5 Nov 2002, Jorge Adriano wrote:

 I might have been not very clear in my last mail. I decided to post again, and 
 go straight to the point, with some small examples.
 
 Consider the following function streams.
 
 streams :: (Int-Bool, Int-Bool)-(Int, Int)-([Int],[Int])
 streams (p,q) (x,y) = (xs',ys')
 where
 (xs,ys) = streams (p,q) ((x+y),(y-x))
 xs' = if p x then x:xs else xs
 ys' = if q y then y:xs else ys
 
 
 - produces a pair of ('infinite') lists
 - produced lists are not indepentent (you need to calculate elements of one 
 list to calculate elements of the other)
 - in each recursive call an element is added to the 1st/2nd list iff  it 
 satisfies a given (Int-Bool) function p/q
 
 How should one consume (part of) both lists, avoiding space leaks?
 
 A particular example of consuming both lists might be writing them to files:
 main :: IO()
 main = do
let (s1,s2)=stream ... -- stream applied to some arguments (p,q) (x,y)
p' = ... 
q' = ... 
writeFile f1.txt (show$ takeWhile p' s1)
writeFile f2.txt (show$ takeWhile q' s2)
 
 In this example all elements of s2 required to evaluate (takeWhile p' s1) are 
 kept in memory, until the first file is writen. Notice that writing one 
 element from s1 and one from s2 successively might still cause space leaks to 
 arise. Fusing the consuming functions with the producer is a possible, but 
 IMO dirty, way out. 
 
 If my question doesn't seem to make sense for any reason, please tell me, 
 maybe I am missing something obvious here. 
 Thanks,
 J.A.
 
 
 
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: can't find sequence?

2002-10-29 Thread Hal Daume III
I believe you need 5.04 or greater to get the hierarchical libraries.  You
might try just using Monad instead of Control.Monad.Identity with
5.02.2, but I can't guarentee anything.  Even better: upgrade GHC :)

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 30 Oct 2002, Jason Smith wrote:

 Hi
 
 Yes Andrew, I'm using the TernaryTrie that u created.I tired the
 suggestion that Alastair gave me regarding the use of -package data but it
 still complained saying that it could not find module
 Control.Monad.Identity...
 
 How are u compiling it? Note that I'm using ghc 5.02.2 on windows.
 
 Thanks
 Jason.
 
  G'day all.
 
  On Mon, Oct 28, 2002 at 08:47:08AM +, Alastair Reid wrote:
 
   (btw There were some remarks that Chris's library might be dropped
   from distributions because no-one is supporting it.  I don't recall
   whether a decision was made on this.)
 
  If Jason is using a version of Edison that requires
  Control.Monad.Identity, it's almost certainly the HFL version, which
  is indeed supported (by me, mostly).
 
  However it is very alpha (especially the interface), so I wouldn't
  recommend packaging it at the moment.  In particular, Hugs is not
  currently a Supported Platform(tm).
 
  Cheers,
  Andrew Bromage
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: SOE exercise

2002-10-22 Thread Hal Daume III
 applyEach [(+1), (+3), (+2)]  1
 = [2,4,3] :: [Integer]
 
  applyEach' :: [a-b] - a - [b]
  applyEach' funs x = map applyx funs where applyx (fun) = fun x

...or more simply:

applyEach' l x = map ($x) l

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



Re: FFI and GHC

2002-10-19 Thread Hal Daume III
Two things.  First, you need a module name.  So prefix your code with
'module Foo where'.  Secondly, the call to ghc needs -fglasgow-exts to
pick up the necessary extensions.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On 19 Oct 2002, [ISO-8859-1] João Ferreira wrote:

 Hello all,
 
 I am trying to learn how to use FFI with GHC. I've tried the example in
 GHC's user's guide but it didn't worked. Here it is:
 
 
 1) The haskell code
 ===
 
 [bracaman@tucano hib]$ cat foo.hs
 foreign export ccall foo :: Int - IO Int
 
 foo :: Int - IO Int
 foo n = return (length (f n))
 
 f :: Int - [Int]
 f 0 = []
 f n = n:(f (n-1))
 
 2) The error
 
 
 [bracaman@tucano hib]$ ghc -c foo.hs
 foo.hs:3: Type signature given for an expression
 [bracaman@tucano hib]$
 
 
 I just can't understand why this is happening... can someone, please,
 help?
 
 Thank you in advance,
 João Ferreira
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Pure File Reading (was: Dealing with configuration data)

2002-10-11 Thread Hal Daume III

This message seems to have been lost and I'd like to try to breathe some
life into it.

First, a question: could such readFilePure functions be implemented on
TOP of the current IO module (perhaps in IO.Pure or something).  Of
course, one could do something like:
  readFileOnce :: FilePath - Maybe String
  readFileOnce = unsafePerformIO 
  {-# NOINLINE readFilePure #-}
but this is the sort of thing we're trying to get away from anyway.  There
doesn't (to me, at least) seem to be an obvious way to do this.  It seems
to be the sort of thing that requires compiler support.  In this case, do
any of the compiler implementers have a heart to tackle such a thing?  On
the other hand, if there's a way to do it on top of what already exists, I
would be more than happy to implement it if someone were to point me in
the right direction...

 The point is that the use of this function will typically
 happen at the beginning of a program, when reading the
 configuration file(s). When all this has happened, the
 function readFileOnce, and its memo table, will be garabage
 collected.

I like this, and it works for configuration files, but I have another
problem I would like to solve with this whole ...Once business which does
not fit into this model.

I have a large database-like-file which essentially contains an index at
the beginning.  When you want to look up something, you binary search for
the term in the index, find the position of the entity you want, seek to
that location and then read a specified amount.

The way I have this currently set up is that everything in my program is
embedded in the IO monad because

  1) the database is huge and i cannot store it all in memory
  2) usually only about 100 out of 25 entries are queried per run,
 but which entries these are change from run to run

Unfortunately, this means all my functions are monadic.  However, there's
no reason for them to be (in a sense): they are perfectly pure.  In fact,
I don't even have write access to the database :), but no one would ever
change it anyway.

So while I like the 'readFileOnce' and variants, I think that if someone
is serious about this '...Once' stuff, we should have more or less the
entire reading portion of the IO library in pure format for cases like
this.

Thoughts?

 - Hal

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



Re: need help optimizing a function

2002-10-08 Thread Hal Daume III

I already saw one reply mentioning using state threaded arrays.  This is
probably your best (in terms of performance) option.

Keep in mind that Haskell arrays are *not* your standard imperative
arrays.  Like imperative arrays, they give you O(1) lookup, but only
O(n) insert.  If you want to keep with a functional style, I'd suggest
using a different data structure for the data.  A FiniteMap should work
fine and should give you pretty good (at least much
better) performance.  And you won't have to give up the FP style (for
whatever that's worth).

 - Hal

p.s., I sense your next question is going to be something like why can't
the compiler detect that the array can be updated in place instead of
copied and the answer, from what i can tell, is simply that it doesn't
try.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 8 Oct 2002, David Roundy wrote:

 Hello.  If you followed my previous post (which was about a bug in my lcs
 function), this is still the same code (only now bug-free, it seems).
 
 It turns out that my lcs diff function is MUCH slower than GNU diff on some
 test files (much worse than 1000 time slower!).The test case where its
 speed was close was IO bound on the output to an xterm (silly me).
 
 I've profiled my lcs code, and it is spending about 95% of its time in the
 hunt_one_char function.  It also claims to spend 0.0% of its time in
 my_bs, which does a binary search on the array, and is the only other
 function that gets called by hunt_one_char (not counting itself).
 
 I've told the compiler (ghc) to inline hunt_one_char and my_bs to no avail.
 I guess maybe it can't or won't inline a recursive function, or maybe that
 just doesn't gain me anything.
 
 My only guess is that for some reason it is making an entirely new copy of
 the array each time it recurses, but that doesn't make any sense, since the
 array is getting threaded through, so it should be able to just modify the
 array in place.  But then, I'm not entirely clear as to what the compiler
 can and cannot do as it optimizes.
 
 data Threshold a = Thresh Int! [a]
  deriving (Show)
 
 hunt_one_char :: String - [Int] - Array Int (Threshold String) -
  Array Int (Threshold String)
 hunt_one_char c [] th = th
 hunt_one_char c (j:js) th =
 case my_bs (Thresh j [c]) th of
 Nothing - hunt_one_char c js th
 Just k -
 case th!(k-1) of
 Thresh _ rest -
 hunt_one_char c js th//[(k,Thresh j (c:rest))]
 
 For what it's worth, the calling function is:
 
 hunt_internal :: [String] - [[Int]] - 
  Array Int (Threshold String) -
  Array Int (Threshold String)
 hunt_internal [] _ th = th
 hunt_internal _ [] th = th
 hunt_internal (c:cs) (m:ms) th =
 hunt_internal cs ms $ hunt_one_char c m th
 
 Each string in this list of strings is a line from one of the files (and
 the [[Int]] is a list of line numbers in the other file that that line
 matches).  The array 'th' has size (1,n) where n is the number of lines in
 the file.
 
 My simplest test case consists of a 20k line file, each line of which is
 unique and a second file which is simply a permutation of the first (moving
 the first line to the last), so hunt_one_char should be called exactly once
 for each line, and it is always called with its second argument having
 exactly one element.  In this test case, according to the ghc profiler,
 89.7% of the time is spent in hunt_one_char:
   individual inherited
 COST CENTRE  MODULE entries  %time %alloc   %time %alloc
   hunt_internal  Main 200010.2   0.0 91.4  95.3
hunt_one_char Main 4   89.7  95.0 91.1  95.3
 my_bsMain 20.2   0.0  1.4   0.3
  my_helper_bsMain3072311.2   0.3  1.2   0.3
 
 This has me at a loss.  It seems like such a simple function... of course,
 it is called 20k times, which could certainly add up, but while each call
 of my_bs should take O(log 20k) time, each call of hunt_one_char (apart
 from its one call to my_bs) should only take O(1), so most of the time
 should be spent in my_bs unless something is terribly wrong (which must be
 the case here).
 
 If it would help, I'd be happy to send a listing of the complete code, but
 it's 6.5k so I figured it'd be better not to send it, since it seems
 unlikely that anyone would want to run it anyways.
 -- 
 David Roundy
 http://civet.berkeley.edu/droundy/
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Data structure definitions

2002-10-08 Thread Hal Daume III

I think this is more or less the standard way of doing it.  I don't think
type classes are the right thing to do.  Usually constructors are prefixed
with the first character of their type in situations like this (or so I've
seen), so you get:

data Expression = EValue Value | EVariable Variable | ...
data Value = VNumber Number | V... | ...
etc...

I'm not sure if this answers your question or not, tho...

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Tue, 8 Oct 2002, Mark T.B. Carroll wrote:

 I have a program that basically has,
 
   data Expression =
 Value Value
   | EVariable Variable | other stuff ...
 
   data Value = VNumber Number | other stuff ...
 
   data Variable = Variable { variable_name :: String, variable_time :: Expression }
   data Number = Number { value :: Double, dimension :: Dimension }
 
   newtype VariableCount = VariableCount (Variable, Number)
 
 The VNumber and EVariable constructors are ugly, though, so I was
 wondering if I should be using typeclasses - e.g.,
 
   class Expression a
   class Expression a = Value a
   instance Value Number
   instance Expression Variable
 
 ... but I don't see how to define Variable in such a scheme. Maybe I
 shouldn't be using typeclasses?
 
 (Obviously, I actually have lots more type constructors in Expression and
 Value - dyadic expressions, booleans, etc. - the above with just numbers
 and variables is somewhat truncated, but should suffice.)
 
 -- Mark
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Boxed versus Unboxed

2002-10-02 Thread Hal Daume III

We can think of it like this:

  When we have a value x :: Int, then 'x' is a computation
  which when evaluated will return either an Int or will
  be bottom (undefined).

When the program runs and x is evaluated, suppose it evalutes to an
actual Int (not bottom).  Then in the future any time x is evaluated,
instead of redoing the entire computation, we only want to get the value
out which we previously calculated.

What we do to accomplish this is to replace to thunk (computation) which
calculates x with a thunk which simply returns the value which was
computed before.

The problem is that every time you need to get x in the future, you have
to follow this pointer to the (trivial) code which returns a value.  THis
gets expensive if you need these values frequently.

Enter unboxed values.  An unboxed value is just that low-level value, not
wrapped inside a thunk.  This means that it is strict in the sense that it
cannot be undefined without your program necessarily dying.

In GHC, the type of an unboxed integer is Int#.  In fact, the Int type is
defined in terms of this:

   data Int = Int Int#

You can get more information that you really want from SPJ's paper
Implementing lazy functional languages on stock hardware: the Spineless
Tagless G-machine which talks about this issue.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 2 Oct 2002, Shawn P. Garbett wrote:

 -BEGIN PGP SIGNED MESSAGE-
 Hash: SHA1
 
 I've been reading on this list about boxed/unboxed structures. I'm not quite 
 clear what this terminology means. Is there a good paper that covers this 
 topic in detail, or a book reference?
 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.0.7 (GNU/Linux)
 
 iEYEARECAAYFAj2a8OEACgkQDtpPjAQxZ6DUSgCeIRgAl3dpOPavJhrmwFxal5O1
 Y8IAnRDzmdag9lyljlacKtE4aZMujfiG
 =h2Zn
 -END PGP SIGNATURE-
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Dealing with configuration data

2002-09-26 Thread Hal Daume III

Koen,

   getConfig :: Configuration
   getConfig = unsafePerformIO $
 do ...read configuration from file...
return configuration
 
 (*) Actually, a Haskell compiler is free to inline these
 kind of expressions, so really one has to give a
 NOINLINE pragma to the compiler as well.

I'd always avoided this type of thing precisely because of the inline
issue, which I don't think my version is in danger of.  That's just me,
though :).

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



Re: new to haskell-not working for some reason

2002-09-25 Thread Hal Daume III

Among other things, please make sure your layout lines up.  Also, you
cannot have the definition of getText at the same indentation of
userText-getText otherwise your compiler will think this is part of the
do statement (I believe):

 main=do userText-getText
 
 ---
 getText::IO String
 getText=do nc-getText
 ___return (:nc)


these need to be lined up

 _do putSpc (length Room)
 _return(RoomLength)


It would help if you also posted the error messaage the compiler gave you
and the line number and (perhaps) a shorter version of the program.

 - Hal

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



Re: Dealing with configuration data

2002-09-25 Thread Hal Daume III

AFAIK, the global variable (so-called), passing around, and lifting the IO
monad are your only options.  I almost always use the global variable
method since I know that in this case the unsafePerformIO is actually
safe, since writing to the variable will always occur before the call to
upIO and that it will only be written once.  I don't feel bad about doing
this because GHC does this itself for its own configuration :).

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Thu, 26 Sep 2002, Liyang Hu wrote:

 Evening,
 
 I'm trying to write a utility that reads in some user preferences from
 a pre-determined file, does some work, and exits. Sounds simple enough.
 
 The problem I'm having is with the preferences: How do I make it
 available throughout the entire program? (FWIW, most of the work is
 effectively done inside the IO monad.) I could explicitly pass the
 record around everywhere, but that seems a trifle inelegant.
 
 My current solution is to use a global ('scuse my terminology, I'm not
 sure that's the right word to use here) variable of type IORef Config
 obtained through unsafePerformIO. It works, but strikes me as a rather
 barbaric solution to a seemingly tame enough problem...
 
 Intuition tells me I should be able to `embed', if you will, the config
 record somehow within or alongside the IO state, and retrieve it at
 will. (Is this what MonadState is for?) However it also tells me that
 this will /probably/ involve lots of needless lifting and rewriting of
 the existing code, which makes it even less enticing than passing
 everything around explicitly.
 
 Any opinions or suggestions?
 
 Cheers,
 /Liyang
 -- 
 .--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
 | :: zettai unmei mokusiroku  absolute destined apocalypse : |
 

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



Re: Dealing with configuration data

2002-09-25 Thread Hal Daume III

Sorry, I should also mention implicit parameters, if you're willing to use
that extension.  I don't like them, though, and my impression from SPJ is
that it's very unclear whether they will get into Haskell 2 or not...

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 25 Sep 2002, Hal Daume III wrote:

 AFAIK, the global variable (so-called), passing around, and lifting the IO
 monad are your only options.  I almost always use the global variable
 method since I know that in this case the unsafePerformIO is actually
 safe, since writing to the variable will always occur before the call to
 upIO and that it will only be written once.  I don't feel bad about doing
 this because GHC does this itself for its own configuration :).
 
 --
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 
 On Thu, 26 Sep 2002, Liyang Hu wrote:
 
  Evening,
  
  I'm trying to write a utility that reads in some user preferences from
  a pre-determined file, does some work, and exits. Sounds simple enough.
  
  The problem I'm having is with the preferences: How do I make it
  available throughout the entire program? (FWIW, most of the work is
  effectively done inside the IO monad.) I could explicitly pass the
  record around everywhere, but that seems a trifle inelegant.
  
  My current solution is to use a global ('scuse my terminology, I'm not
  sure that's the right word to use here) variable of type IORef Config
  obtained through unsafePerformIO. It works, but strikes me as a rather
  barbaric solution to a seemingly tame enough problem...
  
  Intuition tells me I should be able to `embed', if you will, the config
  record somehow within or alongside the IO state, and retrieve it at
  will. (Is this what MonadState is for?) However it also tells me that
  this will /probably/ involve lots of needless lifting and rewriting of
  the existing code, which makes it even less enticing than passing
  everything around explicitly.
  
  Any opinions or suggestions?
  
  Cheers,
  /Liyang
  -- 
  .--{ Liyang HU }--{ http://nerv.cx/ }--{ Caius@Cam }--{ ICQ: 39391385 }--.
  | :: zettai unmei mokusiroku  absolute destined apocalypse : |
  
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Dealing with configuration data

2002-09-25 Thread Hal Daume III

I don't mean to troll, but this isn't what I meant.  Suppose we have:

data Configuration = ...  -- config data

globalConfig :: IORef Configuration
globalConfig = unsafePerformIO (newIORef undefined)

Now, we define an unsafe function to read the configuration:

getConfig :: Configuration
getConfig = unsafePerformIO $ readIORef globalConfig

Okay, this is bad but I claim it's okay, iff it is used as in:

main = do
   ...read configuration from file...no calls to getConfig...
   writeIORef globalConfig configuration
   doStuff
   return ()

now, we have doStuff :: IO a.  doStuff is allowed (even in its pure
methods) to use getConfig.  I claim that this is safe.  I could be
wrong; this is only a hand-waiving argument.  Why?

The first reference in the program to globalConfig is through a
writeIORef.  This means that at this point globalConfig gets evaluated and
thus a ref is created.  Immediately we put a value in it.

Now, when doStuff runs, since it is an action run *after* the call to
writeIORef, provided that it doesn't also write to 'globalConfig' (which I
mentioned in my original message), any call to getConfig is deterministic.

I could be wrong...please correct me if I am.




--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Thu, 26 Sep 2002, Nick Name wrote:

 On Wed, 25 Sep 2002 16:06:29 -0700 (PDT)
 Hal Daume III [EMAIL PROTECTED] wrote:
 
  I don't feel bad about doing
   this because GHC does this itself for its own configuration :).
 
 I am going to show you that using unsafePerformIO where there really are
 side effects leads to unpredictable results, and is generally wrong in a
 lazy language. Don't hate me for this :)
 
 Consider this example (supposing that a Config is represented by an
 Int):
 
 storeConfig :: Int - ()
 readConfig :: Int
 
 They both are obtained through the use of unsafePerformIO.
 
 Now, say I got this code:
 
  (storeConfig 0,storeConfig 1,readConfig,storeConfig 0,readConfig)
 
 What is this 5-uple supposed to evaluate to?
 
 First of all, this depends on order of evaluation. We can't say that all
 the elements of the tuple will be evaluated, so we can't tell if the
 fifth readConfig will evaluate to 0 or 1 (if the third storeConfig is
 never evaluated, readConfig will evaluate to 0, else to 1) This is one
 of the causes of the use of monads: ensuring correct order of
 evaluation.
 
 Second, suppose we were able to force order of evaluation (which
 shouldn't be allowed, in a lazy language). We still can't say what the
 last readConfig would evaluate to, since we don't know if the compiler
 is substituting equals for equals (I am expecting a lazy functional
 language to do this). 
 
 If the compiler does, the last readConfig is equal to the first (in
 fact, by the use of unsafePerformIO, you have told the compiler that
 both the functions storeConfig and readConfig are pure, which is not
 true) and will evaluate to 1, else it will evaluate to 0. And, besides,
 the compiler should also substitute the second storeConfig 0 with the
 result of the first occurrence, so it would not evaluate the second
 storeConfig at all.
 
 This is another example of the need for monads: allowing program
 transformations, first of all substituting equals for equals.
 
 This is why (even if, by enough knoweledge of the implementation, we
 could), by only relying on the semantics of a lazy language, we can not
 have functions with side effects.
 
 If it wasn't so, they would not have invented monads, believe me.
 
 I apologize, as always, for my terrible english, and hope I have been
 clear.
 
 Vincenzo Ciancia
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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



Re: Monad Maybe?

2002-09-23 Thread Hal Daume III

I know this has been written about way too much, but I was wondering what
people thought about using 'liftM f' as opposed to '= return . f'.  I
would probably have written Andrew's code using liftM, but I don't know if
one is necessarily better than the other.  Does anyone have strong
thoughts on this?

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Sun, 22 Sep 2002, Andrew J Bromage wrote:

 G'day all.
 
 On Sat, Sep 21, 2002 at 12:56:13PM -0700, Russell O'Connor wrote:
 
  case (number g) of
   Just n - Just (show n)
   Nothing -
case (fraction g) of
 Just n - Just (show n)
 Nothing -
  case (nimber g) of
   Just n - Just (*++(show n))
   Nothing - Nothing
 
 This isn't exactly the most beautiful way of doing it, but...
 
   (number g   = return . show) `mplus`
   (fraction g = return . show) `mplus`
   (nimber g   = return . ('*':) . show)
 
 Cheers,
 Andrew Bromage
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Monad Maybe?

2002-09-21 Thread Hal Daume III

 show g | Just n = number g   = Just (show n)
| Just n = fraction g = Just (show n)
| Just n = nimber g   = Just (*++show n)
| Nothing = Nothing

These should be Just n - number g, not =

 - Hal

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



Re: layout problem

2002-09-18 Thread Hal Daume III

   |(isMemberOf -f args)  (isMemberOf -i args)
  =printFreq(sortWordCount(parseLcLine textLines))
 |(isMemberOf -f args)

these two '|'s should be lined up, as in:

   |(isMemberOf -f args)  (isMemberOf -i args)
  =printFreq(sortWordCount(parseLcLine textLines))
   |(isMemberOf -f args)

as should all successive '|'s

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



Re: Question about use of | in a class declaration

2002-08-21 Thread Hal Daume III

This is a functional dependency.  You can probably find informationin the
GHC docs.  It's a way of telling the compiler how to derive type
information on multiparameter classes.  For example, if I have a class:

  class C a b where
f :: a - b

the type of f is

  (C a b) = a - b

The problem here is that you may have multiple instances of C with the
same a:

  instance C Int Bool ...
  instance C Int Char ...

so when you use f, it doesn't know which instance to use.  Writing 'a -
b' means a uniquely determines b and makes it so for any given a, you
can only have one instance of C, so the two above instances would be
rejected: you could only have one.

This means that when you write 'f (5::Int)' it knows which instance to
choose, since there can only be one.

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 21 Aug 2002, Guest, Simon wrote:

 Hello all,
 
 Please could someone explain the meaning of | in this class declaration (from 
Andrew's example):
 
   class (Ord k) = Map m k v | m - k v where
 lookupM :: m - k - Maybe v
 
 I couldn't find reference to this in any of my standard Haskell tutorials, nor the 
Haskell 98 report.  Any references?
 
 cheers,
 Simon
 
 -Original Message-
 From: Andrew J Bromage [mailto:[EMAIL PROTECTED]]
 Sent: 21 August 2002 04:19
 To: [EMAIL PROTECTED]
 Subject: Re: Question about sets
 
 
 G'day all.
 
 On Tue, Aug 20, 2002 at 10:57:36AM -0700, Hal Daume III wrote:
 
  Lists with arbitrary
  elements are possible, but not very useful.  After all, what could you do
  with them?
 
 It's often useful to have containers of arbitrary _constrained_ types,
 because then you can do something with them.  For example, given the
 class of partial mappings on orderable keys:
 
   class (Ord k) = Map m k v | m - k v where
 lookupM :: m - k - Maybe v
 
 
   instance (Ord k) = Map (FiniteMap k v) k v where
 lookupM = lookupFM
 
   instance (Ord k) = Map [(k,v)] k v where
 lookupM m k = case [ v | (k',v) - m, k == k' ] of
   []- Nothing
   (v:_) - Just v
 
   instance (Ord k) = Map (k - Maybe v) k v where
 lookupM   = id
 
 You can make a list of elements, which can be any type so long as
 they are a member of that class:
 
   data MAP k v = forall m. (Map m k v) = MAP m
 
   type ListOfMap k v = [MAP k v]
 
 Then you can do things with it:
 
   lookupLom :: (Ord k) = ListOfMap k v - k - [ Maybe v ]
   lookupLom xs k = [ lookupM a k | MAP a - xs ]
 
   test :: [Maybe Int]
   test
 = lookupLom maps 1
 where
   maps = [ MAP finiteMap, MAP assocListMap, MAP functionMap ]
   finiteMap = listToFM [(1,2)]
   assocListMap = [(1,3)]
   functionMap = \k - if k == 1 then Just 4 else Nothing
 
 It's a little unfortunate that you have to introduce the MAP type here.
 You can in fact construct a list of this type:
 
   type ListOfMap k v = [ forall m. (Map m k v) = m ]
 
 But then you can't use the elements in the list because the Haskell
 type checker can't find the (Map m k v) constraint.
 
 Cheers,
 Andrew Bromage
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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



Re: questions

2002-08-20 Thread Hal Daume III

There are three basic problems here.  The first is the syntax error you
see, the second and third will become available once you fix the syntax
error.

 lexi (a:x)
  | isLetter a = token: lexi restante
where S = takeWhile isLetterorDigit x
 line 20 --   restante = dropWhile isLetterorDigit x
token = 'Id' ++ S

So, Haskell uses a system of layout.  THis saves us from writing lots of
braces and parentheses (some people don't like layout and you're free to
do without it -- Ashley will probably post something along these
lines).  The basic idea is that without layout, you would have to write:

  ... where { S = takeWhile isLetterorDigit x ; restante = dropWhile
isLetterorDigit x ... }

what layout allows you to do is tell the compiler where to insert these
braces and semicolons implicitly.  You do this by verical
alignment.  Basically, if a keywords like 'where' (or 'let' or 'do') is
not followed by a brace, the column number at which the next identifier is
found is remembered.  Henceforth, as long as columns begin at that column
number, they are part of the same where clause.  This might be a bit
tricky to grasp, but the moral is:

  make sure the starting column for the definition of each element in a
where clause is the same.  

so you would write:

 lexi (a:x)
  | isLetter a = token: lexi restante
where S = takeWhile isLetterorDigit x
  restante = dropWhile isLetterorDigit x
  token = 'Id' ++ S

now, the second problem.  identifiers must begin with lowercase letters,
so this S will not do.  According to haskell, things that begin with a
capital letter are type constructors, types, classes.  So you must you
s instead of S.

Finally, the third problem.  You define:

 main = lexi

But this won't work.  The type of lexi (once you get it working) is
'String - [String]' but the type of main must be 'IO ()'.

Presumably, you want to apply the lexer to stdin and then print the
identifiers out one per line.  You can do this with something like:

  main = interact (unlines . lexi)

The function 'interact' has type

  (String - String) - IO ()

and what it does is read from stdin, run what it reads through the string
processing function, and prints the results to stdout.  Now, your function
lexi has type 'String - [String]', so this won't do.  The function
'unlines' has type:

  [String] - String

and basically takes the list of strings, puts newlines between them, and
catenates them.

Finally, '.', the composition operator composes the two functions, thus
producing a function of type 'String - String' as required by interact.

I hope this has made some sense.

 - Hal

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



Re: Infix expressions

2002-07-29 Thread Hal Daume III

 Is there any reason other than potential confusion when one of the two
 backquotes is accidentally omitted?

I thought about this a while ago and I think it probably simply has to do
with complexity of expressions.  If you allow arbitrary expressions to
appear within the ticks, you have a problem with:

  x `f a `b` g c` y

does this mean

  (b (f a) (g c)) x y

or

  f a x (g c b y)

or what?

You could impose the constraint that you can't have embedded ticks, but
this would grossify the CFG.  Furthermore, you then have the case of, why
isn't this valid:

  a `f (x `g` y)` b

where the embedding is unambiguous because of the parentheses.  i don't
really know, but i find this fairly difficult to read.

  a `h` b where h = x `g` y

is a lot simpler imo...

 - Hal

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



Re: Doubts...

2002-07-26 Thread Hal Daume III

In short, these need to be in a file.  Take a look at YAHT (yet another
haskell tutorial) which is under development and see if that answers any
of your questions...if not, PLEASE let me know so I can update the
tutorial so it does answer your questions.

The tutorial is available off my web page http://www.isi.edu/~hdaume as a
DVI, PS or PDF.

 - Hal

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 26 Jul 2002, Pedro L. P. Dias wrote:

 Dear Professor:
 
 My name is Carlos Alexandre Grimaldi.  I'm engineering student at Federal University 
of Rio de Janeiro, Brazil.  I began my studies in Haskell, and I have some doubts 
which I report here.
 I'm very gratefully if you could help me.
 I'm following a book I downloaded from Internet: A Gentle Introduction to Haskell, 
Version 98.  Following this, I face some problems:
 
 - inc :: Integer - Integer don't work
 
 - inc n = n+1 don't work too;
 
 - data Bool = False | True also...;
 
 - data Color = Red | Green | Blue | Indigo | Violet also fails.
 
 I thought that this commands and definitions must be inside a program, and don't at 
prompt prelude.  So, I opened other book, also downloaded from Internet: The Hugs 
98 User Manual, and I tryed:
 
 module Fact where
 fact :: Integer - Integer
 fact n = product [1..n]
 
 thinking that would be created a file Fact, in which the definitions for fact 
would work.  But this also yield an error...  So, I ask you:
 
 - is necessary the creation of a file where that definitions could work?
 
 - is this file a .hs?
 
 - how can I create a file like this?  Which command or editor?
 
 - or, if I wrong, why that examples don't work?
 
 Thank you very much for your help.
 Best regards,
 Carlos A. Grimaldi.
 

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



Re: problems figuring out what the type system is telling me

2002-06-07 Thread Hal Daume III

see http://haskell.org/wiki/wiki?ThatAnnoyingIoType and
http://haskell.org/wiki/wiki?UsingIo

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 7 Jun 2002, Chris Moline wrote:

 hi. i am really stuck on this problem and i cant seem to figure it out and so 
 i am posting this in the hopes someone will help me. i realize you prolly get 
 this kind of question alot but the wiki and the papers i have been reading 
 arent helping to clarify things.
 
 i am trying to write a little utility to make it easier to get rid of ports on 
 my machine. the function that is giving me trouble is getDepends. it takes the 
 name of a port and opens the appropriate +CONTENTS file and returns the 
 dependencies it finds.
 
 here is the function and its helper.
 
 getDepends :: String - [String]
 getDepends p = do
 handle - openFile (portsDir ++ p) ReadMode
 fetchDepends handle
 
 fetchDepends :: Handle - [String]
 fetchDepends handle = do
 l - hGetLine handle
 e - hIsEOF handle
 case (not e) of   -- ifs keep giving indent errors so ill just use case
 True -
 case (matchRegex (mkRegex ^@pkgdep) l) of
 Just [a] - [drop 8 l] ++ (fetchDepends handle)
 _ - fetchDepends handle
 False - 
 
 here is ghci's error messages.
 
 Compiling Pheobe   ( Phoebe.hs, interpreted )
 
 Phoebe.hs:19:
 Couldn't match `[]' against `IO'
 Expected type: [t]
 Inferred type: IO Handle
 In the application `openFile (portsDir ++ p) ReadMode'
 In a 'do' expression pattern binding:
 handle - openFile (portsDir ++ p) ReadMode
 
 Phoebe.hs:24:
 Couldn't match `[]' against `IO'
 Expected type: [t]
 Inferred type: IO String
 In the application `hGetLine handle'
 In a 'do' expression pattern binding: l - hGetLine handle
 Failed, modules loaded: none.
 
 could someone be so kind as to explain what the problem is?
 
 sincerly,
 chris moline
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Q: Resolving ambiguous type variable

2002-05-17 Thread Hal Daume III

In short, you cannot.

What if your main were:

main = getArgs = print . first_h

The compiler doesn't know the difference and so it needs a type.

Simple fix:

 main = print (first_h ([] :: [Char]))


--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 17 May 2002 [EMAIL PROTECTED] wrote:

 Hello,  
I am writing a function which returns an exception/error string should an 
unexpected parameter is passed in. Borrowing from the Maybe module I have the 
following:
 
 data Result a = Ex String | Value a deriving Show
 
 -- Testing the Result a type
 first_h :: [a] - Result a
 first_h [] = Ex No list
 first_h (x:xs) = Value x
 
 -- Trying out the first_h
 main :: IO()
 main = print (first_h [])
 
 
 Which the compiler complains:
 
 Ambiguous type variable(s) `a' in the constraint `Show a'
 arising from use of `print' at atype.hs:8
 In the definition of `main': print (first_h [])
 
 This is understandable since it is unable to unify the empty list with a concrete 
list of type 'a' i.e. there are an infinite types which would match. My question is 
how can I indicate to the compiler that it does not matter which type the empty list 
is since the return result is of a concreate type.
 
 Thanks
 
 Tee
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Q: Resolving ambiguous type variable

2002-05-17 Thread Hal Daume III

Erm, I think I said something stupid (or at least implied it).

main = getArgs = print . first_h

*will* work, because it knows that the result of a getArgs is a list of
Strings.

The problem you originally had was that when you say:

first_h []

The [] could refer to a list of any type of element.  Since not every
element type is an instance of Show, it doesn't know that it can apply
show to the list.

By saying, for instance, (first_h ([] :: [Char])) you're saying okay,
this is an empty list, but it's a list of Characters and you know that a
character can be shown.  If you backtrack what the type checker is doing,
it says:

print (first_h [])

okay, the argument to print must be an instance of Show (print has type
Show a = a - IO ()).  therefore,

first_h []

must be an instance of Show.  well, what's the type of first_h []?  Well,
the type of first_h is [a] - Result a.  is Result a an instance of
show?  well, let's see...you said data Result a = ... deriving
(Show).  this basically means you get an instance declaration:

instance Show a = Show (Result a) where
  ...some stuf...

so, we want to know if Result a is an instance of show.  Well, it is
whenever a is an instance of show.  so, if the elements of your list are
an instance of show, then (first_h []) is an instance of Show, as we
require.

however, since you just say [] it knows this is of type [a], but it
*doesn't* know what a is.  therefore, a could either be or not be an
instance of show.  however, if you explicitly specify what a is and that
explicit type is an instance of show (like Char in my example), then
everything is fine.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 17 May 2002, Hal Daume III wrote:

 In short, you cannot.
 
 What if your main were:
 
 main = getArgs = print . first_h
 
 The compiler doesn't know the difference and so it needs a type.
 
 Simple fix:
 
  main = print (first_h ([] :: [Char]))
 
 
 --
 Hal Daume III
 
  Computer science is no more about computers| [EMAIL PROTECTED]
   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 
 On Fri, 17 May 2002 [EMAIL PROTECTED] wrote:
 
  Hello,  
 I am writing a function which returns an exception/error string should an 
unexpected parameter is passed in. Borrowing from the Maybe module I have the 
following:
  
  data Result a = Ex String | Value a deriving Show
  
  -- Testing the Result a type
  first_h :: [a] - Result a
  first_h [] = Ex No list
  first_h (x:xs) = Value x
  
  -- Trying out the first_h
  main :: IO()
  main = print (first_h [])
  
  
  Which the compiler complains:
  
  Ambiguous type variable(s) `a' in the constraint `Show a'
  arising from use of `print' at atype.hs:8
  In the definition of `main': print (first_h [])
  
  This is understandable since it is unable to unify the empty list with a concrete 
list of type 'a' i.e. there are an infinite types which would match. My question is 
how can I indicate to the compiler that it does not matter which type the empty list 
is since the return result is of a concreate type.
  
  Thanks
  
  Tee
  ___
  Haskell-Cafe mailing list
  [EMAIL PROTECTED]
  http://www.haskell.org/mailman/listinfo/haskell-cafe
  
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Q: Resolving ambiguous type variable

2002-05-17 Thread Hal Daume III

The problem is that a is still ambiguous.  For instance, look at the
difference between:

  show ([] :: [Int])==   []
  show ([] :: [Char])   ==   

because character lists are shown between quotes.  so even though we know
that this type variable a is an instance of show, we still don't know how
to show it (i.e., we don't know which dictionary to use to lookup the
show function for the datatype).

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Fri, 17 May 2002 [EMAIL PROTECTED] wrote:

 Would it be correct to conclude from your reasoning that the following would be 
properly typed by the compiler ?
 
 first_h :: (Show a) = [a] - Result a
 first_h [] = Ex No list
 first_h (x:xs) = Value x
 
 since we are explicitly stating first_h can only take a list containing elements 
deriving Show. My expectations would be that this would be unambiguous, unfortunately 
ghc-5.02.3 
 still complains with the reported error.
 
 Regards
 
 Tee
 
  Original Message 
 From: [EMAIL PROTECTED]
 To: [EMAIL PROTECTED]
 Cc: [EMAIL PROTECTED]
 Subject: Re: Q: Resolving ambiguous type variable
 Date: Fri, 17 May 2002 10:24:29 -0700 (PDT)
 
  Erm, I think I said something stupid (or at least implied it).
  
  main = getArgs = print . first_h
  
  *will* work, because it knows that the result of a getArgs is a list of
  Strings.
  
  The problem you originally had was that when you say:
  
  first_h []
  
  The [] could refer to a list of any type of element.  Since not every
  element type is an instance of Show, it doesn't know that it can apply
  show to the list.
  
  By saying, for instance, (first_h ([] :: [Char])) you're saying okay,
  this is an empty list, but it's a list of Characters and you know that a
  character can be shown.  If you backtrack what the type checker is doing,
  it says:
  
  print (first_h [])
  
  okay, the argument to print must be an instance of Show (print has type
  Show a = a - IO ()).  therefore,
  
  first_h []
  
  must be an instance of Show.  well, what's the type of first_h []?  Well,
  the type of first_h is [a] - Result a.  is Result a an instance of
  show?  well, let's see...you said data Result a = ... deriving
  (Show).  this basically means you get an instance declaration:
  
  instance Show a = Show (Result a) where
...some stuf...
  
  so, we want to know if Result a is an instance of show.  Well, it is
  whenever a is an instance of show.  so, if the elements of your list are
  an instance of show, then (first_h []) is an instance of Show, as we
  require.
  
  however, since you just say [] it knows this is of type [a], but it
  *doesn't* know what a is.  therefore, a could either be or not be an
  instance of show.  however, if you explicitly specify what a is and that
  explicit type is an instance of show (like Char in my example), then
  everything is fine.
  
  --
  Hal Daume III
  
   Computer science is no more about computers| [EMAIL PROTECTED]
than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
  
  On Fri, 17 May 2002, Hal Daume III wrote:
  
   In short, you cannot.
   
   What if your main were:
   
   main = getArgs = print . first_h
   
   The compiler doesn't know the difference and so it needs a type.
   
   Simple fix:
   
main = print (first_h ([] :: [Char]))
   
   
   --
   Hal Daume III
   
Computer science is no more about computers| [EMAIL PROTECTED]
 than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
   
   On Fri, 17 May 2002 [EMAIL PROTECTED] wrote:
   
Hello,  
   I am writing a function which returns an exception/error string should an 
unexpected parameter is passed in. Borrowing from the Maybe module I have the 
following:

data Result a = Ex String | Value a deriving Show

-- Testing the Result a type
first_h :: [a] - Result a
first_h [] = Ex No list
first_h (x:xs) = Value x

-- Trying out the first_h
main :: IO()
main = print (first_h [])


Which the compiler complains:

Ambiguous type variable(s) `a' in the constraint `Show a'
arising from use of `print' at atype.hs:8
In the definition of `main': print (first_h [])

This is understandable since it is unable to unify the empty list with a 
concrete list of type 'a' i.e. there are an infinite types which would match. My 
question is how can I indicate to the compiler that it does not matter which type the 
empty list is since the return result is of a concreate type.

Thanks

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

RE: defining (- Bool) as a set

2002-04-26 Thread Hal Daume III

Would there be any problems if there were an artificial - type
constructor in Haskell which was basically:

type a - b = b - a

but not a type synonym so you could define it to be instances of classes,
but then those get applied backwards to -?

Okay, that made no sense.  I'll try again.  Type lambda = bad
(undecidable).  What about only type lambda on function types and not even
type lambda; simply allow partial application to the second argument
*only* on -?  This would solve my problem and I believe that of an
earlier poster who wanted to define catamorphisms (I think; don't feel
like checking), but couldn't because of this restriction.  Is this still
too loose to be made to work?

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Mon, 22 Apr 2002, Simon Peyton-Jones wrote:

 Hal, 
 
 [I think this sort of question would be better on the haskell-cafe
 list.]
 
 I don't think what you want can be done directly.  It's the old
 thing about not having lambdas at the type level.  You want:
 
   instance Eq a = Coll (\x. x - Bool) a where ...
 
 and you just can't do that.   You *can* abstract the second argument
 of (-):
 
   instance Eq a = Coll ((-) Bool) a where ...
 
 but not the first.  It's a well known shortcoming in Haskell, that you
 can
 partially apply type constructors, but you can't do argument
 permutation.
 
 I know of no good solution.  Adding type lambdas in their full glory
 makes type inference pretty much impossible.  What we'd like is
 a compromise.  Maybe someone can invent one.  But take care.
 The ground is littered with corpses.
 
 Simon
 
 
 | -Original Message-
 | From: Hal Daume III [mailto:[EMAIL PROTECTED]] 
 | Sent: 23 April 2002 01:30
 | To: Jorge Adriano
 | Cc: Haskell Mailing List
 | Subject: Re: defining (- Bool) as a set
 | 
 | 
 | Yeah, both options suggested are valid, of course.  But I 
 | really don't want to have a constructor and I'm using Edison 
 | where Coll is defined something like:
 | 
 | class Coll c e where
 |   empty :: c e
 |   insert :: c e - e - c e
 | 
 | etc., which precludes the fun dep solution.
 | 
 |  - Hal
 | 
 | --
 | Hal Daume III
 | 
 |  Computer science is no more about computers| [EMAIL PROTECTED]
 |   than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume
 | 
 | On Tue, 23 Apr 2002, Jorge Adriano wrote:
 | 
 |  
 |   class Collection e ce | ce - e where
 |   empty :: ce
 |   insert :: e - ce - ce
 |   member :: e - ce - Bool
 |  
 |   instance Eq a = Collection a (a - Bool) where
 |   empty = (\x - False)
 |   insert e f = (\x - if x == e then True else f x)
 |   member e f = f e
 |  
 |  This is way better than my solution...
 |  
 |  I had never used multi-parameter classes before, so I forgot the 
 |  functional
 |  dependency (right name? the |ce-e), and there was 
 | obviously no need for my 
 |  extra constructor.
 |  
 |  J.A.
 |  
 | 
 | ___
 | Haskell mailing list
 | [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell
 | 
 

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



Re: lazy comparison for equality ?

2002-04-24 Thread Hal Daume III

I don't think you can write such a function.  For instance, how would you
know whether [1..] is circular or not?  In order to know that it's not
you'd need to evaluate it fully.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Wed, 24 Apr 2002 [EMAIL PROTECTED] wrote:

 
 Hi -
 I'm a Haskell beginner and I have a problem. 
 
 Let's have a list which may be normal list
 list1 = [1,2,3]
 or a circular list
 list2 = 1:2:list2
 
 Now I'd like to have a function which tells me whether the 
 given list is circular or not. This doesn't work:
 
 circ l = l l
 circ2 l [] = False
 circ2 l (_:as) | l==as = True
| True = (circ2 l as)
 
 
 It seems that comparison l==as really compares element by element thus
 falling into an infinite loop. I would need to compare pointers instead of
 values.
 
 Does anybody know how this could be done ?
 
 Thanks.
 
 
 
 
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

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



Re: Ground Up

2002-02-28 Thread Hal Daume III

On Thu, 28 Feb 2002, Jerzy Karczmarczuk wrote:

 I didn't follow that discussion, but let's be serious. Really.
 Your second version constructs and destroys plenty of tuples, of
 ephemeric data structures which live one step only, and this is
 obviously costly. No way to know this? Are you sure?

And yet there's no reason I shouldn't get update-in-place on those
tuples.  What's more, if I create my own data type for tuples which is
strict in both of its arguments and use a function which is strict in the
tuple (yes, even if i use proper tail recursion), it's still slower. 

 WHAT is a problem?
 I see only one: a Haskell user should master the essentials of 
 a reasonably professional functional style.
 
 sumProdTo n = spt n 1 1 where
  spt 1 s p = (s,p)
  spt n s p = spt (n-1) (n+s) (n*p)

This is obviously the preferred solution, but it seems there should be no
performance difference between this and:

sumProdTo n = spt n (1,1) where
  spt 1 acc   = acc
  spt n (s,p) = spt (n-1) (n+s, n*p)

but there is a huge difference, even if i put seqs in to force evaluation
of the sum and product before creating the tuple.

but this is obviously a made-up situation.  (more down further)

  ... it's just that i don't think it's
  fair to say you don't have to understand what the compiler is doing to
  write code.
 
 This is not the question of this or that *compiler*, but of understanding
 the basics of data processing independent of the language. I am abhorred by
 the idea of putting down: this looks like it would speed up your program...
 in cases where it is rather clear that it might not. Please do the same 
 experience in C with dynamically allocated tuples.

so constructing and tearing apart tuples, you should say then, displays a
lack of understanding of the basics of data processing in haskell.  let's
look at the definition of the standard library function mapAccumL:

 mapAccumL   :: (a - b - (a, c)) - a - [b] - (a, [c])
 mapAccumL f s [] = (s, [])
 mapAccumL f s (x:xs) = (s'',y:ys)
  where (s', y ) = f s x
(s'',ys) = mapAccumL f s' xs

this is clearly the same problem.  it's constantly creating and tearing
apart tuples.

or unfoldr:

 unfoldr f b  = case f b of Nothing- []
Just (a,b) - a : unfoldr f b

the list goes on.

clearly creating small intermediate structures (like tuples) is very
central to haskell.  in fact, for speed reasons i have frequently written
my own versions of the above functions which remove the tuple creation
because it simply makes it too slow.  this is *not* at all what haskell is
about.  it's about writing functions which are small and modular and have
good reuse.  that's why this functions are in the standard libraries.

you can also observe the frequent use of functions which take a state and
return a (state,value) pair.  using functions like these pushes the
creation and destruction of tuples very far.

given the importance tuples and other small data structures have in
haskell, i found it hard to believe that using them would cause me to
suffer such a severe performance penalty.  i *assumed* that since they
were so widely used and so integral to the language, that the compilers
would do a much better job that they do with being intelligent about using
them.  i found this assumption to be incorrect, and that's the primary
reason i think you need to know more about what's going on in the compiler
to write fast programs.

 - Hal


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



Re: (no subject)

2002-02-24 Thread Hal Daume III

I'm not sure where the documentation is, but here's the idea on how to
used named fields.  I'll make a smaller example, though :)

 data T = T { x :: Int, y :: Bool }

now, to create a value of type T, you can write:

 x = T 5 True

as the datatype declaration creates the following function:

 T :: Int - Bool - T

You can also pattern match as if you had just declared it as data T = T
Int Bool.  However, this datatype declaration introduces two functions
into the namespace:

 x :: T - Int
 y :: T - Bool

which extract values.  for instance:

 x (T 5 True)

evaluates to 5 and

 y (T 5 True)

evaluates to True.

You can also use field names to create values:

 T { x = 5, y = True }

or

 T { y = True, x = 5}

order is irrelevant (i'm not sure about rules if you specify the same
field more than once...check in the report on that).

Finally, you can update parts of labelled fields independent of everything
else:

 let q = T {x=4, y=True}
 q' = q {x=5}
 in  q'

will yield T 5 True.

Of course, this isn't value replacement, it's just a more convenient way
to create a new value based on an old one, with minor changes.

I see Ashley also replied to this thread with a pointer to
documentation.  Hopefully the combination will help.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On 25 Feb 2002, Tom Bevan wrote:

 
 
 Hi,
 
 I've come across this sort of data constructor below many times but I'm
 not really sure how to use it. Can someone please point me to the right
 section in the documentation?
 In particular, I want to know how to create a calendar time and how to
 access the fields .
 
 Tom
 
 data CalendarTime = CalendarTime {
   ctYear   :: Int,
   ctMonth  :: Month,
   ctDay, ctHour, ctMin, ctSec  :: Int,
   ctPicosec :: Integer,
   ctWDay:: Day,
   ctYDay   :: Int,
   ctTZName   :: String,
   ctTZ  :: Int,
   ctIsDST :: Bool
   } deriving (Eq, Ord, Read, Show)
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


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



Re: syntax...(strings/interpolation/here docs)

2002-02-13 Thread Hal Daume III

 hugs and ghc.  With hugs, I use the builtin feature, of course.  With GHC, we 
 just use a pre-processor.  This is a bit awkward with GHC 5.02 and earlier 
 versions, but starting with 5.03, GHC now has a proper interface for hooking 
 in a pre-processor (don't know the details, bug Sigbjorn says it's in there). 

Is this true?  Is there any documentation on it?

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



Re: Random questions after a long haskell coding day

2002-01-26 Thread Hal Daume III

For your last question (about reduction to hnf), use the attached
code; search the haskell mailing list for deepseq for more.

--
Hal Daume III

 Computer science is no more about computers| [EMAIL PROTECTED]
  than astronomy is about telescopes. -Dijkstra | www.isi.edu/~hdaume

On Sun, 27 Jan 2002, Jorge Adriano wrote:

 
 
 Am I the only one who'd like to have some the function specified by
  scan_and_fold f e xs= (scanl f e xs, foldl f e xs)  
 In the Lists library. Or is it there somewhere and I missed it?
 
 What about:
  pair (f,g) x = (f x, g x)
  cross (f, g) = pair(f.fst, g.snd)
 I kind of like point free style.
 
 
 Any thumb rule for using arrays? I'm expecting access to be O(1), it is right?
 Need to have a set of data, and I just want to get random elements from that 
 Set, arrays seem like a good solution... am I right?
 
 
 DiffArrays... aren't they supposed to be just like Arrays expect for the (//) 
 behaviour (and accum and accumArray), If so, why is there no Show 
 instance for them? Or Functor instance? When I tried to change to DiffArray 
 it broke everywhere...
 Speaking of functors, in the Haskell98 Library Report:
 The two functions map and ixmap derive new arrays from existing ones (...)
 The map function transforms the array values while ixmap allows for 
 transformations on array indices.
 That is supposed to be fmap, not map right?
 
 
 Unboxed types... Ghci
  f n  =  3# 
 loads ok and,
 Test :t f
 forall t. t - PrelGHC.Int#
 
 nice... now this:
  f :: Int - Int#
  f n  =  3# 
 when trying to load I get:
 
 Test.hs:3: Type constructor or class not in scope: `Int#'
 Failed, modules loaded: none.
 What  am I missing here? Tried Int#, PrelGHC.Int... nothing worked...
 and Ghci also didn't know about (+#) either... 
 
 
 
 Last but not least, got this algorithm 
 w_(n+1) = w_(n) + deltaW  
 
 The ws and deltaW are vectors (lists). The deltaW is calculated using w_(n) 
 and some random point from a DataSet. So I'm doing something like
 
 lstep :: TrainingSet-WeightVector-WeightVector
 lstep ts w = w `vectorsum` deltaW
   where
   bla, bla
 
 learn ::TrainSet-WeightVec-WeightVec
 learn ts w0 = until p (lstep tSet) w0
   where 
   bla, bla
 
 [actually I'm making things a little more simple than they are... lstep 
 receives and returns a triple with the, w, stdGen to get the random val, n. 
 of steps...]
 
 I'm having some stack overflows in my program and I think this is what's 
 causing it. The suspension in my calculated weight vectors... I should be 
 evaluating the weight vectors in each step... (agree?)
 But how can I evaluate a whole list? seq or $! just reduce elements to head 
 normal form.
 [Yes, I know I can always print them all! :-)
 In fact, just to see if that was the cause I tried printing them right now...
 Well I'd have to print 5 results, and I'm short on disk space... 
 redirected the output to dev null and it is printing for about 40min now 
 still no stack overflow... ]
 
 
 Also got this problem if I want to check evaluation times. I used to do it 
 something like this when calculating simple values:
 
  time1 - getCPUTime 
  val - return $! f x
  time2 - getCPUTime
 
 But this doesn't work if val is a list of values. So how do you do it?
 Wouldn't it be nice to have some strict 'lists'? 
 Once I asked why is aren't there any operators to reduce elements to their 
 normal form (not head normal), I was answered that for some types there is no 
 such concept... Is that because of the newtype declaration? (if it isn't I 
 think I'm missing something here... functions are in normal form, for 
 primitive datatypes it's the same as head normal form, and for constructed 
 datatypes you can define it by structural recursion...)
 
 
 And now I'm off to bed
 Thanks to those who actually read the whole mail :-)
 J.A.
 
 ___
 Haskell-Cafe mailing list
 [EMAIL PROTECTED]
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 


module DeepSeq where

class  DeepSeq a  where
  deepSeq :: a - b - b
  deepSeq = seq   -- default, for simple cases

infixr 0 `deepSeq`, $!!

($!!) :: (DeepSeq a) = (a - b) - a - b
f $!! x = x `deepSeq` f x


instance  DeepSeq ()  where

instance  (DeepSeq a) = DeepSeq [a]  where
  deepSeq [] y = y
  deepSeq (x:xs) y = deepSeq x $ deepSeq xs y

instance  (DeepSeq a,DeepSeq b) = DeepSeq (a,b)  where
  deepSeq (a,b) y = deepSeq a $ deepSeq b y
instance  (DeepSeq a,DeepSeq b,DeepSeq c) = DeepSeq (a,b,c)  where
  deepSeq (a,b,c) y = deepSeq a $ deepSeq b $ deepSeq c y
instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d) = DeepSeq (a,b,c,d)  where
  deepSeq (a,b,c,d) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq d y
instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e) = DeepSeq (a,b,c,d,e)  
where
  deepSeq (a,b,c,d,e) y = deepSeq a $ deepSeq b $ deepSeq c $ deepSeq d $ deepSeq e y
instance  (DeepSeq a,DeepSeq b,DeepSeq c,DeepSeq d,DeepSeq e