RE: Working character by character in Haskell

2001-10-19 Thread Simon Marlow

 Humn... I agree with both of you, Albert and Tom. I started 
 it from the
 beginning, using map and don't using reverse anymore. But the 
 C program is
 still 7x faster than the Haskell one. Here is the code of the Haskell
 program:
 
 main :: IO ()
 main = do
  bmFile - openFileEx in.txt (BinaryMode ReadMode)
  bmString - hGetContents bmFile
  writeFile out.txt (map inc bmString)
  hClose bmFile
 
 inc :: Char - Char
 inc a = toEnum ((fromEnum a) + 1)

Well, in Haskell each character of the string takes 20 bytes: 12 bytes
for the list cell, and 8 bytes for the character itself - the memory
used by the character will be recovered at GC time though, as long as
the character is  chr 256.  The map operation also allocates a further
28 bytes per character: list cell + thunk(8) + character, assuming the
inc operation is suitably optimised not to do any extra allocation.
That's a total of 48 bytes per character.

The C code, by comparison, doesn't do any dynamic allocation at all.

To really match the C program, you need to use IOExts.hGetBuf and
IOExts.hPutBuf, and do the operations on raw characters in memory.
Using a UArray of Word8 would be better, but there aren't any operations
to do IO to/from a UArray yet (actually I've written these, but they
aren't in the tree yet).

You should find that the IO library in GHC 5.02 is slightly faster than
the one in 5.00.2.

Anyway, I hope all this helps to explain why the Haskell version is so
slow.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Working character by character in Haskell

2001-10-19 Thread Ketil Malde

Simon Marlow [EMAIL PROTECTED] writes:

 Well, in Haskell each character of the string takes 20 bytes: 12 bytes
 for the list cell, and 8 bytes for the character itself 

Why does a list cell consume as much as 12 bytes?  Two pointers (data
and next) and a 32-bit tag field, perhaps?  And a 64-bit minimum
allocation quatnity, accounting for the 8-byte character?

Isn't it possible to optimize this, e.g. by embedding small data
directly in the cons cell?  21 bits for a Unicode character should
leave enough bits for tagging, shouldn't it?

(Since I'm halfway planning to use Haskell next Spring to process long
lists of data with a small set of values (for instance:

data Base = A | C | G | T

) I'm curious about the performance.)

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

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Strict functions

2001-10-19 Thread Ian Lynagh


Hi all

I've been reading the GHC docs and they say that strict functions are
good for space and time. Section 6.2 goes on to explain how to read the
.hi files to determine the strictness of a function. However, it doesn't
explain all the cases I am seeing. Example of the ones I've noticed are:

V
S(L)V
AAAb
m
C(V)L

What do these mean? And more importantly, how good are they?

Also, the prelude definition of zipWith has LVL whereas the following
definition has LVV. Why is something like the following not used?

 zipWith :: (a-b-c) - [a] - [b] - [c]
 zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
 zipWith _ _  [] = []
 zipWith _ _  _  = []


Thanks
Ian


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Multi-parameter OOP

2001-10-19 Thread George Russell

Recently I've been experimenting with a sort of OOP with GHC, using existential types 
and
(overlapping, undecidable) multi-parameter type classes, but it doesn't seem to work 
as you 
might expect because of the way GHC resolves overloaded functions at compile-time.  
For example, 
given class A a


data WrappedA = forall a . A a = WrappedA a
data A1 = A1 
instance A A1

class B b
data WrappedB = forall b . B b = WrappedB b
data B1 = B1 
instance B B1

class AB a b where
   toBool :: a - b - Bool
instance (A a,B b) = AB a b where
   toBool _ _ = False
instance AB A1 B1 where
   toBool _ _ = True

instance AB WrappedA WrappedB where
   toBool (WrappedA a) (WrappedB b) = toBool a b

a naive user (like me a month ago) might expect that this to work, so that
toBool (WrappedA a) (WrappedB b) will return False unless a is an A1, and b a B1,
in which case it returns True.  In fact ghc5.02 (rightly) gives an error message
with the second instance declaration:
Could not unambiguously deduce (AB a b) from the context (A a, B b)
The choice of (overlapping) instance declaration
depends on the instantiation of `a, b'

So is there any other way of doing this sort of dynamic lookup at runtime, in
a reasonably neat way?

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: Strict functions

2001-10-19 Thread Andrew J Bromage

G'day all.

On Fri, Oct 19, 2001 at 02:30:59PM +0100, Ian Lynagh wrote:

 Also, the prelude definition of zipWith has LVL whereas the following
 definition has LVV. Why is something like the following not used?
 
  zipWith :: (a-b-c) - [a] - [b] - [c]
  zipWith f (a:as) (b:bs) = f a b : zipWith f as bs
  zipWith _ _  [] = []
  zipWith _ _  _  = []

Generally speaking, Haskell programmers don't like inserting more code
with the only effect being to make the function less lazy.  This goes
double for standard library code.

I say generally because occasionally there's a good reason (e.g.
forcing evaluation can make a program more space-efficient).  Is there
a good reason behind your version of zipWith other than the strictness
signature being more symmetrical? :-)

If you really need a reason which doesn't involve bottom, consider a
(fairly common) call such as:

zipWith f xs [1..]

If xs is finite, your version of zipWith would evaluate the infinite
list [1..] one place beyond that which was really needed.

Cheers,
Andrew Bromage

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: Working character by character in Haskell

2001-10-19 Thread Jan-Willem Maessen

Simon Marlow [EMAIL PROTECTED] writes:
 To really match the C program, you need to use IOExts.hGetBuf and
 IOExts.hPutBuf, and do the operations on raw characters in memory.
 Using a UArray of Word8 would be better, but there aren't any
 operations to do IO to/from a UArray yet (actually I've written
 these, but they aren't in the tree yet).

So why don't getContents / putStr / etc. deforest cleanly to calls to
hGetBuf and hPutBuf?  I'm genuinely curious; my own experience in this
direction is The engineering is challenging.  These functions are so
commonly used, though---and they're vastly easier to use, actually
portable, etc.  The effort would surely be repaid.

Plus, I'm curious to hear about any challenges which may be involved
in pulling this off. :-)  If it's genuinely tricky, the tricks are
likely to be generally useful for other stream-ish things.

-Jan-Willem Maessen
Eager Haskell Project
[EMAIL PROTECTED]

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Why is (monad) elegance so costly?

2001-10-19 Thread marku

I am about to rewrite my Z animation tool (JAZA) in a style that
makes more intensive use of state monads.

However, my experiments with a simplified lambda-calculus example
shows that (with GHC 5.00) the state monad is dramatically less
efficient than the simple identity monad:

4 TIMES SLOWER, and
7 TIMES MORE MEMORY!

Is this normal?  Acceptable?  Am I doing something wrong?

Can anyone suggest ways of reducing these overheads?

(I am very keen to use state-monads if possible, because it allows
my 'eval' code to be generic over the monad that is used, which
allows me to reuse the code with other similar monads.  In fact,
I am using it to simulate the 'visitor' design pattern from OO langs.)

Hugs gives slightly smaller differences (3 times more reductions and 
3.5 times more cells), but I had hoped that GHC would be able to
optimize most of the state monad overhead away  (especially when
the monad uses newtype)?

My code and speed measurements are attached.

Mark.


 LambdaCalc.hs


Re: Multi-parameter OOP

2001-10-19 Thread Marcin 'Qrczak' Kowalczyk

Fri, 19 Oct 2001 17:02:54 +0200, George Russell [EMAIL PROTECTED] pisze:

 So is there any other way of doing this sort of dynamic lookup at
 runtime, in a reasonably neat way?

There is module Dynamic. I don't know if it helps or is reasonably
neat.

-- 
 __(  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Your Property Portfolio

2001-10-19 Thread Smith Hawkshaw Properties




 

£ 5 million worth of
Bank  Mortgage Reposessions
Terraced houses
ideal for renting. Tenants waiting.
  SMITH HAWKSHAW 
PROPERTIES
Full Property Management Service
available.
Finance available
from 5% fixed for 5 
years
Our family have been
purveyors of 
properties for over 100 years.
 For further information
either:

visit our web site at www.smithhawkshawproperties.co.uk
or e-mail us on info@smithhawkshawproperties.co.uk
  
Should you not wish to receive any
further information 
e-mailplease click
  on the following address and type 'please remove' in the subject
boxand
  then send - 
[EMAIL PROTECTED]
(interest rates variable)



___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Multi-parameter OOP

2001-10-19 Thread Ashley Yakeley

At 2001-10-19 08:02, George Russell wrote:

a naive user (like me a month ago) might expect that this to work, so that
toBool (WrappedA a) (WrappedB b) will return False unless a is an A1, and 
b a B1, in which case it returns True.

I think existential types are arranged so that Haskell never needs to 
store type information in them at run-time. So you'll never be able to do 
dynamic OOP with them.

One possible extension to Haskell for dynamic OOP, which I never tire of 
suggesting, is the extensible datatype, for instance:

module P
data BaseType = B1 | B2 | _

module Q
data DerivedType = D1 | D2
data BaseType |= BD DerivedType


-- 
Ashley Yakeley, Seattle WA


___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users