Re: [Haskell-cafe] Linker problems linking FFI import call in Windows

2008-07-17 Thread Olivier Boudry
On Wed, Jul 16, 2008 at 6:22 PM, PJ Durai [EMAIL PROTECTED] wrote:
 I do have the import library. It came with the DLL. It links properly
 when I use CCALL on the haskell import statements. Doesnt link when I
 use STDCALL. It looks for  function name with something like '@4 or
 @8' tacked on at the end. Not sure what that is all about.

Is your import library a .lib or a .a file? If you have a .lib
import library ghc will ignore it and link directly with the DLL.

I think you can convert a .lib to a .a using the reimp tool which
is part of the mingw utilities.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread kyra

Felipe Lessa wrote:

Hi,

I tried googling and searching the haskellwiki about this but wasn't
lucky enough. My question is: is there a way to send struct arguments
to C functions via the FFI or do I need to create a C wrapper? I guess
there isn't, and while I can live without it, I'd like to leave no
doubt.
  

Sometimes there is such a way. See below.

Details:

I have something like


typedef struct vect {
float x,y;
} vect;

void func(vect v);
  

For most architectures stack layout of

void func(vect v);

and

void func(float x, float y);

is exactly the same, so for FFI purposes this 'func' can be declared as 
something like:


foreign import ccall unsafe :: Float - Float - IO ()


Cheers,
Kyra

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


[Haskell-cafe] Re: Fixed-Point Combinators

2008-07-17 Thread Jon Fairbairn
Adrian Neumann [EMAIL PROTECTED] writes:

 Hello,

 while studying for a exam I came across this little pearl:

 Y = (L L L L L L L L L L L L L L L L L L L L L L L L L L L L)
 where
 L = λabcdefghijklmnopqstuvwxyzr. (r (t h i s i s a f i x e d
 p o i n  t c o m b i n a t o r))

 posted by Cale Gibbard to this list. Now I'm wondering how
 exactly  does one finde such awesome λ expressions?

In this particular case, once one has seen the Turing fixed
point combinator, I think it's fairly obvious. The idea this
is, we want a fixpoint combinator; let's assume we can make
it by applying one thing to another. F G. We want 

(F G f) = f (F G f)

so F has got to look something like \g f - f (F g f). Oh,
but where are we going to get another F without a fixpoint
combinator? I know, how about passing it in as g?  now F =
(\g f - f (g g f)), which works so long as the argument
given for g is F. So Y = F F.

Now, one can look at this as F is half of a fixpoint
combinator, so what about one third of a fixpoint
combinator?  ie T T T f = f (T T T f) Clearly T has to look
like (\t2 t3 f - f (T T T f)), and the same reasoning
applies.  Obviously it doesn't matter what you call the
bound variables.

 Is there some mathemagical background that lets one
 conjure such beasts?

If you play around with lambda expressions and combinators
enough, they'll come to you in your dreams. To what extent
this is a Good Thing is a matter of personal taste.

-- 
Jón Fairbairn [EMAIL PROTECTED]
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated 2008-04-26)

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


Re: [Haskell-cafe] Type level sets with GADTs, fundeps etc

2008-07-17 Thread J . Burton
At Tue, 15 Jul 2008 10:27:59 -0400,
Jeff Polakow wrote:
 
 [1  text/plain; US-ASCII (7bit)]
 
 [2  text/html; US-ASCII (7bit)]
 Hello,
 
  data LSet t where
  Nil :: LSet Nil
  Ins :: (Member a t b
, If b t (a ::: t) r)
= L a - LSet t - LSet r
 
 Try replacing both original occurrences of r, i.e. (untested)
 
 Ins :: (Member a t b, If b t (a ::: t) (LSet r)) = L a - LSet t - LSet 
 r
 

Thanks. This sort of works, but shifts the problem to another context. Now it
seems that I can't hide the extra type information in the existential
types, which is what I want to do. In the function `insertChar' below
I want the type LSetBox to be opaque (i.e. it will be called by users who
don't need to know about the fancy types):

data LSet t where
Nil :: LSet Nil
Ins :: (Member a t b
  , If b t (a ::: t) (LSet r)) 
  = L a - LSet t - LSet r
   
-- I have to supply a type for `insert' now and it must include the constraints
insert :: (Member a t b
  , If b t (a ::: t) (LSet r)) 
 = L a - LSet t - LSet r
insert = Ins

--insertChar (and the boxing) doesn't work 
insertChar :: Char - LSetBox - LSetBox
insertChar c (LSetBox s) = 
case fromChar c of
  LBox t - LSetBox (insert t s) 

The error:

Could not deduce (If b t1 (a ::: t1) (LSet t), Member a t1 b)
  from the context ()
  arising from a use of `insert'
   at /home/jim/sdf-bzr/dsel/TF/Set-July08.hs:54:25-34
Possible fix:
  add (If b t1 (a ::: t1) (LSet t), Member a t1 b) to the context of
the constructor `LBox'
  or add an instance declaration for (If b t1 (a ::: t1) (LSet t))
In the first argument of `LSetBox', namely `(insert t s)'
In the expression: LSetBox (insert t s)
In a case alternative: LBox t - LSetBox (insert t s)
Failed, modules loaded: none.

Jim

 -Jeff
 
 ---
 
 This e-mail may contain confidential and/or privileged information. If you
 are not the intended recipient (or have received this e-mail in error)
 please notify the sender immediately and destroy this e-mail. Any
 unauthorized copying, disclosure or distribution of the material in this
 e-mail is strictly forbidden.
 
 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Searchig for modules

2008-07-17 Thread fero

Hi I am learnig Haskell form SOE book, but I can't find out how to import SOE
module. I use eclipsefp IDE and I get no error when I have SOE.hs in my
project and in SimpleGraphics.hs I make import SOE. But when trying to run
it I get error: Could not find module `SOE': Use -v to see a list of the
files searched for. Where ghc/ghci search for modules? Is it possible put
some modules somewhere that every Haskell project can find it (something as
global classpath in java). And is it posible in eclipsefp to link some
modules to project that this project will use them. As I wrote even when I
have 2 modules in src in project I when trying to run one of then the others
are not found. I can't find any site about searching for modules (in java
there is a lot options, global/local classpath, directory in java runtime
used only with this rt or directory in web server used in all apps run on
this server...). Can you put a link?

Thanks

Fero
-- 
View this message in context: 
http://www.nabble.com/Searchig-for-modules-tp18505770p18505770.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Searchig for modules

2008-07-17 Thread fero

Actually I have already found the way how to do it but not in eclipsefp.
Either I run ghci and when both modules are in the same dir it works or I
use -idirs but in eclipsefp it doesn't. Can somebody help me how to
configure eclipsefp. I don't want to go to command prompt every time I want
to run my program.

Fero
-- 
View this message in context: 
http://www.nabble.com/Searchig-for-modules-tp18505770p18506257.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Duncan Coutts

On Wed, 2008-07-16 at 22:45 -0300, Felipe Lessa wrote:
 Hi,
 
 I tried googling and searching the haskellwiki about this but wasn't
 lucky enough. My question is: is there a way to send struct arguments
 to C functions via the FFI or do I need to create a C wrapper? I guess
 there isn't, and while I can live without it, I'd like to leave no
 doubt.

Correct. The FFI spec does not support C structs as C function
parameters or results. You'll need a wrapper.

If the struct is passed by reference of course then you're fine, but if
it's by value then you need a C wrapper. The reason is because it's
beyond the scope of the FFI to know the structure layout and how to map
that to haskell types. That's the domain of FFI pre-processors. However
I don't know of any FFI pre-processors that help in this case. Passing C
structs by value seems to be pretty rare in exported C APIs.

Duncan


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


Re: [Haskell-cafe] Searchig for modules

2008-07-17 Thread Isaac Dupree

fero wrote:

Actually I have already found the way how to do it but not in eclipsefp.
Either I run ghci and when both modules are in the same dir it works or I
use -idirs but in eclipsefp it doesn't. Can somebody help me how to
configure eclipsefp. I don't want to go to command prompt every time I want
to run my program.


I don't know anything about IDEs, but...
ghc --make, should work to find the module on the command-line, and so 
should `runghc` (like interpreter but runs 'main').


There is also a way to install it more globally but I'm not sure what is 
a simple way to do that (it could involve making a .cabal file, I think)


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


Re: [Haskell-cafe] Searchig for modules

2008-07-17 Thread frantisek kocun
It works when I put -idirs c:\eworkspace2\Soe\src\SOE to extra compiler
options and set GHCi to use GHC setting, but you need to restart ecpilse.
And the module, wht is loaded is SOE so I always need to switch module..

Fero

On Thu, Jul 17, 2008 at 1:18 PM, fero [EMAIL PROTECTED] wrote:


 Actually I have already found the way how to do it but not in eclipsefp.
 Either I run ghci and when both modules are in the same dir it works or I
 use -idirs but in eclipsefp it doesn't. Can somebody help me how to
 configure eclipsefp. I don't want to go to command prompt every time I want
 to run my program.

 Fero
 --
 View this message in context:
 http://www.nabble.com/Searchig-for-modules-tp18505770p18506257.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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

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


[Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread stefan kersten

hi,

i've attached an example program which seems to indicate that the  
magnitude function from Data.Complex is very slow compared to a more  
naive implementation (for Complex Float). on my machine (intel core2  
duo, osx 10.4) the CPU time using the library function is about 6-7  
times as much as when using the other function. any ideas what might  
be going on? any flaws in my measurement code?


thanks,
sk



magnitude.hs
Description: Binary data



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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread kyra

If the struct is passed by reference of course then you're fine, but if
it's by value then you need a C wrapper. The reason is because it's
beyond the scope of the FFI to know the structure layout and how to map
that to haskell types. That's the domain of FFI pre-processors. However
I don't know of any FFI pre-processors that help in this case. Passing C
structs by value seems to be pretty rare in exported C APIs.


Yes, but programmer *knows* the structure layout, so she usually can 
emulate it with a sequence of primary ffi type arguments. It's pretty 
trivial for the original example (see my previous post on this subj) and 
can be extended further. For example, in my homebrew COM library I 
pretty successfully marshall 16-byte Variants *by value* by means of two 
consecutive legal Word64 arguments.


Cheers,
Kyra

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


Re: [Haskell-cafe] Type level sets with GADTs, fundeps etc

2008-07-17 Thread Jeff Polakow
Hello,

 Thanks. This sort of works, but shifts the problem to another context. 
Now it
 seems that I can't hide the extra type information in the existential
 types, which is what I want to do. 

I think that you can't abstract over a type context, i.e. you can't expect 
type inference to instantiate a type variable to a constrained polymorphic 
type.

I get the impression that GADTs are a bit of a distraction for what you 
are aiming to do. I'm not sure exactly what you mean by 
 
  :t insert (undefined::A) (undefined:: A ::: Nil)
 insert (undefined::A) (undefined:: A ::: Nil) :: A ::: Nil 
 
 But what I really want to do is wrap this up so that it can be used 
 at runtime, not just in the type-checker, so that (just a sketch) 
 I could have
 
 insert 'A' empty :: Set (A ::: Nil)
 
 where the runtime value of the set is fully determined by its type. 

but it looks like it should be a realtively easy bit of machinery to add 
to what you already had.

Also, in case you haven't already seen these, other good sources of type 
level programming are the HList paper (
http://homepages.cwi.nl/~ralf/HList/) and the OOHaskell paper (
http://homepages.cwi.nl/~ralf/OOHaskell/)

-Jeff



---

This e-mail may contain confidential and/or privileged information. If you 
are not the intended recipient (or have received this e-mail in error) 
please notify the sender immediately and destroy this e-mail. Any 
unauthorized copying, disclosure or distribution of the material in this 
e-mail is strictly forbidden.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread Henning Thielemann


On Thu, 17 Jul 2008, stefan kersten wrote:

i've attached an example program which seems to indicate that the magnitude 
function from Data.Complex is very slow compared to a more naive 
implementation (for Complex Float). on my machine (intel core2 duo, osx 10.4) 
the CPU time using the library function is about 6-7 times as much as when 
using the other function. any ideas what might be going on? any flaws in my 
measurement code?


Complex.magnitude must prevent overflows, that is, if you just square 
1e200::Double you get an overflow, although the end result may be also 
around 1e200. I guess, that to this end Complex.magnitude will separate 
mantissa and exponent, but this is done via Integers, I'm afraid.

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


RE: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Bayley, Alistair
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED] On Behalf Of Duncan Coutts
 Sent: 17 July 2008 12:46
 
 On Wed, 2008-07-16 at 22:45 -0300, Felipe Lessa wrote:
  Hi,
  
  I tried googling and searching the haskellwiki about this but wasn't
  lucky enough. My question is: is there a way to send struct 
 arguments
  to C functions via the FFI or do I need to create a C 
 wrapper? I guess
  there isn't, and while I can live without it, I'd like to leave no
  doubt.
 
 If the struct is passed by reference of course then you're 
 fine, but if
 it's by value then you need a C wrapper. The reason is because it's
 beyond the scope of the FFI to know the structure layout and 
 how to map
 that to haskell types. That's the domain of FFI 
 pre-processors. However
 I don't know of any FFI pre-processors that help in this 
 case. Passing C
 structs by value seems to be pretty rare in exported C APIs.


hsc2hs can help a bit (I haven't used the other FFI tools, so don't take
this as an endorsement of hsc2hs over them). You could create a wrapper
that marshals your Vector to a vector struct like this:

 .hsc file:

#include vect.h  -- whatever header contains your C vector struct

data VectorC = Ptr ()  -- opaque data type, like void*

-- your Haskell vector
data Vector = Vector Float Float

vector2cvect :: Vector - IO VectorC
vector2cvect (Vector x y) = do
  ptr - mallocBytes #{size vect}
  pokeByteOff #{offset vect, x} x
  pokeByteOff #{offset vect, x} x
  return ptr

cvect2Vector :: VectorC - IO Vector
cvect2Vector ptr = do
  x - peekByteOff ptr #{offset vect, x}
  y - peekByteOff ptr #{offset vect, y}
  return (Vector x y)

-- inline your *vect-vect wrapper (ends up in generated .c file)
#def void funcWrapper(vect *v) { func(*v); }

foreign import stdcall funcWr unsafe funcWrapper :: VectorC - IO ()

main = do
  vc - vector2cvect (Vector 3 4)
  funcWr vc
  free vc
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*

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


Re: [Haskell-cafe] uvector and the stream interface

2008-07-17 Thread Evan Laforge
 An abstraction stack:

Impure  Pure

How about strict vs. lazy?  I ask because I assumed there were lazy
variants of uvector or storablevector, using the bytestring list of
chunks approach, but apparently not?  Making a lazy version seems
pretty easy, but rewriting all the basic functions looks not so easy.
Granted, I can probably do most of what I want with just foldr...

Also, what's the distinction between storablevector and uvector?

Also, it's even more off subject, but haddock crashes on uvector.  You
can see the errors on hackage.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] uvector and the stream interface

2008-07-17 Thread Henning Thielemann


On Thu, 17 Jul 2008, Evan Laforge wrote:


An abstraction stack:

   Impure  Pure


How about strict vs. lazy?  I ask because I assumed there were lazy
variants of uvector or storablevector, using the bytestring list of
chunks approach, but apparently not?


For storablevector there exists code, but not complete and not tested:
   http://code.haskell.org/storablevector/Data/StorableVector/Lazy.hs


Also, what's the distinction between storablevector and uvector?


I hoped that I answered this with my previous mail.

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


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread Ian Lynagh
On Thu, Jul 17, 2008 at 05:18:01PM +0200, Henning Thielemann wrote:
 
 On Thu, 17 Jul 2008, stefan kersten wrote:
 
 i've attached an example program which seems to indicate that the 
 magnitude function from Data.Complex is very slow compared to a more naive 
 implementation (for Complex Float). on my machine (intel core2 duo, osx 
 10.4) the CPU time using the library function is about 6-7 times as much 
 as when using the other function. any ideas what might be going on? any 
 flaws in my measurement code?
 
 Complex.magnitude must prevent overflows, that is, if you just square 
 1e200::Double you get an overflow, although the end result may be also 
 around 1e200. I guess, that to this end Complex.magnitude will separate 
 mantissa and exponent, but this is done via Integers, I'm afraid.

Here's the code:

{-# SPECIALISE magnitude :: Complex Double - Double #-}
magnitude :: (RealFloat a) = Complex a - a
magnitude (x:+y) =  scaleFloat k
 (sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk 
y)^(2::Int)))
where k  = max (exponent x) (exponent y)
  mk = - k

So the slowdown may be due to the scaling, presumably to prevent
overflow as you say. However, the e^(2 :: Int) may also be causing a
slowdown, as (^) is lazy in its first argument; I'm not sure if there is
a rule that will rewrite that to e*e. Stefan, perhaps you can try timing
with the above code, and also with:

{-# SPECIALISE magnitude :: Complex Double - Double #-}
magnitude :: (RealFloat a) = Complex a - a
magnitude (x:+y) =  scaleFloat k
 (sqrt (sqr (scaleFloat mk x) + sqr (scaleFloat mk y)))
where k  = max (exponent x) (exponent y)
  mk = - k
  sqr x = x * x

and let us know what the results are?


Thanks
Ian

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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Felipe Lessa
On Thu, Jul 17, 2008 at 12:08 PM, kyra [EMAIL PROTECTED] wrote:
 Yes, but programmer *knows* the structure layout, so she usually can emulate
 it with a sequence of primary ffi type arguments. It's pretty trivial for
 the original example (see my previous post on this subj) and can be extended
 further. For example, in my homebrew COM library I pretty successfully
 marshall 16-byte Variants *by value* by means of two consecutive legal
 Word64 arguments.

I am concerned, however, with the portability of the library. I mean,
is the calling convention for both

void func(vect v);
void func(float x, float y);

the same on x86? On x86-64? On Windows? On Linux? I guess it would be
a lot faster to pass the arguments on the stack than alloca'ting,
copying to the new area and then copying from the area to the stack,
but I don't want to sacrifice the portability.

Thanks,

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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Felipe Lessa
On Thu, Jul 17, 2008 at 12:37 PM, Bayley, Alistair
[EMAIL PROTECTED] wrote:
 -- inline your *vect-vect wrapper (ends up in generated .c file)
 #def void funcWrapper(vect *v) { func(*v); }

 foreign import stdcall funcWr unsafe funcWrapper :: VectorC - IO ()

I am using hsc2hs currently, but googling about #def with Cabal I
found out that some people were having trouble to make Cabal discover
that hsc2hs had created a new C file. Specifically, bug #245 [1] which
says that the milestone is undefined. So for now I'm creating a
wrapper.[ch] myself.

[1] http://hackage.haskell.org/trac/hackage/ticket/245

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


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread stefan kersten

On 17.07.2008, at 17:42, Ian Lynagh wrote:

On Thu, Jul 17, 2008 at 05:18:01PM +0200, Henning Thielemann wrote:

Complex.magnitude must prevent overflows, that is, if you just square
1e200::Double you get an overflow, although the end result may be  
also
around 1e200. I guess, that to this end Complex.magnitude will  
separate

mantissa and exponent, but this is done via Integers, I'm afraid.


Here's the code:

{-# SPECIALISE magnitude :: Complex Double - Double #-}
magnitude :: (RealFloat a) = Complex a - a
magnitude (x:+y) =  scaleFloat k
 (sqrt ((scaleFloat mk x)^(2::Int) +  
(scaleFloat mk y)^(2::Int)))

where k  = max (exponent x) (exponent y)
  mk = - k

So the slowdown may be due to the scaling, presumably to prevent
overflow as you say. However, the e^(2 :: Int) may also be causing a
slowdown, as (^) is lazy in its first argument; I'm not sure if  
there is
a rule that will rewrite that to e*e. Stefan, perhaps you can try  
timing

with the above code, and also with:

{-# SPECIALISE magnitude :: Complex Double - Double #-}
magnitude :: (RealFloat a) = Complex a - a
magnitude (x:+y) =  scaleFloat k
 (sqrt (sqr (scaleFloat mk x) + sqr (scaleFloat  
mk y)))

where k  = max (exponent x) (exponent y)
  mk = - k
  sqr x = x * x

and let us know what the results are?


thanks ian, here are the absolute runtimes (non-instrumented code)  
and the corresponding entries in the profile:


c_magnitude0 (Complex.Data.magnitude)   0m7.249s
c_magnitude1 (non-scaling version)  0m1.176s
c_magnitude2 (scaling version, strict square)   0m3.278s

 %time  %alloc
 (inherited)

c_magnitude0 91.6   90.2
c_magnitude1 41.7   49.6
c_magnitude2 81.5   71.1

interestingly, just pasting the original ghc library implementation  
seems to

slow things down considerably (0m12.264s) when compiling with

-O2
-funbox-strict-fields
-fvia-C
-optc-O2
-fdicts-cheap
-fno-method-sharing
-fglasgow-exts

when leaving away -fdicts-cheap and -fno-method-sharing the execution  
time for
the pasted library code reduces to 0m6.873s. seems like some options  
that are
useful (or even necessary?) for stream fusion rule reduction, may  
produce

non-optimal code in other cases?

sk

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


Re: [Haskell-cafe] uvector and the stream interface

2008-07-17 Thread Isaac Dupree

Evan Laforge wrote:

An abstraction stack:

   Impure  Pure


How about strict vs. lazy?  I ask because I assumed there were lazy
variants of uvector or storablevector, using the bytestring list of
chunks approach, but apparently not?


wait list of chunks makes something that behaves not like a 
random-access array, and yet is still rather strict in the elements. 
How about strict vs. lazy as in UArray vs. Array: whether the elements 
are evaluated lazily (although UArray has the complication that the 
elements must also be Storable: e.g. what if you want a strict 
random-access array of functions -- so there is not such an easy 
solution for a strict but boxed array).


so do we have at least three different variables here? :-)

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


[Haskell-cafe] Space leaks

2008-07-17 Thread Peter Gavin

Hello everyone,

I have this piece of code I've been working on, and I've been stuck on 
tracking down a space leak in it for some time now.  The code is 
essentially a tight loop that updates a rather largish data structure 
with embedded functions that are called by the driver loop.  The code 
doesn't accumulate any data as the loop runs (at least deliberately), so 
I would expect the memory profile to be flat.  Unfortunately, the 
profile is a wedge :)   I've added bangs and `seq` literally everywhere, 
and it looks (to me at least) like there's nothing left to be lazily 
evaluated anywhere.  I've used retainer profiling, and the functions 
that are leaking space according to the profiler output are strict 
throughout.


I'm really pulling my hair out over this, but I'm reluctant to publish 
the code just yet because I'm planning on using it (eventually) for my 
thesis. It seems like I've just about run out of options, though.


Does anyone have any advice on tracking down space leaks?  I don't want 
to accuse GHC of having a bug just yet, but has GHC had space leak bugs 
in the past?


Thanks in advance,
Peter Gavin
[EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Luke Palmer
On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin [EMAIL PROTECTED] wrote:
 Hello everyone,

 I have this piece of code I've been working on, and I've been stuck on
 tracking down a space leak in it for some time now.  The code is essentially
 a tight loop that updates a rather largish data structure with embedded
 functions that are called by the driver loop.  The code doesn't accumulate
 any data as the loop runs (at least deliberately), so I would expect the
 memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
 added bangs and `seq` literally everywhere, and it looks (to me at least)
 like there's nothing left to be lazily evaluated anywhere.  I've used
 retainer profiling, and the functions that are leaking space according to
 the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

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


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread stefan kersten

On 17.07.2008, at 17:18, Henning Thielemann wrote:
i've attached an example program which seems to indicate that the  
magnitude function from Data.Complex is very slow compared to a  
more naive implementation (for Complex Float). on my machine  
(intel core2 duo, osx 10.4) the CPU time using the library  
function is about 6-7 times as much as when using the other  
function. any ideas what might be going on? any flaws in my  
measurement code?


Complex.magnitude must prevent overflows, that is, if you just  
square 1e200::Double you get an overflow, although the end result  
may be also around 1e200. I guess, that to this end  
Complex.magnitude will separate mantissa and exponent, but this is  
done via Integers, I'm afraid.


very enlightening, thanks! it might be possible to (almost) get the  
best of two worlds (ported from dejagnu's libm):


c_magnitude4 :: Complex Float - Float
c_magnitude4 (x:+y) = if x'  y'
then mag y' x'
else mag x' y'
where
x'  = abs x
y'  = abs y
sqr x   = x * x
mag a 0 = a
mag a b = a * sqrt (1 + sqr (b/a))

is fast and doesn't overflow intermediate results but accuracy isn't  
so great ...


sk

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


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread Lennart Augustsson
If scaleFloat and exponent are implemented with bit twiddling they can
be quite fast.
I have a feeling that they involve slow FFI calls in GHC (being the
original author of a lot of the code involved).

On Thu, Jul 17, 2008 at 8:21 PM, stefan kersten [EMAIL PROTECTED] wrote:
 On 17.07.2008, at 17:18, Henning Thielemann wrote:

 i've attached an example program which seems to indicate that the
 magnitude function from Data.Complex is very slow compared to a more naive
 implementation (for Complex Float). on my machine (intel core2 duo, osx
 10.4) the CPU time using the library function is about 6-7 times as much as
 when using the other function. any ideas what might be going on? any flaws
 in my measurement code?

 Complex.magnitude must prevent overflows, that is, if you just square
 1e200::Double you get an overflow, although the end result may be also
 around 1e200. I guess, that to this end Complex.magnitude will separate
 mantissa and exponent, but this is done via Integers, I'm afraid.

 very enlightening, thanks! it might be possible to (almost) get the best of
 two worlds (ported from dejagnu's libm):

 c_magnitude4 :: Complex Float - Float
 c_magnitude4 (x:+y) = if x'  y'
then mag y' x'
else mag x' y'
where
x'  = abs x
y'  = abs y
sqr x   = x * x
mag a 0 = a
mag a b = a * sqrt (1 + sqr (b/a))

 is fast and doesn't overflow intermediate results but accuracy isn't so
 great ...

 sk

 ___
 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] Data.Complex.magnitude slow?

2008-07-17 Thread Henning Thielemann


On Thu, 17 Jul 2008, Ian Lynagh wrote:


On Thu, Jul 17, 2008 at 05:18:01PM +0200, Henning Thielemann wrote:


Complex.magnitude must prevent overflows, that is, if you just square
1e200::Double you get an overflow, although the end result may be also
around 1e200. I guess, that to this end Complex.magnitude will separate
mantissa and exponent, but this is done via Integers, I'm afraid.


Here's the code:

{-# SPECIALISE magnitude :: Complex Double - Double #-}
magnitude :: (RealFloat a) = Complex a - a
magnitude (x:+y) =  scaleFloat k
(sqrt ((scaleFloat mk x)^(2::Int) + (scaleFloat mk 
y)^(2::Int)))
   where k  = max (exponent x) (exponent y)
 mk = - k

So the slowdown may be due to the scaling, presumably to prevent
overflow as you say. However, the e^(2 :: Int) may also be causing a
slowdown, as (^) is lazy in its first argument; I'm not sure if there is
a rule that will rewrite that to e*e.


I guess the rule should be INLINE.

Indeed, here you can see
  http://darcs.haskell.org/packages/base/GHC/Float.lhs

that scaleFloat calls decodeFloat and encodeFloat. Both of them use 
Integer. I expect that most FPUs are able to divide a floating point 
number into exponent and mantissa, but GHC seems not to have a primitive 
for it? As a quick work-around, Complex.magnitude could check whether the 
arguments are too big, then use scaleFloat and otherwise it should use the 
naive algorithm.

 In the math library of C there is the function 'frexp'
   http://www.codecogs.com/reference/c/math.h/frexp.php?alias=
 but calling an external functions will be slower than a comparison that 
can be performed by a single FPU instruction.

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


Re: [Haskell-cafe] Data.Complex.magnitude slow?

2008-07-17 Thread Henning Thielemann


On Thu, 17 Jul 2008, stefan kersten wrote:


On 17.07.2008, at 17:18, Henning Thielemann wrote:
i've attached an example program which seems to indicate that the 
magnitude function from Data.Complex is very slow compared to a more naive 
implementation (for Complex Float). on my machine (intel core2 duo, osx 
10.4) the CPU time using the library function is about 6-7 times as much 
as when using the other function. any ideas what might be going on? any 
flaws in my measurement code?


Complex.magnitude must prevent overflows, that is, if you just square 
1e200::Double you get an overflow, although the end result may be also 
around 1e200. I guess, that to this end Complex.magnitude will separate 
mantissa and exponent, but this is done via Integers, I'm afraid.


very enlightening, thanks! it might be possible to (almost) get the best of 
two worlds (ported from dejagnu's libm):


c_magnitude4 :: Complex Float - Float
c_magnitude4 (x:+y) = if x'  y'
  then mag y' x'
  else mag x' y'
  where
  x'  = abs x
  y'  = abs y
  sqr x   = x * x
  mag a 0 = a
  mag a b = a * sqrt (1 + sqr (b/a))

is fast and doesn't overflow intermediate results but accuracy isn't so great 
...


Yes, that's also a possible work-around. But division is quite slow.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Jefferson Heard
Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what largish looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer [EMAIL PROTECTED] wrote:
 On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin [EMAIL PROTECTED] wrote:
 Hello everyone,

 I have this piece of code I've been working on, and I've been stuck on
 tracking down a space leak in it for some time now.  The code is essentially
 a tight loop that updates a rather largish data structure with embedded
 functions that are called by the driver loop.  The code doesn't accumulate
 any data as the loop runs (at least deliberately), so I would expect the
 memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
 added bangs and `seq` literally everywhere, and it looks (to me at least)
 like there's nothing left to be lazily evaluated anywhere.  I've used
 retainer profiling, and the functions that are leaking space according to
 the profiler output are strict throughout.

 I don't know what I can suggest as for general tactics.  Without
 seeing the code it's hard to say what could be happening.  Just
 remember that strictness is not always the answer!

 From the very limited amount of information I got from this
 description, my first guess would be the data structure itself, or the
 functions inside it.  If it's lazily generated, then you might not be
 seeing the full amount of space it's taking up at once.  But that's
 just a guess.

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




-- 
I try to take things like a crow; war and chaos don't always ruin a
picnic, they just mean you have to be careful what you swallow.

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


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Justin Bailey
On Thu, Jul 17, 2008 at 11:14 AM, Peter Gavin [EMAIL PROTECTED] wrote:

 evaluated anywhere.  I've used retainer profiling, and the functions that
 are leaking space according to the profiler output are strict throughout.


Have you looked at the Core code generated? That might show something that
isn't strict which you think is. I believe let statements in Core
represent allocations, while case statements are strict.

In case you don't know, the best thing you can do to read core is to add
comment annotations ({-# CORE ... #-} I think), which will help you
pinpoint which Haskell gets turned into core. To produce core with 6.8, use
the -fext-core flag.

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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Magnus Therning
Felipe Lessa wrote:
 Hi,

 I tried googling and searching the haskellwiki about this but wasn't
 lucky enough. My question is: is there a way to send struct arguments
 to C functions via the FFI or do I need to create a C wrapper? I guess
 there isn't, and while I can live without it, I'd like to leave no
 doubt.

You might find this old post of mine useful.

http://therning.org/magnus/archives/315



 Details:

 I have something like

 
 typedef struct vect {
 float x,y;
 } vect;

 void func(vect v);
 =

 on the C side and

 
 -- Please disregard float /= Float, just an example :)
 data Vector = Vector Float Float

 instance Storable Vector where
 ...
 

 on the Haskell side, and I want to call func with Vector as argument.
 Now, Vector isn't a basic FFI type, although it implements Storable.
 So does that mean that I need to create something like

 
 void funcWrapper(vect *v) {
 func(*v);
 }
 

 and then allocate some temporary memory on the Haskell side to use func?

 Cheers!



-- 
Magnus Therning (OpenPGP: 0xAB4DFBA4)
magnus@therning.org Jabber: magnus@therning.org
http://therning.org/magnus

Haskell is an even 'redder' pill than Lisp or Scheme.
 -- PaulPotts




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


Re: [Haskell-cafe] FFI and struct arguments

2008-07-17 Thread Duncan Coutts

On Thu, 2008-07-17 at 13:36 -0300, Felipe Lessa wrote:

 I am using hsc2hs currently, but googling about #def with Cabal I
 found out that some people were having trouble to make Cabal discover
 that hsc2hs had created a new C file. Specifically, bug #245 [1] which
 says that the milestone is undefined.

Note that a milestone of _|_ doesn't mean we don't want a fix, just that
nobody has said they're going to do it. We would welcome a fix for this
if someone wants to contribute. (Of course we'd like contributions to
fix all our bugs!)

Duncan

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


Re: [Haskell-cafe] Space leaks

2008-07-17 Thread Peter Gavin

Thanks for the responses.

This is basically what I've got looks like (grossly simplified):


data Monad m = Foo m a b =
 Foo
 { action :: m (Foo m a b, b)
 , update :: a - Foo m a b
 }

The driver loop injects new values with update, and executes action 
whenever it's ready to, replacing the old Foo with the newly returned Foo.


I finally fixed the space leak it by inserting SPECIALIZE pragmas for 
Foo IO a b on every function that creates a Foo. I'm not sure if I can 
remove all the strictness annotations I've accumulated yet, though. 
This is a bit disconcerting, though, because in the future I'd like to 
not use IO and use a strict State instead. I hope I won't have to 
specialize for every monad that ends up getting used.


Thanks again,
Pete


Jefferson Heard wrote:

Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what largish looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer [EMAIL PROTECTED] wrote:

On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin [EMAIL PROTECTED] wrote:

Hello everyone,

I have this piece of code I've been working on, and I've been stuck on
tracking down a space leak in it for some time now.  The code is essentially
a tight loop that updates a rather largish data structure with embedded
functions that are called by the driver loop.  The code doesn't accumulate
any data as the loop runs (at least deliberately), so I would expect the
memory profile to be flat.  Unfortunately, the profile is a wedge :)   I've
added bangs and `seq` literally everywhere, and it looks (to me at least)
like there's nothing left to be lazily evaluated anywhere.  I've used
retainer profiling, and the functions that are leaking space according to
the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

Luke
___
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] Space leaks

2008-07-17 Thread Peter Gavin

Replying to myself...

Interesting.  I removed all the bangs other than the obvious loop 
variables, and all the uses of seq that I had inserted, and there's 
still no leak.


Does anyone know why the leak would disappear when GHC is using IO other 
than a generic (unspecified) monad?  Is there something special about 
the = and return operators for IO that aren't true for other monads?


Thanks,
Pete


Peter Gavin wrote:

Thanks for the responses.

This is basically what I've got looks like (grossly simplified):


data Monad m = Foo m a b =
 Foo
 { action :: m (Foo m a b, b)
 , update :: a - Foo m a b
 }

The driver loop injects new values with update, and executes action 
whenever it's ready to, replacing the old Foo with the newly returned Foo.


I finally fixed the space leak it by inserting SPECIALIZE pragmas for 
Foo IO a b on every function that creates a Foo. I'm not sure if I can 
remove all the strictness annotations I've accumulated yet, though. This 
is a bit disconcerting, though, because in the future I'd like to not 
use IO and use a strict State instead. I hope I won't have to specialize 
for every monad that ends up getting used.


Thanks again,
Pete


Jefferson Heard wrote:

Peter, from 500 feet, we can't see much, but your strictness might
actually be your problem depending on what largish looks like and
whether you're reading your data from disc.  It's entirely possible
that your data structure updates or disc reads are head-strict and
you're evaluating or loading the entirety of data in memory at a
single update.

-- Jeff

On Thu, Jul 17, 2008 at 2:58 PM, Luke Palmer [EMAIL PROTECTED] wrote:

On Thu, Jul 17, 2008 at 12:14 PM, Peter Gavin [EMAIL PROTECTED] wrote:

Hello everyone,

I have this piece of code I've been working on, and I've been stuck on
tracking down a space leak in it for some time now.  The code is 
essentially

a tight loop that updates a rather largish data structure with embedded
functions that are called by the driver loop.  The code doesn't 
accumulate
any data as the loop runs (at least deliberately), so I would expect 
the
memory profile to be flat.  Unfortunately, the profile is a wedge 
:)   I've
added bangs and `seq` literally everywhere, and it looks (to me at 
least)

like there's nothing left to be lazily evaluated anywhere.  I've used
retainer profiling, and the functions that are leaking space 
according to

the profiler output are strict throughout.

I don't know what I can suggest as for general tactics.  Without
seeing the code it's hard to say what could be happening.  Just
remember that strictness is not always the answer!

From the very limited amount of information I got from this
description, my first guess would be the data structure itself, or the
functions inside it.  If it's lazily generated, then you might not be
seeing the full amount of space it's taking up at once.  But that's
just a guess.

Luke
___
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