Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Ryan Ingram
 Thanks to everyone, especially Bulat Ziganshin.

In http://haskell.org/haskellwiki/Modern_array_libraries there is enough
information to do what I want.  It specifically mentions that it's OK to
pass ByteArray# and MutableByteArray# to an unsafe foreign procedure as
long as that procedure doesn't save the pointer, and that worked for me.

Here is what I ended up using, which worked great and the FFI usage for a
couple of key functions sped up my code by a large factor:
 import Data.Array.Base
import Data.Array.IO.Internals
import GHC.Exts

{-# INLINE unsafeByteArrayToPtr #-}
unsafeByteArrayToPtr :: IOUArray Int Word32 - Ptr Word32
unsafeByteArrayToPtr (IOUArray (STUArray _ _ array#)) = Ptr (unsafeCoerce#
array#)

Possibly a better thing to do would be to declare that the call takes a
MutableByteArray# directly in the foreign import statement, which I believe
would let me avoid using unsafeCoerce# at all, but this was good enough for
my purposes.

Afterwards I used -ddump-simpl to check on the generated Core for the
foreign call and it looked good.

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


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:03:45PM -0700, Ryan Ingram wrote:
  Thanks to everyone, especially Bulat Ziganshin.
 
 In http://haskell.org/haskellwiki/Modern_array_libraries there is enough
 information to do what I want.  It specifically mentions that it's OK to
 pass ByteArray# and MutableByteArray# to an unsafe foreign procedure as
 long as that procedure doesn't save the pointer, and that worked for me.
 
 Here is what I ended up using, which worked great and the FFI usage for a
 couple of key functions sped up my code by a large factor:
  import Data.Array.Base
 import Data.Array.IO.Internals
 import GHC.Exts
 
 {-# INLINE unsafeByteArrayToPtr #-}
 unsafeByteArrayToPtr :: IOUArray Int Word32 - Ptr Word32
 unsafeByteArrayToPtr (IOUArray (STUArray _ _ array#)) = Ptr (unsafeCoerce#
 array#)
 
 Possibly a better thing to do would be to declare that the call takes a
 MutableByteArray# directly in the foreign import statement, which I believe
 would let me avoid using unsafeCoerce# at all, but this was good enough for
 my purposes.
 
 Afterwards I used -ddump-simpl to check on the generated Core for the
 foreign call and it looked good.

Your code is broken in a most evil and insidious way.

Addr# is an uninterpreted address.  Since it might point to arbitrary
memory, or even be a coerced integer, it is meaningless for the garbage
collector to try to follow it.

MutableByteArray#s are objects in the heap, and can move.

If a garbage collection happens after the unsafeCoerce# but before the
foreign call, then you will pass a dangling pointer to memcpy.  Massive
memory corruption will ensue.

As it stands, 1. the garbage collector is only called when all threads
run out of memory in their local 4k blocks and 2. the optimizer will
eliminate all allocation between the Ptr construction and the call.  So
you'll never notice anything wrong.

Suppose some unsuspecting developer tries to compile without
optimizations.  Then that Ptr construction will remain, and each time
your function is called, there is a 1/32,768 chance of catastrophe.
Unreproducable bugs are rarely reported, but they do add to people's
impression of how unstable a language/library is.

But I can just add a comment saying -O only.

Then suppose in the mists of future time one of those parameters of GHC
itself that I described, changes.

Stefan


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


Re: [Haskell-cafe] Dynamic thread management?

2007-08-21 Thread Hugh Perkins
On 8/11/07, Neil Bartlett [EMAIL PROTECTED] wrote:
 You're absolutely right that a dynamic/adaptive approach is the only
 one that will work when the tasks are of unknown size. Whether this
 approach is as easy as you think is open for you to prove. I look
 forward to testing your VM implementation,

Well... obviously migrating Haskell to use a VM is itself non-trivial
;-)  There are two obstacles:
- technical
- political

The technical obstacle means implementing it.  Given that high
performance VMs exist this is largely pure software engineering,
rather than research?

The political obstacle means: pursuading people to use it if it were
written.  If no-one uses it, it wont be maintained, and is basically
pretty useless.  The main reasons why it might not be used are:
- breaks the status quo / de facto standard
- provides no advantage in a single-core environment

Breaking the status quo is not an inconsiderable obstacle, but it
would be broken if there was a real advantage of using automatic
threading, which there is not right now because most machines are
single-cored.  Whilst it's the right time to think about how to
implement things, it's maybe a year or two early to actually implement
it and expect people to use it.

What I think is:
- automatic threading is not really that hard.  Once you've got a pure
FP running in a VM, the actual automatic threading bit is pretty easy
(largely software engineering, not research)
- when machines become multicored, Microsoft will just take F# (which
already runs in a VM I guess? but not sure if it's an FP-dedicated VM,
they might need to build one), and just slot in the automatic
threading bit.

 or at the very least
 reading your paper on the subject ;-)

Writing a paper would be fun.  I think I'm a little out of my depth to
be writing a paper ;-) but just on the off-chance, how does one go
about writing a paper and getting it published?  Does one have to be a
member of an accredited institution, or can one write one as a
freelancer?  If one has to be a member of an accredited institution,
what are the options?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Dynamic thread management?

2007-08-21 Thread Tim Chevalier
On 8/21/07, Hugh Perkins [EMAIL PROTECTED] wrote:
 On 8/11/07, Neil Bartlett [EMAIL PROTECTED] wrote:
  You're absolutely right that a dynamic/adaptive approach is the only
  one that will work when the tasks are of unknown size. Whether this
  approach is as easy as you think is open for you to prove. I look
  forward to testing your VM implementation,

 Well... obviously migrating Haskell to use a VM is itself non-trivial
 ;-)  There are two obstacles:
 - technical
 - political

 The technical obstacle means implementing it.  Given that high
 performance VMs exist this is largely pure software engineering,
 rather than research?


GHCi, of course, is a bytecode interpreter, so that's sort of like a
VM. You might start by looking at how GHCi works and see what you
would need to change if performance rather than interactivity was your
goal.

 The political obstacle means: pursuading people to use it if it were
 written.  If no-one uses it, it wont be maintained, and is basically
 pretty useless.  The main reasons why it might not be used are:
 - breaks the status quo / de facto standard
 - provides no advantage in a single-core environment

 Breaking the status quo is not an inconsiderable obstacle, but it
 would be broken if there was a real advantage of using automatic
 threading, which there is not right now because most machines are
 single-cored.  Whilst it's the right time to think about how to
 implement things, it's maybe a year or two early to actually implement
 it and expect people to use it.


I don't think you have to worry too much about the political
obstacles. People want automatic multithreading, and in a year or two
we'll all have multicore boxen. In any case, if you don't solve the
technical problems, the political ones will never surface; if you
build it, people will come, or if they don't, you at least know
something that you wouldn't have known if you didn't build it :-)

 Writing a paper would be fun.  I think I'm a little out of my depth to
 be writing a paper ;-) but just on the off-chance, how does one go
 about writing a paper and getting it published?  Does one have to be a
 member of an accredited institution, or can one write one as a
 freelancer?  If one has to be a member of an accredited institution,
 what are the options?

Anyone can submit a paper to a CS journal or conference. While most
people who do so are affiliated with universities, research labs, or
(more rarely) non-research companies, there are independent
researchers out there, and sometimes you'll notice a paper where
someone is listed by just their name with no affiliation. Conferences
issue calls for papers (you might see some posted on this mailing
list) that give you an idea for the rough format of the paper and
submission guidelines. But really, you'll want to find a mentor who
can give you advice on how to write a paper that will fit the mold.
First come up with a technical result that you believe is
paper-worthy, then find other people to talk to who can confirm that
opinion and help you get your paper submitted :-)

Cheers,
Tim


-- 
Tim Chevalier * catamorphism.org * Often in error, never in doubt
I cannot remember a time when I did not take it as understood that
everybody has at least two, if not twenty-two, sides to
him.--Robertson Davies
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Donald Bruce Stewart
ryani.spam:
 
 Your code is broken in a most evil and insidious way.
 
 
 
Interesting.  This is for a toy project, so I'm not too
worried, but lets say I wanted to do this correctly and I
was set on using IOUArray for some reason. (The Haskell wiki
claims that StorableArray is slower; is that actually the
case?)
 
 
 
Which of the following fixes would work now?  Which has the
lowest probability of not working in the future?
 
 
 
1) Declare f to take Addr# and don't construct a Ptr Word32
 
I suspect this would be enough unless the GC changed to
some sort of continous GC which can happen even without an
allocation
 
 
 
2) Declare f to take MutableByteArray#
 
Is this good enough to make the collector happy?
 
 
 
3) Something else I haven't thought of?
 
If there was no other option, and StorableArray wasn't
slower, and I was working on a real project, I'd probably
wrap my own around ForeignPtr like Data.ByteString.

Yeah, we have ForeignPtr arrays and Foreign.Array /exactly/ for calling
to C safely. I don't know why people suggest all these other dodgy
solutions, when there's one that's guaranteed by the FFI spec to work.

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


Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:47:06PM -0700, Ryan Ingram wrote:
  Your code is broken in a most evil and insidious way.
 
 Interesting.  This is for a toy project, so I'm not too worried, but lets
 say I wanted to do this correctly and I was set on using IOUArray for some
 reason.

Heh, I'm a lot less worried now.  (Somehow I thought this was going into
a high-visibility library!)

 (The Haskell wiki claims that StorableArray is slower; is that
 actually the case?)

Good question!  I wrote a basic CA benchmark and a much simpler array
benchmark, both parameterized by the array type, and couldn't get
consistent results, so I'll take this as a no.

[EMAIL PROTECTED]:/tmp$ cat ArrayTest.hs
{-# OPTIONS_GHC -fglasgow-exts -cpp #-}

import Data.Array.MArray
import Data.Bits
import Data.Array.IO
import Data.Array.Base
import Data.Array.Storable
import GHC.Exts

-- #define ARRAY IOUArray

-- uch!

iter :: Int - ARRAY Int Word - IO ()
iter 4096 arr = arr `seq` return ()
iter ix   arr = do
unsafeWrite arr ix . succ = unsafeRead arr ix
iter (ix+1) arr

bench 10 arr = arr `seq` return ()
bench ct arr = do
iter 0 arr
bench (ct+1) arr

main = do
arr - newListArray (0,4095) [1..]
bench 0 arr

print = getElems arr
[EMAIL PROTECTED]:/tmp$ ghc -fforce-recomp -DARRAY=IOUArray -O2 ArrayTest.hs  
time ./a.out  /dev/null

real0m2.006s
user0m2.028s
sys 0m0.008s
[EMAIL PROTECTED]:/tmp$ ghc -fforce-recomp -DARRAY=StorableArray -O2 
ArrayTest.hs  time ./a.out  /dev/null

real0m1.845s
user0m1.872s
sys 0m0.004s
[EMAIL PROTECTED]:/tmp$ 


 Which of the following fixes would work now?  Which has the lowest
 probability of not working in the future?
 
 1) Declare f to take Addr# and don't construct a Ptr Word32
 I suspect this would be enough unless the GC changed to some sort of
 continous GC which can happen even without an allocation

Would work now, I think.

 2) Declare f to take MutableByteArray#
 Is this good enough to make the collector happy?

Maybe.  In theory the collector should know that an argument passed to a
foreign function as a pointer type, should be followed.  I'd tentatively
call it a bug if this breaks, but it's fragile enough that you should
expect to find yourself reporting said bug.

 3) Something else I haven't thought of?

 If there was no other option, and StorableArray wasn't slower, and I was
 working on a real project, I'd probably wrap my own around ForeignPtr like
 Data.ByteString.

Stefan


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


Re[2]: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Bulat Ziganshin
Hello Stefan,

Tuesday, August 21, 2007, 10:08:59 AM, you wrote:

 Your code is broken in a most evil and insidious way.

and this code, too? :)

freezeSTUArray :: Ix i = STUArray s i e - ST s (UArray i e)
freezeSTUArray (STUArray l u marr#) = ST $ \s1# -
case sizeofMutableByteArray# marr#  of { n# -
case newByteArray# n# s1#   of { (# s2#, marr'# #) -
case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -
case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -
(# s4#, UArray l u arr# #) 

 Unreproducable bugs are rarely reported, but they do add to people's
 impression of how unstable a language/library is.




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: Re[2]: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Ryan Ingram
Ah, sneaky.  That code is fine because it uses unsafeCoerce# on memcpy,
changing memcpy from whatever type it is, into
MutableByteArray# s# - MutableByteArray# s# - Int# - s# - (# s#, () #)

So as long as the GC understands MutableByteArray# it's safe; it's relying
on the C calling convention being handled properly.

On 8/21/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

 Hello Stefan,

 Tuesday, August 21, 2007, 10:08:59 AM, you wrote:

  Your code is broken in a most evil and insidious way.

 and this code, too? :)

 freezeSTUArray :: Ix i = STUArray s i e - ST s (UArray i e)
 freezeSTUArray (STUArray l u marr#) = ST $ \s1# -
case sizeofMutableByteArray# marr#  of { n# -
case newByteArray# n# s1#   of { (# s2#, marr'# #) -
case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -
case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -
(# s4#, UArray l u arr# #) 

  Unreproducable bugs are rarely reported, but they do add to people's
  impression of how unstable a language/library is.




 --
 Best regards,
 Bulatmailto:[EMAIL PROTECTED]


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


Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-21 Thread ajb

G'day all.

Quoting David Ritchie MacIver [EMAIL PROTECTED]:


I was playing with some code for compiling regular expressions to
finite state machines and I ran into the following problem. I've solved
it, but I'm not terribly happy with my solution and was wondering if
someone could come up with a better one. :-)


Doing structural induction is quite viable, as you noted.

However, there are advantages to implementing explicit indirection.
The main one is memory usage.  Explicit indirection is much less
leak-prone, and you can easily share structures thanks to hash consing.

At any rate, I'm extremely curious as to how your code compares with
mine, performance-wise:

   http://www.ninebynine.org/Software/HaskellRDF/Dfa/Dfa.lhs

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


Re: Re[2]: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 12:50:22AM -0700, Ryan Ingram wrote:
 Ah, sneaky.  That code is fine because it uses unsafeCoerce# on memcpy,
 changing memcpy from whatever type it is, into
 MutableByteArray# s# - MutableByteArray# s# - Int# - s# - (# s#, () #)
 
 So as long as the GC understands MutableByteArray# it's safe; it's relying
 on the C calling convention being handled properly.

Which still isn't quite correct, because the code for
base-2.1:Data.Array.Base.memcpy could still be perverse and trigger a
GC.  However, since base is version-locked to GHC, it can depend on as
much undocumented behaviour as it needs.  The worst that can happen is a
few more testsuite failures when someone tries to change the compiler.

 On 8/21/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:
 
  Hello Stefan,
 
  Tuesday, August 21, 2007, 10:08:59 AM, you wrote:
 
   Your code is broken in a most evil and insidious way.
 
  and this code, too? :)
 
  freezeSTUArray :: Ix i = STUArray s i e - ST s (UArray i e)
  freezeSTUArray (STUArray l u marr#) = ST $ \s1# -
 case sizeofMutableByteArray# marr#  of { n# -
 case newByteArray# n# s1#   of { (# s2#, marr'# #) -
 case unsafeCoerce# memcpy marr'# marr# n# s2# of { (# s3#, () #) -
 case unsafeFreezeByteArray# marr'# s3# of { (# s4#, arr# #) -
 (# s4#, UArray l u arr# #) 
 
   Unreproducable bugs are rarely reported, but they do add to people's
   impression of how unstable a language/library is.

Stefan


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


Re[2]: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Bulat Ziganshin
Hello Ryan,

Tuesday, August 21, 2007, 10:47:06 AM, you wrote:

 Your code is broken in a most evil and insidious way.
   
  Interesting.  This is for a toy project, so I'm not too worried,
 but lets say I wanted to do this correctly and I was set on using
 IOUArray for some reason. (The Haskell wiki claims that
 StorableArray is slower; is that actually the case?)

it was in 6.4. in 6.6 it has the same speed as IOArray

the Arrays wiki page was written primarily by me and suggestion to use
unsafeCoerce# based solely on the code fragment i just citated. so
this page is broken in that it says primarily about rather old 6.4
version and that it suggests unreliable trick without much
understanding of ghc intrinsics :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] can't build haxml under ghc 6.7, says HughesPJ is hidden... but ghc-pkg doesn't say it's hidden...

2007-08-21 Thread Malcolm Wallace
I wrote:
  Just for information, the HaXml darcs repo has recently adopted the
  solution of containing two .cabal files, one for ghc-6.6.x, and the
  other for the split-base packages (=ghc-6.7).

Thomas Hartman [EMAIL PROTECTED] wrote:
 $ runghc Setup.hs configure
 Setup.hs: Multiple description files found.  Please use only one of : 
 [HaXml.cabal,HaXml-darcs.cabal]
 
 is there a way to specify which cabal file should be used, or do you
 just  have to  move a file out out the way?

For now, the latter (remove the unneeded file).  Ultimately, the use of
Cabal Configurations will allow us to revert to a single .cabal file
with sections conditional on the compiler version.

 Understanding this better is important to me because I am installing a
 number of packages on 6.7, and am reluctant to send a patch that
 breaks  backwards compabitility with earlier versions.

Multiple .cabal files are just a temporary measure for development ease.
Neither ghc-6.7 nor this version of HaXml have been released officially,
so you should not rely on any particular behaviour.

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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Philip Armstrong

On Mon, Aug 20, 2007 at 09:57:38PM +0100, Simon Peyton-Jones wrote:

GHC does some constant folding, but little by way of strength
reduction, or using shifts instead of multiplication.  It's pretty
easy to add more: it's all done in a single module.  Look at
primOpRules in the module PrelRules.

Patches welcome!  But please also supply test-suite tests that check
the correctness of the rules.


Sucking another example out of comp.lang.functional:

This:

  import System

  f :: Int - Int - Int
  f s n = if n  0 then f (s+n) (n-1) else s

  main = do
[n] - getArgs
putStrLn $ show $ f 0 (read n) 


is 3-4x slower than this:

  #include stdio.h
  #include stdlib.h
  #include assert.h

  int f(int s, int n) { 
return n  0 ? f(s+n, n-1) : s;

  }

  int main(int argc, char *argv[]) { 
assert(argc == 2);

printf(%d\n, f(0, strtol(argv[1],0,0)));
  }

The generated assembler suggests (if I've read it correctly) that gcc
is spotting that it can replace the tail call with a jump in the C
version, but for some reason it can't spot it for the Haskell version
when compiling with -fvia-C (and neither does ghc itself using
-fasm). So the haskell version ends up pushing and popping values on
and off the stack for every call to f, which is a bit sad.

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Donald Bruce Stewart
phil:
 On Mon, Aug 20, 2007 at 09:57:38PM +0100, Simon Peyton-Jones wrote:
 GHC does some constant folding, but little by way of strength
 reduction, or using shifts instead of multiplication.  It's pretty
 easy to add more: it's all done in a single module.  Look at
 primOpRules in the module PrelRules.
 
 Patches welcome!  But please also supply test-suite tests that check
 the correctness of the rules.
 
 Sucking another example out of comp.lang.functional:
 
 This:
 
   import System
 
   f :: Int - Int - Int
   f s n = if n  0 then f (s+n) (n-1) else s
 
   main = do
 [n] - getArgs
 putStrLn $ show $ f 0 (read n) 
 
 is 3-4x slower than this:
 
   #include stdio.h
   #include stdlib.h
   #include assert.h
 
   int f(int s, int n) { 
 return n  0 ? f(s+n, n-1) : s;
   }
 
   int main(int argc, char *argv[]) { 
 assert(argc == 2);
 printf(%d\n, f(0, strtol(argv[1],0,0)));
   }
 
 The generated assembler suggests (if I've read it correctly) that gcc
 is spotting that it can replace the tail call with a jump in the C
 version, but for some reason it can't spot it for the Haskell version
 when compiling with -fvia-C (and neither does ghc itself using
 -fasm). So the haskell version ends up pushing and popping values on
 and off the stack for every call to f, which is a bit sad.
 

That doesn't sound quite right. The C version should get a tail call ,
with gcc -O2, the Haskell version should be a tail call anyway.

Let's see:

C
$ gcc -O t.c -o t 
$ time ./t 10
zsh: segmentation fault (core dumped)  ./t 10
./t 10  0.02s user 0.22s system 5% cpu 4.640 total

Turning on -O2

$ time ./t 10
-243309312
./t 10  1.89s user 0.00s system 97% cpu 1.940 total


And GHC:

$ ghc -O2 A.hs -o A
$ time ./A 10   
   
-243309312
./A 10  3.21s user 0.01s system 97% cpu 3.289 total

So, what, 1.6x slower than gcc -O2
Seems ok without any tuning.

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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Rodrigo Queiro
On my system, the C version runs about 9x faster than the haskell
version (with -O3 and -O2 -fvia-c -optc-O3 respectively). However, GCC
seems to produce about 70 lines of assembly for the main loop,
compared to about 10 from GHC. I suspect the speed difference is the
result of some heavy optimisation by GCC, which would need to be
hand-tuned for GHC. (I would be interested to see what this would be.
Unfortunately I don't know x86 assembly well enough to understand the
GCC output.)

On 21/08/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:
 phil:
  On Mon, Aug 20, 2007 at 09:57:38PM +0100, Simon Peyton-Jones wrote:
  GHC does some constant folding, but little by way of strength
  reduction, or using shifts instead of multiplication.  It's pretty
  easy to add more: it's all done in a single module.  Look at
  primOpRules in the module PrelRules.
  
  Patches welcome!  But please also supply test-suite tests that check
  the correctness of the rules.
 
  Sucking another example out of comp.lang.functional:
 
  This:
 
import System
 
f :: Int - Int - Int
f s n = if n  0 then f (s+n) (n-1) else s
 
main = do
  [n] - getArgs
  putStrLn $ show $ f 0 (read n)
 
  is 3-4x slower than this:
 
#include stdio.h
#include stdlib.h
#include assert.h
 
int f(int s, int n) {
  return n  0 ? f(s+n, n-1) : s;
}
 
int main(int argc, char *argv[]) {
  assert(argc == 2);
  printf(%d\n, f(0, strtol(argv[1],0,0)));
}
 
  The generated assembler suggests (if I've read it correctly) that gcc
  is spotting that it can replace the tail call with a jump in the C
  version, but for some reason it can't spot it for the Haskell version
  when compiling with -fvia-C (and neither does ghc itself using
  -fasm). So the haskell version ends up pushing and popping values on
  and off the stack for every call to f, which is a bit sad.
 

 That doesn't sound quite right. The C version should get a tail call ,
 with gcc -O2, the Haskell version should be a tail call anyway.

 Let's see:

 C
 $ gcc -O t.c -o t
 $ time ./t 10
 zsh: segmentation fault (core dumped)  ./t 10
 ./t 10  0.02s user 0.22s system 5% cpu 4.640 total

 Turning on -O2

 $ time ./t 10
 -243309312
 ./t 10  1.89s user 0.00s system 97% cpu 1.940 total


 And GHC:

 $ ghc -O2 A.hs -o A
 $ time ./A 10
 -243309312
 ./A 10  3.21s user 0.01s system 97% cpu 3.289 total

 So, what, 1.6x slower than gcc -O2
 Seems ok without any tuning.

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

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


[Haskell-cafe] Re: Tying the knot with unknown keys

2007-08-21 Thread ChrisK
David Ritchie MacIver wrote:
 I was playing with some code for compiling regular expressions to finite
 state machines and I ran into the following problem. I've solved it, but
 I'm not terribly happy with my solution and was wondering if someone
 could come up with a better one. :-)
 
 Essentially I have
 
 data FSM = State { transitions :: (Map Char FSM) }
 
 and
 
 transitions' :: Regexp - Map Char Regexp
 
 I want to lift this so that the Regexps become states of the finite
 state machine (while making sure I set up a loop in the data structure).
 Tying the knot is the traditional way of doing such things, but we
 couldn't figure out a way to make it work without the set of keys known
 in advance because of the strictness of Map in its keys (an association
 list was suggested, and that would probably work, but it seemed a bit
 ugly and would be fairly inefficient).
 
 In the end what I did was just work out the set of reachable regexps in
 advance and use a standard tying the knot trick, but it felt vaguely
 unsatisfactory (and does some repeat work which I felt should be
 unneccessary). Anyone have a more elegant suggestion?
 
 Regards,
 David

As others have pointed out, the decision to use Data.Map is a limiting issue.

Another approach is the combinator method in CTK Light
http://www.cse.unsw.edu.au/~chak/haskell/ctk/ which was specialized and enhanced
for regexp in the regex-dfa package [1].  This lazily constructs a DFA from the
regular expression.  The tying the knot happens in the definition of the
'star' combinator (the '*' regexp character, also implied by '+').  The problem
with this elegant definition is that it fails badly if the pattern being
repeated might succeed after consuming zero characters (it hangs in an infinite
loop).  Other than that it is a wonderful definition:

 type Regexp = Lexer - Lexer

 -- star re1 re2 means repeat re1 follow with re2: ((re1)*)(re2)
 star :: Regexp - Regexp - Regexp
 star re1 re2  = \l - let self = re1 self || re2 l in self


My regex-tdfa package did something quite different since it has to deal with a
lot of extra complexity.  It works in a few stages, in particular because it
needs the NFA states to handle subexpression captures and because it has to
handle anchors like ^ and $.

String of regexp = Parsec extended regexp parser = parse tree data type

parse tree = complicated analyzer (uses mdo) = smarter tree data type

smarter tree = My complicated assembly monad (uses mdo) = Array Int NFA

Where a simplified description of NFA is something like
data NFA = NFA Int Trans
data Trans = Trans (Map Char (Set Int))-- Might lead to more than one NFA state
I could just as easily have made this
data Trans = Trans (Map Char (Set NFA))
or
data Trans = Trans (Map Char (Set Trans))
by doing a lazy lookup into the array, but it would then not have been as easy
to make the DFA in the next step:

Array Int NFA = Use of Trie indexed by (Set Int) = DFA

Where a simplified DFA is like
data DFA = DFA (Set Int) (Map Char DFA)
and the Trie means I can lazily lookup any subset of NFA state and get their
merge DFA state.

So the procedure starts with a simple empty winning NFA to the right of the
parse tree.  The rexgexp tree walk is done in a monad which provides the supply
of unique Int index when a new NFA state is created.  The last NFA state to be
created is the unique start state which always gets the largest Int index.

The tying the knot trick in building the NFA was handled by walking the regexp
parse tree where each node is attached to an NFA representing the future
continuation from that node.  The tricky case was the one that kills the simple
tying the knot in CTK Light's method: when you have 'p*' and 'p' might match
zero characters.  The continuation needed to describe the future in that case
had to be supplied in a more complicated form while walking 'p' to avoid the
infinite looping.

There are no mutable STRef/IORef variables.  All the NFA nodes that are created
during the monadic traversal are part of the final NFA (so there is no wasted
work even though I make a single walk through the tree).  The resulting NFA is
not as minimal as the differentiation method since my traversal does not look at
whether characters in the regexp are equal (my NFA builder is equivalent to
treating all the regexp characters are distinct).  But this also means I do not
have the combinatoric explosion of regexps that the differentiation method can
produce.  I kept improving the design until it reproduced the same kinds of NFA
graphs I could produce manually under those assumptions.

The typical NFA state represents the condition you have just accepted character
X in the regexp.  This is different from the Thompson NFA where states usually
mean you have just accepted a character leading to character X in the regexp.

The NFA that regexp-tdfa produces
  * has no empty transitions
  * Captures extended regexp Posix semantics (difficult with empty matches)
  * handles anchors 

Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 01:14:20PM +0100, Rodrigo Queiro wrote:
 On my system, the C version runs about 9x faster than the haskell
 version (with -O3 and -O2 -fvia-c -optc-O3 respectively). However, GCC
 seems to produce about 70 lines of assembly for the main loop,
 compared to about 10 from GHC. I suspect the speed difference is the
 result of some heavy optimisation by GCC, which would need to be
 hand-tuned for GHC. (I would be interested to see what this would be.
 Unfortunately I don't know x86 assembly well enough to understand the
 GCC output.)

The fundamental problem is that GHC doesn't have enough registers to to
a good job with Haskell.  Normal Haskell code  makes extensive use of
the GHC stack for function calls, the C stack for signal handlers, the
capability base pointer for thread state, and the heap for everything
else.  Which doesn't really leave us in a good state for optimizing.  In
particular, x86 ghc ALWAYS passes parameters on the stack, even for tail
calls.  I didn't actually bother to check, but I'm pretty sure that's
what the OP was noticing - if you look carefully it's not actually
pushing or popping anything, just using stack memory.

Situations are far better on x86_64 (16 registers) and ppc (32
registers).  There is some work being done on the backend to improve
this (in particular, a new and much better register allocator and a
parameter-aware Cmm system).

Stefan


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


Re: [Haskell-cafe] Dynamic thread management?

2007-08-21 Thread Hugh Perkins
On 8/21/07, Tim Chevalier [EMAIL PROTECTED] wrote:
 I don't think you have to worry too much about the political
 obstacles. People want automatic multithreading, and in a year or two
 we'll all have multicore boxen. In any case, if you don't solve the
 technical problems, the political ones will never surface; if you
 build it, people will come, or if they don't, you at least know
 something that you wouldn't have known if you didn't build it :-)

Ok, that's good encouragement.  Practical question: I dont have a
multicore box ;-)  It's my main show-stopper right now.  Any clues on
how to get access to one, eg via ssh?  32-core or higher would be
favorite ;-) but I guess even just a 4-core or so is enough for
proof-of-concept?

 GHCi, of course, is a bytecode interpreter, so that's sort of like a
 VM. You might start by looking at how GHCi works and see what you
 would need to change if performance rather than interactivity was your
 goal.

Yes, I guess two approaches are to take GHCi and make it handle
automatic threading, but keeping the interactivity, ie not seeking to
rival ghc in real performance, but merely providing a PoC, ...

... or build a minimal vm, enough to get 3 or 4 somewhat interesting
algorithms / programs to run, and get automatic threading working on a
couple of targets, eg on maps, and whatever [ x | x - somelist ]
these things are called.  (folds are a little harder from an
implementation point of view, so can be a future upgrade).

 Anyone can submit a paper to a CS journal or conference. While most
 people who do so are affiliated with universities, research labs, or
 (more rarely) non-research companies, there are independent
 researchers out there, and sometimes you'll notice a paper where
 someone is listed by just their name with no affiliation.

Again, that's quite encouraging :-)  I'm far too lazy to sign my life
away for 7 years of phd :-D  (unless someone knows anyone looking for
phd students in somewhere exotic like Paris, China or Singapore???),
but working on it in my own time sounds fun.

 First come up with a technical result that you believe is
 paper-worthy

I guess a paperworthy technical result doesnt have to be a fully
fledged Haskell VM with in-depth automatic threading?, but either GHCi
with some simple automatic threading, or a minimal vm implementation,
again with some simple automatic threading?

Basically, we give it one or three algorithms with automatic threading
switched off, time execution, then run it on (ideally 32 or 64 cores
but 4 is ok) a multicore machine, and show that the execution elapsed
time is less?

 But really, you'll want to find a mentor who
 can give you advice on how to write a paper that will fit the mold.
, then find other people to talk to who can confirm that
 opinion and help you get your paper submitted :-)

Would you or Neil fancy being a mentor for this, if I can start to get
somewhere on it?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread Hugh Perkins
 Exactly. For this to work there needs to be the constraint that there's a
 one-to-one mapping in each direction. The Bimap should have the uniqueness
 promise that Set (k, v) gives. Yet you should be able to search on either
 tuple value.

Or... have the possibility of returning a list of values.

Arguably there are two possible implementations, one that enforces
one-to-one mapping, and one which allows multiple values, in either
direction.

But how can you change a value if there are non-unique keys?.  Well,
you dont change a value, you change a list of values ;-)

So, let's say our bimap is:

1,1
1,2
5,2
5,3

then:

bimap_getvalue ourbimap 1 gives  [1,2]
bimap_getkey ourbimap 2 gives [1,5]

Executing bimap_setkey ourbimap 2 [1,4] changes the bimap to:

1,1
1,2
4,2
5,3
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Philip Armstrong

On Tue, Aug 21, 2007 at 05:25:49AM -0700, Stefan O'Rear wrote:

On Tue, Aug 21, 2007 at 01:14:20PM +0100, Rodrigo Queiro wrote:

On my system, the C version runs about 9x faster than the haskell
version (with -O3 and -O2 -fvia-c -optc-O3 respectively). However, GCC
seems to produce about 70 lines of assembly for the main loop,
compared to about 10 from GHC. I suspect the speed difference is the
result of some heavy optimisation by GCC, which would need to be
hand-tuned for GHC. (I would be interested to see what this would be.
Unfortunately I don't know x86 assembly well enough to understand the
GCC output.)


GCC is carrying out two major optimisations that ghc is missing here:
replacing the tail call with a jump directly into the function body
(having stuffed the correct arguments into the appropriate registers)
and unrolling the loop. That's pretty much it. Neither are what I'd
call 'heavy' optimisations.


The fundamental problem is that GHC doesn't have enough registers to to
a good job with Haskell.  Normal Haskell code  makes extensive use of
the GHC stack for function calls, the C stack for signal handlers, the
capability base pointer for thread state, and the heap for everything
else.  Which doesn't really leave us in a good state for optimizing.  In
particular, x86 ghc ALWAYS passes parameters on the stack, even for tail
calls.  I didn't actually bother to check, but I'm pretty sure that's
what the OP was noticing - if you look carefully it's not actually
pushing or popping anything, just using stack memory.


Yes, absolutely.


Situations are far better on x86_64 (16 registers) and ppc (32
registers).  There is some work being done on the backend to improve
this (in particular, a new and much better register allocator and a
parameter-aware Cmm system).


fires up ppc box

Ouch. That's even worse:

$ ./sum 1

C version: 0.16s
Haskell  : 1.40s

Looking at the generated assembler, the ppc version has exactly the
same problem that the x86 version does. It carries out the
calculation, the stores the result in some memory locations and calls f
again so that the preamble to f can pull those same results out of the
memory locations in order to put them back into the same registers
again!

(I'm using ghc 6.6.1 on Debian unstable btw for anyone following along.)

cheers, Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: I'm stuck in my thought experiment

2007-08-21 Thread Al Falloon

Levi Stephen wrote:

Al Falloon wrote:
This code seems to indicate that you want to be able to extend the 
widget types without changing this source file. This is a good goal, 
but it may not be worth the extra complexity.


Ideally, I'd like Widgets to be added through hs-plugins or similar. That
is a ideal goal though, not a necessity.


Also, this looks a lot like the Composite pattern from OO. A rule of 
thumb that I use is: if I would do this with inheritance in OO, I 
probably want a variant in FP. Since Composite depends on the 
inheritance of the composite object type, I would probably look to use 
a  single data type with multiple constructors for the different 
compisites like the Widget type above.


Interesting. I've been curious how OO concepts can map to FP, as most specs
(consider stuff like DOM) seem to be written with OO implementaitons in 
mind.


This is a very interesting discussion that could be its own text book 
(or flame war) as far as I can tell, the only answer everyone agrres on 
is it depends. After that it gets a little hairy.


For me, I find that the best method is to just come at the problem fresh 
using an FP approach, and don't worry about 'mapping' the concepts.


If I wanted to develop the widgets themselves separately from the 
layout, I would probably do something like this:


class Widget a where
render :: a - Html
bbox :: a - Size

type Layout = forall a. Widget a = Widget a
| Rows Spacing [Layout]
| Columns Spacing [Layout]
| Grid Spacing [[Layout]]

type Page = Page String Layout

renderLayout :: Layout - Html

renderPage :: Page - Html


I'm unsure this gives what I'm after. I'm trying to have layouts consist 
of Widgets (e.g., header images, common menu), and as pages also consist 
of Widgets it seems like they can be modelled using a common 
type/construct.


Well if you want to abstract over the layout too, you can just add

instance Widget Layout where
render = renderLayout
bbox = ...

But just because you can, doesn't mean you should. I don't know the full 
details of your design, but what do you gain by allowing the layout to 
intermingle with the widgets? Is worth the extra complexity?


If you treat layout as just another widget then it becomes harder to 
answer specific questions about the page layout because you have less 
information in your tree.



So you want some sort of wildcard element that can be substituted in
later? Maybe I am misunderstanding your requirement, but if thats the
behavior you want, you should check out the term-level evaluators for
lambda calculus for inspiration on substitution, but I expect your
requirement may be simpler than that.


I'm thinking a BlankWidget or ReplacableWidget is a fairly simple 
option. They could be named for the case of multiple replacements, and 
have a method similar to


-- src   -   replacements- result
replaceWidgets :: Widget - [(String,Widget)] - Widget

which replaces all ReplacableWidgets in the source Widget with those 
specified.


Would you happen to have some links on the evaluators for lambda 
calculus you talk about? I'm not as familiar as I should be with lambda 
calculus


They are surprisingly hard to find! It must be one of those things that 
is so ingrained that no-one thinks to write it down. Anyway, the closest 
I could find to what I meant is the Interpretive Haskell programmer 
heading in The evolution of a Haskell programmer 
http://www.willamette.edu/~fruehr/haskell/evolution.hs


However, now that I look at your example again, I may have been too 
quick to answer with LC evaluator! because your language only has 
substitution and not abstraction (defining functions) so you don't have 
much of the complexity to contend with.


The obvious implementation of replaceWidgets will probably work fine for 
you.



It might be simple to have a PlaceHolderWidget. Then insertions of 
the child page

content happens at each of those widgets.


This just gets trickier if I start considering multiple extension 
points for child
pages and what happens when the layout/parent page changes. This is 
why I'm

thinking I may be going along a bad path here.


Exactly. With multiple substitutions you get into issues of naming, so 
thats why looking at lambda calculus evaluators would be the right 
inspiration, but I think it may be more complicated than you need. The 
zipper approach might be easier.


I think I will try and investigate both approaches. I'm after the 
process here, rather than the end result


Good luck.

You can learn a lot just by lurking on the cafe and reading some of the 
better blogs. The papers are also good reading, I have a rule of 2 if 
I have heard the title come up twice, I read it.


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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Philip Armstrong

Don's reply didn't reach me for some reason, but pulling it out of the
previous response:


On 21/08/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote:

phil:
 The generated assembler suggests (if I've read it correctly) that gcc
 is spotting that it can replace the tail call with a jump in the C
 version, but for some reason it can't spot it for the Haskell version
 when compiling with -fvia-C (and neither does ghc itself using
 -fasm). So the haskell version ends up pushing and popping values on
 and off the stack for every call to f, which is a bit sad.


That doesn't sound quite right. The C version should get a tail call ,
with gcc -O2, the Haskell version should be a tail call anyway.


Just to be clear; the Haskell version is a tail call, but it's pushing
the values to and from memory (well, cache really of course) for every
call to f, which is killing the performance.


Let's see:

C
$ gcc -O t.c -o t
$ time ./t 10
zsh: segmentation fault (core dumped)  ./t 10
./t 10  0.02s user 0.22s system 5% cpu 4.640 total

Turning on -O2

$ time ./t 10
-243309312
./t 10  1.89s user 0.00s system 97% cpu 1.940 total


-O3 does better thanks to the loop unrolling, see timings bellow.


And GHC:

$ ghc -O2 A.hs -o A
$ time ./A 10
-243309312
./A 10  3.21s user 0.01s system 97% cpu 3.289 total

So, what, 1.6x slower than gcc -O2
Seems ok without any tuning.


You're getting much better timings than I am!

$ time -p ./sum-hs 10
-243309312
real 3.75
user 3.70
$ time -p ./sum-c-O2 10
-243309312
real 1.40
user 1.35
$ time -p ./sum-c-O3 10
-243309312
real 1.21
user 1.18

(My box has a AMD Athlon64 3000+ CPU fwiw, but the powerpc version is
even worse when compared to it's respective C binary!)

Phil

--
http://www.kantaka.co.uk/ .oOo. public key: http://www.kantaka.co.uk/gpg.txt
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Hugh Perkins
On 8/21/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
 Currently, it's never worse.  GHC's backend is about as good as GCC;
 most of the optimiations it doesn't do are not possible for GCC because
 of various lack-of-information problems (the stack pointer never aliases
 the heap pointer, stuff like that).  It's conceivable that at some point
 -fasm will be faster, because you have the possibility of much more
 accurate aliasing information inside the compiler, than can be coded in
 C.  In the meantime, note that the runtime difference is less than 3%
 and the compile time difference is over 100%, so it's only worthwhile if
 you expect *this version* of your program to be used more than 30 times,
 ie releases only.

Wait, you're saying that ghc can produce pure c-code, that doesnt
contain any assembly code, and that runs as fast as ghc code that does
contain assembly?

Sooo if I was feeling evil, could I take this c-code and pipe it
into something that turns it into C#???   If it contains lots of
macros (or any macros at all perhaps...), this becomes non-trivial,
but otherwise I think most things in C can be mapped fairly trivially
to C#?  (It's a one-way mapping of course, eg delete in C is simply
dropped when mapped to c#).

(Not that I have any good reason to do this, simply... fun).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Neil Mitchell
Hi

 Wait, you're saying that ghc can produce pure c-code, that doesnt
 contain any assembly code, and that runs as fast as ghc code that does
 contain assembly?

No. It can produce pure C code (unregistered), but to get high
performance it processes the output assembly afterwards (registered).

 Sooo if I was feeling evil, could I take this c-code and pipe it
 into something that turns it into C#???

You might be able to. Much easier would be to use Yhc and pass the
--dotnet flag which generates .NET binaries natively.

 macros (or any macros at all perhaps...), this becomes non-trivial,
 but otherwise I think most things in C can be mapped fairly trivially
 to C#?  (It's a one-way mapping of course, eg delete in C is simply
 dropped when mapped to c#).

There isn't going to be much free/delete, its all a garbage collected heap.

Thanks

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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 09:39:32PM +0800, Hugh Perkins wrote:
 On 8/21/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
  Currently, it's never worse.  GHC's backend is about as good as GCC;
  most of the optimiations it doesn't do are not possible for GCC because
  of various lack-of-information problems (the stack pointer never aliases
  the heap pointer, stuff like that).  It's conceivable that at some point
  -fasm will be faster, because you have the possibility of much more
  accurate aliasing information inside the compiler, than can be coded in
  C.  In the meantime, note that the runtime difference is less than 3%
  and the compile time difference is over 100%, so it's only worthwhile if
  you expect *this version* of your program to be used more than 30 times,
  ie releases only.
 
 Wait, you're saying that ghc can produce pure c-code, that doesnt
 contain any assembly code, and that runs as fast as ghc code that does
 contain assembly?

No.

Name:Registerized C
Performance: 1.00
Flags:   -fvia-C

C, but with gcc and machine specific hacks to implement general tail
calls and (most notably) register global variables.

Name:Native code generator
Performance: 0.97
Flags:   -fasm

GHC's own mini C compiler converts the internal C-- data into assembly
code, which is then piped to gas.

Name:Unregisterized C
Performance: 0.40
Flags:   -unreg

Generates near-ANSI C, using memory variables for the VM's registers and
the returning function pointer hack seen in oh so many Scheme compilers.
Good for early stages of porting, and not much else.

Name:Byte-code
Performance: 0.05
Flags:   -fbyte-code (GHCi HEAD only)

Generates a compact form of STG code, and then interprets it.  A
generally quite bad idea, whose main redeeming feature is that it
doesn't require starting the GNU toolchain.

 Sooo if I was feeling evil, could I take this c-code and pipe it
 into something that turns it into C#???

Yes.  You could do the same with the original haskell.  It's called a
compiler.

 If it contains lots of macros (or any macros at all perhaps...), this
 becomes non-trivial,

I fail to see how macros have anything to do with this.  Especially
since cpp removes them all.

 but otherwise I think most things in C can be mapped fairly trivially
 to C#?

Unsafe C#, sure.  Haskell's type system is strictly more expressive than
C#, and you need to sacrifice either machine efficiency or checked
safety.

 (It's a one-way mapping of course, eg delete in C is simply dropped
 when mapped to c#).

There is no delete in C, and even if there was, GHC wouldn't use it.
Allocation is *the* major bottleneck of functional programs, and having
a custom allocator inlined into every call site is vital to have usable
performance.

 (Not that I have any good reason to do this, simply... fun).

Stefan


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


[Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread apfelmus

Hugh Perkins wrote:

Exactly. For this to work there needs to be the constraint that there's a
one-to-one mapping in each direction. The Bimap should have the uniqueness
promise that Set (k, v) gives. Yet you should be able to search on either
tuple value.


Or... have the possibility of returning a list of values.

Arguably there are two possible implementations, one that enforces
one-to-one mapping, and one which allows multiple values, in either
direction.


Terminology reminder :)
- the latter is called (binary) relation
  http://en.wikipedia.org/wiki/Binary_relation
- the former would be a bijection
  http://en.wikipedia.org/wiki/Bijective_map

Regards,
apfelmus

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


[Haskell-cafe] ANN: SF Bay Area Functional Programmers Group

2007-08-21 Thread Keith Fahlgren
Hi All,

I'd like to announce the formation of the Bay Area Functional
Programmers group.  This group is for anyone using or interested in
functional programming and functional programming languages,
particularly strongly typed languages such as Haskell, OCaml, SML,
etc.

The first meeting will be Thursday, September 13th at 7:30pm somewhere
in San Francisco.  Please join the mailing list at
http://groups.google.com/group/bayfp and suggest a location. The
initial meeting will be a casual pizza and beer get together, although
going forward we'd like to also include speakers, reading and
discussion of technical papers, and some hands on coding.  Future
announcements and the location of the first meeting will be posted to
the BayFP mailing list.

More information will be available on the website: http://bayfp.org/.




Keith (+ Mike Wells)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Generic data constructor in pattern?

2007-08-21 Thread Peter Verswyvelen
Consider the following example code:

data Vector = V Float Float
data Matrix = M Vector Vector

  liftV1 f (V x y) = V (f x) (f y)
liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2)

liftM1 f (M x y) = M (f x) (f y)
liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2)

Both pairs of lift functions have almost identical implementations. Can I
merge these somehow? I know data constructors are first class values and are
not types, but if I want to merge these lift functions I have to write
something like

lift1 f (d x y) = d (f x) (f y)
lift2 f (d x1 y1) (d x2 y2) = d (f x1 x2) (f y1 y2)

But this does not work, as the pattern matcher does not seem to like this.

Thanks,
Peter Verswyvelen

PS: Of course I could define a single type like:

data Pair a = P a a
type Vector = Pair Float
type Matrix = Pair Vector
lift1 f (P x y) = P (f x) (f y)
lift2 f (P x1 y1) (P x2 y2) = P (f x1 x2) (f y1 y2)

But that's beside the question :)   



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


Re: [Haskell-cafe] Generic data constructor in pattern?

2007-08-21 Thread Neil Mitchell
Hi Peter,

   liftV1 f (V x y) = V (f x) (f y)
 liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2)

 liftM1 f (M x y) = M (f x) (f y)
 liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2)

 Both pairs of lift functions have almost identical implementations. Can I
 merge these somehow?

Using the Uniplate library the first already has a name, its called descend.

The second does not, but could be implemented in Uniplate if you wanted.

descend2 :: Biplate a b = (b - b - b) - a - a - a
descend2 f a b = a2 (zipWith f as bs)
   where
  (as, a2) = uniplate a
  (bs, b2) = uniplate b

For full details see the website: http://www-users.cs.york.ac.uk/~ndm/uniplate/

Thanks

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


Re: [Haskell-cafe] Generic data constructor in pattern?

2007-08-21 Thread Henning Thielemann

On Tue, 21 Aug 2007, Peter Verswyvelen wrote:

 Consider the following example code:

   data Vector = V Float Float
   data Matrix = M Vector Vector

   liftV1 f (V x y) = V (f x) (f y)
   liftV2 f (V x1 y1) (V x2 y2) = V (f x1 x2) (f y1 y2)

   liftM1 f (M x y) = M (f x) (f y)
   liftM2 f (M x1 y1) (M x2 y2) = M (f x1 x2) (f y1 y2)

 Both pairs of lift functions have almost identical implementations. Can I
 merge these somehow? I know data constructors are first class values and are
 not types, but if I want to merge these lift functions I have to write
 something like

Maybe you are happy with instances of Control.Applicative (GHC-6.6)
  
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Applicative.html


(untested code follows)

data Vector a = Vector a a

instance Functor a where
   fmap f (Vector x y) = Vector (f x) (f y)

instance Applicative
   pure x = Vector x x
   (Vector fx fy) * (Vector x y) = Vector (fx x) (fy y)


pure f * vx
pure f2 * vx * vy


However, I'm not convinced that your code becomes more readable or
flexible by this change.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Yet another stupid question about numeric conversion

2007-08-21 Thread Peter Verswyvelen
Does a general approach exist to convert any non-constant (Num a) to a
Float? Not using type annotation of course.

Now I wrote a Convert class that has a toFloat function which I instantiate
for all different numeric types, but as all these toFloat/toInt functions
disappeared a long time ago from Haskell, it feels like a bad idea to
reintroduce them locally in my code...

Thanks (again!)
Peter Verswyvelen


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


Re: [Haskell-cafe] Yet another stupid question about numeric conversion

2007-08-21 Thread Lennart Augustsson
How can you hope to convert an arbitrary Num to a Float?
Num contains things like complex numbers that don't have any reasonable
translation to a Float.
But anyway, realToFrac is a good conversion function.

  -- Lennart

On 8/21/07, Peter Verswyvelen [EMAIL PROTECTED] wrote:

 Does a general approach exist to convert any non-constant (Num a) to a
 Float? Not using type annotation of course.

 Now I wrote a Convert class that has a toFloat function which I
 instantiate
 for all different numeric types, but as all these toFloat/toInt functions
 disappeared a long time ago from Haskell, it feels like a bad idea to
 reintroduce them locally in my code...

 Thanks (again!)
 Peter Verswyvelen


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

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


Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread Andrew Coppin

Stefan O'Rear wrote:

sum = sum' 0
sum' k [] = k
sum' k (x:xs) = (sum' $! (k+x)) xs

enum x y | x = y= 0
 | otherwise = x : enum (x+1) y


sum (enum 1 10) =
sum' 0 (enum 1 10)  =
sum' 0 (1 : enum (1+1) 10)  =
(sum' $! (0+1)) (enum (1+1) 10) =
sum' 1 (enum (1+1) 10)  =

sum' 1 (2 : enum (2+1) 10)  =
(sum' $! (1+2)) (enum (2+1) 10) =
sum' 3 (enum (2+1) 10)  =

sum' 3 (3 : enum (3+1) 10)  =
(sum' $! (3+3)) (enum (3+1) 10) =
sum' 6 (enum (3+1) 10)  =

sum' 6 (4 : enum (4+1) 10)  =
(sum' $! (6+4)) (enum (4+1) 10) =
sum' 10 (enum (4+1) 10) =

...


sum' 36 (9 : enum (9+1) 10)  =
(sum' $! (36+9)) (enum (9+1) 10) =
sum' 45 (enum (9+1) 10)  =
sum' 45 []   =
45

(I need to find some way to automate making these trails :) )
  


I did have a fairly small Tcl implementation for this...

I don't have the code now, and I wrote it early in my Haskell career, so 
there's masses of stuff it didn't handle. (*cough* type classes)


Actually, I've often longed for some tool (maybe even integrated into 
Lambdabot) to show the reduction sequence of an arbitrary expression. 
But none exists, AFAIK...


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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Andrew Coppin

Simon Peyton-Jones wrote:

GHC does some constant folding, but little by way of strength reduction, or 
using shifts instead of multiplication.  It's pretty easy to add more: it's all 
done in a single module.  Look at primOpRules in the module PrelRules.

Patches welcome!  But please also supply test-suite tests that check the 
correctness of the rules.
  


So... you mean it's source-level transformation rules? (Rather than 
wired into the compiler itself somewhere.)


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


Re: [Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-21 Thread Andrew Coppin

Donald Bruce Stewart wrote:

This puts the channel at around the 13th largest community of the 5500
freenode channels. For comparision, a sample of the state of the other
language communities:

#php 485
#perl472
##c++457
##c  445
#python  430
#ruby-lang   420
 
   #haskell 411


#lisp246
##java   236
##javascript 226
#perl6   144
#scheme  139
#erlang  118
#lua 105
#ocaml58
  


...does this mean Haskell is officially harder to understand than Lisp, 
Java, Perl and O'Caml? :-}


(OTOH, does this mean Haskell is easier to understand than PHP or C++?)

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


Re: [Haskell-cafe] Dynamic thread management?

2007-08-21 Thread Andrew Coppin

Tim Chevalier wrote:

Anyone can submit a paper to a CS journal or conference. While most
people who do so are affiliated with universities, research labs, or
(more rarely) non-research companies, there are independent
researchers out there, and sometimes you'll notice a paper where
someone is listed by just their name with no affiliation. Conferences
issue calls for papers (you might see some posted on this mailing
list) that give you an idea for the rough format of the paper and
submission guidelines. But really, you'll want to find a mentor who
can give you advice on how to write a paper that will fit the mold.
First come up with a technical result that you believe is
paper-worthy, then find other people to talk to who can confirm that
opinion and help you get your paper submitted :-)
  


I highly doubt that automatic threading will happen any time this decade 
- but I just learned something worth while from reading this email. ;-)


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


RE: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Simon Peyton-Jones
|  GHC does some constant folding, but little by way of strength
| reduction, or using shifts instead of multiplication.  It's pretty easy
| to add more: it's all done in a single module.  Look at primOpRules in
| the module PrelRules.
| 
|  Patches welcome!  But please also supply test-suite tests that check
| the correctness of the rules.
| 
|
| So... you mean it's source-level transformation rules? (Rather than
| wired into the compiler itself somewhere.)

No, constant folding is part of the compiler, I'm afraid, in the module 
PrelRules.

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


[Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread apfelmus

Stefan O'Rear wrote:

sum (enum 1 10) =
sum' 0 (enum 1 10)  =
...

sum' 36 (9 : enum (9+1) 10)  =
(sum' $! (36+9)) (enum (9+1) 10) =
sum' 45 (enum (9+1) 10)  =
sum' 45 []   =
45

(I need to find some way to automate making these trails :) )


Yes! We'd need such an automatic tool for the wikibook, too.

Regards,
apfelmus

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


Re: [Haskell-cafe] Yet another stupid question about numeric conversion

2007-08-21 Thread Henk-Jan van Tuyl
On Tue, 21 Aug 2007 18:53:43 +0200, Peter Verswyvelen [EMAIL PROTECTED]  
wrote:



Does a general approach exist to convert any non-constant (Num a) to a
Float? Not using type annotation of course.



Instances of class Integral (Int and Integer) can be converted with  
fromIntegral.


--
Met vriendelijke groet,
Henk-Jan van Tuyl


--
http://functor.bamikanarie.com
http://Van.Tuyl.eu/
--

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


RE: [Haskell-cafe] Yet another stupid question about numeric conversion

2007-08-21 Thread Peter Verswyvelen
Yes indeed, I realized that. I oversimplified my question. I'm basically
trying to model 4D CG/HLSL operations (pixel/vertex shaders) in Haskell.

I tried realToFrac, but that did not work. Then I tried splitting the
instances into Fractional and Integral, but I kept getting errors. Maybe
because I also made the Vector datatype an instance of Num, Fractional, etc,
which was needed to model the CG/HLSL piecewise operations (so
multiplication of two vectors is done piecewise by default in the CG model;
one has special dot, cross, and mul operations for performing the other
operations).

Anyway, although I got something working when I enabled many GHC extensions,
I dropped it for now. I notice that a lot of Haskell code uses type
annotations (e.g. in HOpenGL), so I guess that's the price one has to pay.

It would be nice if one could have a full predicate in the constraints
section of a type class, like 

class ((Num a)  not (Vector4D a)) = ...

But I guess this indicates bad design? 

Thanks,
Peter


[EMAIL PROTECTED] wrote:
How can you hope to convert an arbitrary Num to a Float?
Num contains things like complex numbers that don't have any reasonable
translation to a Float.
But anyway, realToFrac is a good conversion function.



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


Re: [Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread Neil Mitchell
Hi

  sum (enum 1 10) =
  sum' 0 (enum 1 10)  =
  ...
 
  sum' 36 (9 : enum (9+1) 10)  =
  (sum' $! (36+9)) (enum (9+1) 10) =
  sum' 45 (enum (9+1) 10)  =
  sum' 45 []   =
  45
 
  (I need to find some way to automate making these trails :) )

 Yes! We'd need such an automatic tool for the wikibook, too.

The problem is that Haskell is ridiculously complex, and the small
step interpretation is much harder than you'd think. For example, sum
may well be defined as foldl' (+) 0, which is a CAF, so gets reduced
once. The 0 won't actually be a 0, but will be fromInteger 0, which
will correspond to looking up an item in the dictionary and applying
it. Dictionaries especially make the simple interpretation
completely wrong.

It's easy to do informally, but once you start being more precise, its
very complex.

Thanks

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


Re: [Haskell-cafe] Re: Newbie question: Where is StackOverflow on the Wiki?

2007-08-21 Thread Andrew Coppin

Neil Mitchell wrote:

Hi

  

(I need to find some way to automate making these trails :) )
  

Yes! We'd need such an automatic tool for the wikibook, too.



The problem is that Haskell is ridiculously complex, and the small
step interpretation is much harder than you'd think. For example, sum
may well be defined as foldl' (+) 0, which is a CAF, so gets reduced
once. The 0 won't actually be a 0, but will be fromInteger 0, which
will correspond to looking up an item in the dictionary and applying
it. Dictionaries especially make the simple interpretation
completely wrong.

It's easy to do informally, but once you start being more precise, its
very complex.
  


Like I said, I made a tool in Tcl that works. If you program in 
partially-parsed Haskell by hand first for all the functions it calls. 
(Except a few basic math ops.) Indeed, it was by playing with this tool 
that I first discovered why foldl' needs to exist! ;-)


So, making a tool that you can set up to quickly generate an automated 
trace is quite easy. If you want a tool where you can just casually toss 
arbitrary Haskell at it and expect sensible answers... hmm... that's 
going to be kinda tricky. (!)


(I had a go at it myself, several times. Each time I was tripped over by 
being unable to correctly parse arbitrary Haskell code. I never even got 
to writing the execution engine...!)


I think a lot of people will agree that if such a tool existed it could 
be a *tremendous* help in many, many ways - a tool for experimenting and 
teaching, finding out why your really-complicated-function behaves 
wrong, checking out strictness properties, etc. But somebody has to 
write it first.


It's ironic really; Haskell *looks* so easy to single-step. ;-)

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


Re: [Haskell-cafe] Re: Bi-directional Maps

2007-08-21 Thread Albert Y. C. Lai

apfelmus wrote:

Hugh Perkins wrote:

Arguably there are two possible implementations, one that enforces
one-to-one mapping, and one which allows multiple values, in either
direction.


Terminology reminder :)
- the latter is called (binary) relation
  http://en.wikipedia.org/wiki/Binary_relation
- the former would be a bijection
  http://en.wikipedia.org/wiki/Bijective_map


Following a great tradition,

That's just semantics.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] #haskell irc channel reaches 400 users

2007-08-21 Thread Albert Y. C. Lai

Andrew Coppin wrote:
...does this mean Haskell is officially harder to understand than Lisp, 
Java, Perl and O'Caml? :-}


(OTOH, does this mean Haskell is easier to understand than PHP or C++?)


Or, Haskell is the easiest to understand of them all.

Reason: Extremely large channel means so hard to understand that many 
people want help. Extremely small channel means so hard to understand 
that few people show interest. The middle-sized channel sits at the 
sweet spot.


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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Isaac Dupree

Simon Peyton-Jones wrote:

|  GHC does some constant folding, but little by way of strength
| reduction, or using shifts instead of multiplication.  It's pretty easy
| to add more: it's all done in a single module.  Look at primOpRules in
| the module PrelRules.
| 
|  Patches welcome!  But please also supply test-suite tests that check
| the correctness of the rules.
| 
|
| So... you mean it's source-level transformation rules? (Rather than
| wired into the compiler itself somewhere.)

No, constant folding is part of the compiler, I'm afraid, in the module 
PrelRules.

Simon


_Constant_ folding is, but in GHC.Base there are rules like (unboxed) 
multiplying by zero or one, or adding or subtracting zero, from an 
unknown other (non-constant) value.  I think shifts might be doable via 
RULES... if you were willing to make one rule for each denominator 2, 4, 
8 and so on, which rather depends on max. Int... (and that's not 
Integers either, I guess)


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


[Haskell-cafe] Re: I'm stuck in my thought experiment

2007-08-21 Thread Levi Stephen


If I wanted to develop the widgets themselves separately from the 
layout, I would probably do something like this:


class Widget a where
render :: a - Html
bbox :: a - Size

type Layout = forall a. Widget a = Widget a
| Rows Spacing [Layout]
| Columns Spacing [Layout]
| Grid Spacing [[Layout]]

type Page = Page String Layout

renderLayout :: Layout - Html

renderPage :: Page - Html


I'm unsure this gives what I'm after. I'm trying to have layouts 
consist of Widgets (e.g., header images, common menu), and as pages 
also consist of Widgets it seems like they can be modelled using a 
common type/construct.


Well if you want to abstract over the layout too, you can just add

instance Widget Layout where
render = renderLayout
bbox = ...

But just because you can, doesn't mean you should. I don't know the full 
details of your design, but what do you gain by allowing the layout to 
intermingle with the widgets? Is worth the extra complexity?


If you treat layout as just another widget then it becomes harder to 
answer specific questions about the page layout because you have less 
information in your tree.




Layout might not actually be the right term. Page template might be better.

What I'm trying to gain is best described with an example.

* I have a template with a header image, and footer text.
* I create another template defined as the previous, but with a menu bar down
  the left.
* I create a page based on the previous with some text.

The gain comes from when I want to change the header image, or add a 
Login/Register box on all pages, I only edit the first template.


Levi

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


Re: [Haskell-cafe] Parsing binary data.

2007-08-21 Thread Tony Finch
On Sun, 19 Aug 2007, Peter Cai wrote:

 My duty is writing a network server which talks to another server through a
 binary based private protocol.

Haskell needs something like Erlang's bit syntax.

http://erlang.org/doc/reference_manual/expressions.html#6.16
http://erlang.org/doc/programming_examples/bit_syntax.html#4
The IP header example in the latter is a brilliant real-world example.

It has recently been upgraded to support arbitrary bit streams.
See http://www.it.uu.se/research/group/hipe/papers/padl07.pdf

Tony.
-- 
f.a.n.finch  [EMAIL PROTECTED]  http://dotat.at/
IRISH SEA: SOUTHERLY, BACKING NORTHEASTERLY FOR A TIME, 3 OR 4. SLIGHT OR
MODERATE. SHOWERS. MODERATE OR GOOD, OCCASIONALLY POOR.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsing binary data.

2007-08-21 Thread Donald Bruce Stewart
dot:
 On Sun, 19 Aug 2007, Peter Cai wrote:
 
  My duty is writing a network server which talks to another server through a
  binary based private protocol.
 
 Haskell needs something like Erlang's bit syntax.
 
 http://erlang.org/doc/reference_manual/expressions.html#6.16
 http://erlang.org/doc/programming_examples/bit_syntax.html#4
 The IP header example in the latter is a brilliant real-world example.
 
 It has recently been upgraded to support arbitrary bit streams.
 See http://www.it.uu.se/research/group/hipe/papers/padl07.pdf
 

Yes, we've looked at this in the context of Data.Binary. Rather than
extending the core syntax, on option is to use Template Haskell,

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/BitSyntax-0.3

Another is to just use monad and pattern guards, which give quite
reasonable syntax.

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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Twan van Laarhoven

Isaac Dupree wrote:

Simon Peyton-Jones wrote:


...
No, constant folding is part of the compiler, I'm afraid, in the 
module PrelRules.


Simon



_Constant_ folding is, but in GHC.Base there are rules like (unboxed) 
multiplying by zero or one, or adding or subtracting zero, from an 
unknown other (non-constant) value.  I think shifts might be doable via 
RULES... if you were willing to make one rule for each denominator 2, 4, 
8 and so on, which rather depends on max. Int... (and that's not 
Integers either, I guess)



Just to see what this would look like.


First of all, optimizing mod and div can not be done with PrelRules, 
because they are not primitives, quot and rem are. And most of the nice 
optimizations with shifts no longer work there. But using rules should 
work, assuming the inliner is not too fast.


Multiplication and division can become shifts:

 {-# RULES

 -- x * 2^n  --  x `shiftL` n
 x# *# 2#  forall x#.  x# *# 2# = x# `iShiftL#` 1#
 2# *# x#  forall x#.  2# *# x# = x# `iShiftL#` 1#
   -- etc.

 -- x `div` 2^n  --  x `shiftR` n
 x# `divInt#` 2#  forall x#.  divInt# x# 2# = x# `iShiftRA#` 1#
 x# `divInt#` 4#  forall x#.  divInt# x# 4# = x# `iShiftRA#` 2#
   -- etc.

Mod can become and:

 -- x `mod` 2^n  --  x .. (2^n - 1)
 x# `modInt#` 2#  forall x#.  modInt# x# 2# = andInt# x# 1#
 x# `modInt#` 4#  forall x#.  modInt# x# 4# = andInt# x# 3#
   -- etc.

   #-}

Here I use a new function (see instance Bits Int),

 andInt# :: Int# - Int# - Int#
 andInt# x# y# = word2Int# (int2Word# x# `and#` int2Word# y#)

but you could write that inline as well.

A problem with these rules is that you need a whole lot of them. 32 per 
operation (on a 32 bit platform), * 4 operations, * 2 separate versions 
for words and ints = 256.




Other rules that could be interesting are:
 forall a b. fromInteger a + fromInteger b = fromInteger (a + b)
 forall a b. fromInteger a * fromInteger b = fromInteger (a * b)
 -- etc.
To allow optimizations on generic Num code, although I am not sure what 
the Haskell spec has to say about this.




Now, if you want to get really creative you can use other semi-evil 
optimization tricks for quot and rem.

The following is based on code generated by Visual C++:
 -- remPowInt x y == x `rem` (2^y)
 remPowInt x y
 | r = 0 =  r
 | otherwise  =  ((r - 1) .|. (complement yWithSign)) + 1
   where  r = x .. yWithSign
  yWithSign = (1 `shiftL` (bitSize - 1)) .|.
  ((1 `shiftL` y) - 1)
Or in assembly (for y == 2, so x `rem` 4)
  and ecx,8007h
  jns main+60h (401060h)
  dec ecx
  or  ecx,0FFF8h
  inc ecx

The C++ compiler also performs other optimizations when multiplying with 
other constants, for example *3 becomes something like

  lea eax, [eax+eax*2]
Divisions become horrendous constructs with magic numbers,
   -- eax := ecx / 5
  mov eax,6667h
  imulecx
  sar edx,1
  mov eax,edx
  shr eax,1Fh
  add eax,edx
But such things are probably best left to the code generator / a 
peephole optimizer, if they are done at all. I think the LEA trick 
should be feasible.



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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Brandon S. Allbery KF8NH


On Aug 21, 2007, at 22:13 , Twan van Laarhoven wrote:


Other rules that could be interesting are:
 forall a b. fromInteger a + fromInteger b = fromInteger (a + b)


I don't think this will work, a and b have to be the same type.

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


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


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Twan van Laarhoven

Brandon S. Allbery KF8NH wrote:



On Aug 21, 2007, at 22:13 , Twan van Laarhoven wrote:


Other rules that could be interesting are:
 forall a b. fromInteger a + fromInteger b = fromInteger (a + b)



I don't think this will work, a and b have to be the same type.


They are of the same type, both are Integers,

 forall a b :: Integer.
 ((fromInteger (a::Integer)) + (fromInteger b)) :: Num n = n
   =
 (fromInteger (a + b :: Integer)) :: Num n = n

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


Re: [Haskell-cafe] Dynamic thread management?

2007-08-21 Thread Hugh Perkins
On 8/21/07, Andrew Coppin [EMAIL PROTECTED] wrote:
 I highly doubt that automatic threading will happen any time this decade
 - but I just learned something worth while from reading this email. ;-)


That's an interesting observation.  I cant say I dont believe it, but
I'm interested to know why (but it could be just a feeling, or an
observation in time-to-market lead times?).  Are you saying this
because multicores arent sufficiently widespread or powerful enough
yet (4-cores doesnt really even make up for the overhead of using
automatic threading, at least in initial implementations)? or are you
saying this because you think the technical implementations are not
sufficiently advanced?

I kindof think automatic threading is like 3d graphics: as soon as the
hardware became sufficiently powerful, 3d graphics became trivial.
Enough money was thrown at the problem in a very short time by a few
powerful companies that it was a non-issue.

Nevertheless, if I could get a paper out of it before the big
companies notice, that could be fun :-D
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Hugh Perkins
Thank-you for the information.  It was very useful.  Couple of reactions FWIW:

On 8/21/07, Stefan O'Rear [EMAIL PROTECTED] wrote:
  Sooo if I was feeling evil, could I take this c-code and pipe it
  into something that turns it into C#???

 Yes.  You could do the same with the original haskell.  It's called a
 compiler.

Yes, that is true.  However, this is also true, for an appropriate
compiler, for programs such as:

Give me the first 10 numbers of the Fibonnacci (spelling?) series.

The compiler can search on the internet for what is the Fibonnacci
series, and/or ask its friends.

In a subsequent version, a compiler could in fact compile programs such as:

Go!

... where the compiler uses context to deduce what I want it to do ;-)

Nevertheless certain compilers are easier to write than others, and
writing code to automatically port ghc-generated C code is likely to
be significantly easier than to compile Haskell to C#, or to .Net
bytecode, from scratch.


 Name:Native code generator
 Performance: 0.97
 Flags:   -fasm

 GHC's own mini C compiler converts the internal C-- data into assembly
 code, which is then piped to gas.

Ah, hence SPJ's C-- project?


 Name:Unregisterized C
 Performance: 0.40
 Flags:   -unreg

 Generates near-ANSI C, using memory variables for the VM's registers and
 the returning function pointer hack seen in oh so many Scheme compilers.
 Good for early stages of porting, and not much else.

Could be good enough.  C# compiler and VM provides some optimizations
which could handle this.  What is the function pointer hack?
Specifically, is that why you say near-ANSI C, rather than ANSI C?


  If it contains lots of macros (or any macros at all perhaps...), this
  becomes non-trivial,

 I fail to see how macros have anything to do with this.  Especially
 since cpp removes them all.

  but otherwise I think most things in C can be mapped fairly trivially
  to C#?

 Unsafe C#, sure.  Haskell's type system is strictly more expressive than
 C#, and you need to sacrifice either machine efficiency or checked
 safety.

  (It's a one-way mapping of course, eg delete in C is simply dropped
  when mapped to c#).

 There is no delete in C, and even if there was, GHC wouldn't use it.
 Allocation is *the* major bottleneck of functional programs, and having
 a custom allocator inlined into every call site is vital to have usable
 performance.

  (Not that I have any good reason to do this, simply... fun).

 Stefan

 -BEGIN PGP SIGNATURE-
 Version: GnuPG v1.4.6 (GNU/Linux)

 iD8DBQFGyur/FBz7OZ2P+dIRAleTAJ9WiK8tCp0QZE4syG4BZk5EFm1FuQCgzYGK
 NUv22zY5IgeqkEJ5kL3yriQ=
 =0Xkq
 -END PGP SIGNATURE-


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


Re: [Haskell-cafe] Re: Haskell vs GC'd imperative languages, threading, parallelizeability (is that a word? :-D )

2007-08-21 Thread Brandon S. Allbery KF8NH


On Aug 21, 2007, at 23:27 , Hugh Perkins wrote:


Hmmm, that's interesting.  I'd never considered lack of typing to be a
good thing for system robustness before!


The old watchphrase (before Netscape and Microsoft abused it beyond  
anyone's expectation) for Internet protocols was be liberal in what  
you accept and conservative in what you send; same idea.


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


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