Re: [Haskell-cafe] hFileSize vs length

2005-03-12 Thread Gracjan Polak

S. Alexander Jacobson wrote:
 I am using GHC 6.2 on windows and am finding that when I open a file and
 use hFileSize I get a different number than I get from reading in the
 file and calculating the length.  I assume this is not a bug, but I
 don't know why its happening.
Isn't that because of line end conversion? EOL on windows is \r\n (2 
bytes), when read converted on the fly to \n (1 char).

Try to open your file in binary mode.

 Also, why isn't there getFileSize function in System.Directory?
System.Posix.Files has getFileStatus and fileSize. No idea if they work 
on windows.


 -Alex-

 __
 S. Alexander Jacobson tel:917-770-6565 http://alexjacobson.com
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-12 Thread Sean Perry
Andy Georges wrote:
Hi Kaoru,

I have been working through the exercises in Thompson's The Craft of
Functional Programming 2nd Ed book. I am looking for a solution web
site for Thompson's book. Or maybe the people here can help.
In exercise 4.4, I am asked to define a function
howManyOfFourEqual :: Int - Int - Int - Int - Int
which returns the number of integers that are equal to each other. For
example,
howManyOfFourEqual 1 1 1 1 = 4
howManyOfFourEqual 1 2 3 1 = 2
howManyOfFourEqual 1 2 3 4 = 0

A solution which is applicable to any number of arguments is this:
when this example occurs in the text the new Haskell coder has not been 
introduced to most of what you suggest.

Some of the exercises I felt were meant to be a little painful so that 
when you were introduced to a new concept a chapter or two later you 
would think oh, that would have made X.Y so much easier.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-12 Thread Gour
Kaoru Hosokawa ([EMAIL PROTECTED]) wrote:

 I hope to find a better solution. I googled but couldn't find the 
 answer.

Here is what I have. I do not have working Haskell interpreter at
the moment (being on amd64), but this is what I have in my archive:

weakAscendingOrder :: Int - Int - Int - Bool
weakAscendingOrder a b c
  | (a  b)  (b == c) ||
(a == b)  (b  c)= True
  | otherwise  = False


howManyEqual :: Int - Int - Int - Int
howManyEqual a b c
  | (a == b )  (b == c) = 3
  | weakAscendingOrder a b c  = 2
  | (a /= b)  (b /= c)  = 0


isEqual :: Int - Int - Int - Int - Bool
isEqual x a b c
  | (x == a)   = True
  | (x == b)   = True
  | (x == c)   = True
  | otherwise  = False


howManyOfFourEqual :: Int - Int - Int - Int - Int
howManyOfFourEqual a b c d
  | isEqual a b c d   = howManyEqual b c d + 1
  | otherwise = howManyEqual b c d


Pls. test it ;)

Sincerely,
Gour

-- 
Registered Linux User   | #278493
GPG Public Key  | 8C44EDCD
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parity of the number of inversions of a permutation

2005-03-12 Thread Henning Thielemann
On Fri, 11 Mar 2005, William Lee Irwin III wrote:
On Wed, Mar 09, 2005 at 12:42:09PM +0100, Henning Thielemann wrote:

I'm searching for a function which sorts the numbers and determines the
parity of the number of inversions. I assume that there are elegant and
fast algorithms for this problem (n * log n time steps), e.g. a merge sort
algorithm. A brute force solution with quadratic time consumption is
countInversions :: (Ord a) = [a] - Int
countInversions = sum . map (\(x:xs) - length (filter (x) xs)) . init .
tails
That's not a permutation, that's a cycle. Permutations are sets of
disjoint cycles (which commute).
???
A permutation is a bijective function (here on a finite set), isn't it? 
Ok, the list representation is not immediately a permutation. But why a 
cycle?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-12 Thread Mark Carroll
I had a go with things along this theme and came up with a couple of
options, with different type signatures. I use some functions from the
Data.List library.

If we know that, as with Ints, we are dealing with list members that are
instances of Ord, we can do:

howManyEqual :: (Eq a, Ord a) = [a] - Int

howManyEqual = maximum . (0 :) . map length . group . sort

Otherwise, we end up less efficient, with:

howManyEqual :: Eq a = [a] - Int

howManyEqual = countEach 0
where
countEach best [] = best
countEach best list@(x:_) =
let (xs, others) = partition (== x) list
 in countEach (max (length xs) best) others

-- Mark

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


Re: [Haskell-cafe] Solution to Thompson's Exercise 4.4

2005-03-12 Thread Andy Georges
Hi all,

 when this example occurs in the text the new Haskell coder has not been
 introduced to most of what you suggest.

I didn't realise that. All apologies. 

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


[Haskell-cafe] RE: Newbern's Example 7

2005-03-12 Thread Alson Kemp
Jeff,

Thank you for your reply.

 After fn is lifted, where is bind used in allCombinations?
The bind happens inside the liftM2 function, which can be defined as 
(taken from http://www.haskell.org/onlinereport/monad.html):
liftM2 f =  \a b - do { a' - a; b' - b; return (f a' b') }

Using the above, I think that allCombinations can be rewritten:
 allCombinations fn (l:ls) = 
  foldl (\a b - do { a' - a; b' - b; return (fn a' b') }) l ls

I'm not sure how allCombinations (+) [[1,2][2,3]] gets to the final
result, since the above would seem to yield:
 allCombinations (+) [1,2]:[[2,3]] = 
  foldl (\a b - do { a' - a; b' - b; return (fn a' b') }) [1,2] [[2,3]]
 allCombinations (+) [1,2]:[[2,3]] = 
  return ((+) [1,2] [2,3])

You mentioned on your site that the operation of the List monad is key to
comprehending this function, but I still wasn't able to grok it.  Any
pointers would be appreciated.

- Alson

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


[Haskell-cafe] Re: Solution to Thompson's Exercise 4.4

2005-03-12 Thread Kaoru Hosokawa
Thanks to all the replies!

It seems that there are ways to solve the exercise if I use constructs
that are found in later chapters of the book. Sean could be right in
that some of the exercises are meant to be difficult to solve and they
prepare you for later chapters.

Tried Gour's suggestion, but didn't work for 

howManyOfFourEqual 4 4 2 2 = 3

Anyway the approach was similar to mine, and if I use isEqual  I could
get a simpler solution.

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


Re: [Haskell-cafe] Re: Solution to Thompson's Exercise 4.4

2005-03-12 Thread Sean Perry
Kaoru Hosokawa wrote:
Thanks to all the replies!
It seems that there are ways to solve the exercise if I use constructs
that are found in later chapters of the book. Sean could be right in
that some of the exercises are meant to be difficult to solve and they
prepare you for later chapters.
As a programmer, I was unhappy with my answers to some of the earlier 
exercises because they were clearly inefficient and/or inelegant. This 
kept me reading the book, knowing the answers would present themselves.

On more than one occasion I would fret for a few hours over an exercise 
and then a day or two later learn something new two chapters later which 
 made the exercise much, much easier. Sometimes trivial.

As an aside, I kept all of the exercises in revision control. So I can 
look back at what I first wrote and my later changes. A habit I plan to 
keep as I move on to other programming texts and languages.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Solution to Thompson's Exercise 4.4

2005-03-12 Thread Michael Vanier
 Date: Sat, 12 Mar 2005 23:39:21 -0800
 From: Sean Perry [EMAIL PROTECTED]
 Cc: Haskell-Cafe@haskell.org
 
 As an aside, I kept all of the exercises in revision control. So I can 
 look back at what I first wrote and my later changes. A habit I plan to 
 keep as I move on to other programming texts and languages.

That's a nice approach.  But I can't resist asking: once you've learned
Haskell, what is there left to move on to? ;-)

Mike


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