Re: [Haskell-cafe] blas bindings, why are they so much slower the C?

2008-06-28 Thread Don Stewart
so I had a look at the code. The loops are all fine. replicateM_ isn't 
a problem, but getDot is decidedly non trivial. Lots of pattern matching
on different vector forms, and to top it off ffi calls.

With some inlining in the blas library I was able to cut a few seconds
off the running time, but getDot looks to be fundamentally a bit
complicated in the current implementation.

I wonder if you'll get different results with hmatrix?

Anyway, this is a library issue. Better take it up with Patrick.
Pass on to the library author the C code, the Haskell you think should
be compiled identically.

-- Don

aeyakovenko:
 i get the same crappy performance with:
 
 $ cat htestdot.hs
 {-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
 -fglasgow-exts -fbang-patterns -lcblas#-}
 module Main where
 
 import Data.Vector.Dense.IO
 import Control.Monad
 
 main = do
let size = 10
let times = 10*1000*1000
v1::IOVector Int Double - newListVector size $ replicate size 0.1
v2::IOVector Int Double - newListVector size $ replicate size 0.1
replicateM_ times $ v1 `getDot` v2
 
 
 
 On Fri, Jun 27, 2008 at 7:41 PM, Dan Doel [EMAIL PROTECTED] wrote:
  On Friday 27 June 2008, Anatoly Yakovenko wrote:
  $ cat htestdot.hs
  {-# OPTIONS_GHC -O2 -fexcess-precision -funbox-strict-fields
  -fglasgow-exts -fbang-patterns -lcblas#-}
  module Main where
 
  import Data.Vector.Dense.IO
  import Control.Monad
 
  main = do
 let size = 10
 let times = 10*1000*1000
 v1::IOVector Int Double - newListVector size $ replicate size 0.1
 v2::IOVector Int Double - newListVector size $ replicate size 0.1
 sum - foldM (\ ii zz - do
rv - v1 `getDot` v2
return $ zz + rv
) 0.0 [0..times]
 print $ sum
 
  Hackage is down for the time being, so I can't install blas and look at the
  core for your program. However, there are still some reasons why this code
  would be slow.
 
  For instance, a brief experiment seems to indicate that foldM is not a good
  consumer in the foldr/build sense, so no deforestation occurs. Your program
  is iterating over a 10-million element lazy list. That's going to add
  overhead. I wrote a simple test program which just adds 0.1 in each
  iteration:
 
   snip 
 
  {-# LANGUAGE BangPatterns #-}
 
  module Main (main) where
 
  import Control.Monad
 
  main = do
   let times = 10*1000*1000
   sum - foldM (\_ zz - return $ zz + 0.1) 0.0 [0..times]
  --  sum - foo 0 times 0.0
   print $ sum
 
  foo :: Int - Int - Double - IO Double
  foo k m !zz
   | k = m = foo (k+1) m (zz + 0.1)
   | otherwise = return zz
 
   snip 
 
  With foldM, it takes 2.5 seconds on my machine. If you comment that line, 
  and
  use foo instead, it takes around .1 seconds. So that's a factor of what, 
  250?
  That loop allows for a lot more unboxing, which allows much better code to 
  be
  generated.
 
  When Hackage comes back online, I'll take a look at your code, and see if I
  can make it run faster, but you might want to try it yourself in the time
  being. Strictifying the addition of the accumulator is probably a good idea,
  for instance.
 
  Cheers,
  -- Dan
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
Sat Jun 28 00:33:17 PDT 2008  Don Stewart [EMAIL PROTECTED]
  * Some inlining and unpacking for DVectors

New patches:

[Some inlining and unpacking for DVectors
Don Stewart [EMAIL PROTECTED]**20080628073317] {
hunk ./BLAS/Internal.hs 115
+{-# INLINE checkVecVecOp #-}
hunk ./Data/Vector/Dense/Internal.hs 78
-data DVector t n e = 
-  DV { fptr   :: !(ForeignPtr e) -- ^ a pointer to the storage region
- , offset :: !Int-- ^ an offset (in elements, not bytes) 
to the first element in the vector. 
- , len:: !Int-- ^ the length of the vector
- , stride :: !Int-- ^ the stride (in elements, not bytes) 
between elements.
+data DVector t n e =
+  DV { fptr   :: {-# UNPACK #-} !(ForeignPtr e) -- ^ a pointer to the 
storage region
+ , offset :: {-# UNPACK #-} !Int-- ^ an offset (in 
elements, not bytes) to the first element in the vector. 
+ , len:: {-# UNPACK #-} !Int-- ^ the length of the 
vector
+ , stride :: {-# UNPACK #-} !Int-- ^ the stride (in 
elements, not bytes) between elements.
hunk ./Data/Vector/Dense/Internal.hs 84
-| C !(DVector t n e)-- ^ a conjugated vector
+| C {-# UNPACK #-} !(DVector t n e)-- ^ a conjugated vector
hunk ./Data/Vector/Dense/Internal.hs 92
+{-# INLINE coerceVector #-}
hunk ./Data/Vector/Dense/Internal.hs 424
+
hunk ./Data/Vector/Dense/Operations.hs 144
+{-# INLINE getDot #-}
hunk ./Data/Vector/Dense/Operations.hs 153
-unsafeGetDot x@(DV _ _ _ _) (C (C y)) = 
+unsafeGetDot x@(DV _ _ _ _) (C (C y)) =
hunk ./Data/Vector/Dense/Operations.hs 155

Re: [Haskell-cafe] Re: Haskell on ARM (was Re: ANN: Topkata)

2008-06-28 Thread Adrian Hey

Hello Jeremy,

Jeremy Apthorp wrote:

Next year I'll be working on a project for my undergraduate computing
course at UNSW that will involve getting GHC to target the Nintendo
DS. It'll require cross-compilation, because the DS isn't powerful
enough to actually run GHC (4M main ram and a 66MHz processor). It'll
also require that I significantly strip down the runtime system, as
the current RTS won't fit in 4M and leave any left over for the main
application.


Maybe one of these would help (running Linux) ..

http://www.iyonix.com/

It'd be good too have a native code generator support for ARM (not via
C). Many years ago I tinkered with implementing a lazy FPL on ARM (on my
Acorn Risc PC). I never even started the compiler but got a basic single
threaded RTS and mark-sweep-compact garbage collector up and running
(written in ARM assembler).

It wasn't really useable for real programs though as I had to write my
function definitions as comments and actually implement the graph
reduction code by hand in assembler :-)

But I remember the ARM instruction set had some really useful features
that made things like checking for stack-heap collision cheap and if you
got the register allocation right (which is not hard on the ARM) you
could construct the overwhelming majority of heap records using a single
STMIA instruction. Almost seemed like it's instruction set was
designed for efficient FPL implementation :-)

Regards
--
Adrian Hey

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


[Haskell-cafe] The ping method in HDBC

2008-06-28 Thread Agent Zhang
Hi, there

I'm wondering if there's a ping method in HDBC that does the same
thing as Perl DBI's ping. Please see the following link for details:

http://search.cpan.org/~timb/DBI-1.605/DBI.pm#ping

I think It's rather important for database auto-connection when
preserving database connections for a quite long time in fastcgi
applications. Any ideas?

Thanks in advance!

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


[Haskell-cafe] Haskell Related Reading

2008-06-28 Thread Darrin Thompson
I have a trip coming up and might have some reading time. I was hoping to
get through some of the classics, bananas and lenses, the essence, etc.

So I have a few questions:

Bananas and lenses et. al. uses some notation that I don't understand right
out of the gate. Is there a good primer on whatever that brand of double
bars and arrows means?

The essense of functional programming looks good, I could understand it when
I skimmed it but can I print it out on US letter? The PDF at citeseer was
aligned badly. (Essece seemed like a fabulous intro or chapter 2 on getting
used to monads. Better than most stuff on the web. Funny that...)

I'm also interested in FRP as it might relate to web programming. Anyone
have a recommendation?

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


[Haskell-cafe] Hackage

2008-06-28 Thread Cetin Sert
Hi,

Hackage seems to have been down for a few days now. When is it going to be
back online? It is not possible to darcs-get any packages either.

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


[Haskell-cafe] Galois move complete, Hackage back online

2008-06-28 Thread Don Stewart
Galois has completed the move of its data center, and the services:

hackage.haskell.org
darcs.haskell.org

are now back online. Thanks for your patience, everyone!

Enjoy the new bandwidth.

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


[Haskell-cafe] Learning GADT types to simulate dependent types

2008-06-28 Thread Paul Johnson
I'm trying to understand how to use GADT types to simulate dependent 
types.  I'm trying to write  a version of list that uses Peano numbers 
in the types to keep track of how many elements are in the list.  Like this:


{-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

module Plist where


infixr 3 :|

data Zero

data S a

class Add n1 n2 t | n1 n2 - t, n1 t - n2

instance Add Zero n n
instance Add (S n1) n2 (S t)

data Plist n a where
   Nil :: Plist Zero a
   (:|) :: a - Plist n a - Plist (S n) a

instance (Show a) = Show (Plist n a) where
   show Nil = Nil
   show (x :| xs) = show x ++  :|  ++ show xs

pHead :: Plist (S n) a - a
pHead (x :| _) = x

pTail :: Plist (S n) a - Plist n a
pTail (_ :| xs) = xs


pConcat Nil ys = ys
pConcat (x :| xs) ys = x :| pConcat xs ys


Everything works except the last function (pConcat).  I figured that it 
should add the lengths of its arguments together, so I created a class 
Add as shown in the Haskell Wiki at 
http://www.haskell.org/haskellwiki/Type_arithmetic.  But now I'm stuck.  
When I try to load this module I get:


Plist.hs:32:8:
   GADT pattern match in non-rigid context for `Nil'
 Tell GHC HQ if you'd like this to unify the context
   In the pattern: Nil
   In the definition of `pConcat': pConcat Nil ys = ys
Failed, modules loaded: none.

(Line 32 is pConcat Nil ys = ys)

So how do I do this?  Am I on the right track?  Can someone help improve 
my Oleg rating?


Thanks,

Paul.

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


Re: [Haskell-cafe] Learning GADT types to simulate dependent types

2008-06-28 Thread Daniel Fischer
Am Samstag, 28. Juni 2008 19:51 schrieb Paul Johnson:
 I'm trying to understand how to use GADT types to simulate dependent
 types.  I'm trying to write  a version of list that uses Peano numbers
 in the types to keep track of how many elements are in the list.  Like
 this:

 {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

 module Plist where


 infixr 3 :|

 data Zero

 data S a

 class Add n1 n2 t | n1 n2 - t, n1 t - n2

 instance Add Zero n n
 instance Add (S n1) n2 (S t)

 data Plist n a where
 Nil :: Plist Zero a
 (:|) :: a - Plist n a - Plist (S n) a

 instance (Show a) = Show (Plist n a) where
 show Nil = Nil
 show (x :| xs) = show x ++  :|  ++ show xs

 pHead :: Plist (S n) a - a
 pHead (x :| _) = x

 pTail :: Plist (S n) a - Plist n a
 pTail (_ :| xs) = xs


 pConcat Nil ys = ys
 pConcat (x :| xs) ys = x :| pConcat xs ys


 Everything works except the last function (pConcat).  I figured that it
 should add the lengths of its arguments together, so I created a class
 Add as shown in the Haskell Wiki at
 http://www.haskell.org/haskellwiki/Type_arithmetic.  But now I'm stuck.
 When I try to load this module I get:

 Plist.hs:32:8:
 GADT pattern match in non-rigid context for `Nil'
   Tell GHC HQ if you'd like this to unify the context
 In the pattern: Nil
 In the definition of `pConcat': pConcat Nil ys = ys
 Failed, modules loaded: none.

 (Line 32 is pConcat Nil ys = ys)

 So how do I do this?  Am I on the right track?  Can someone help improve
 my Oleg rating?

 Thanks,

 Paul.


My Oleg rating isn't high either, and certainly you can do it more elegant, 
but


class Concat l1 l2 l3 | l1 l2 - l3, l1 l3 - l2 where
pConcat :: l1 a - l2 a - l3 a

instance Concat (Plist Zero) (Plist n) (Plist n) where
pConcat _ ys = ys

instance Concat (Plist n1) (Plist n2) (Plist t) =
Concat (Plist (S n1)) (Plist n2) (Plist (S t)) where
pConcat (x :| xs) ys = x :| pConcat xs ys


works, you don't even need the Add class then - btw, you'd want
instance Add n1 n2 t = Add (S n1) n2 (S t)
anyway.

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


Re: [Haskell-cafe] Learning GADT types to simulate dependent types

2008-06-28 Thread Dan Doel
On Saturday 28 June 2008, Paul Johnson wrote:
 I'm trying to understand how to use GADT types to simulate dependent
 types.  I'm trying to write  a version of list that uses Peano numbers
 in the types to keep track of how many elements are in the list.  Like
 this:

 {-# OPTIONS -fglasgow-exts -fallow-undecidable-instances #-}

 module Plist where


 infixr 3 :|

 data Zero

 data S a

 class Add n1 n2 t | n1 n2 - t, n1 t - n2

 instance Add Zero n n
 instance Add (S n1) n2 (S t)

 data Plist n a where
 Nil :: Plist Zero a
 (:|) :: a - Plist n a - Plist (S n) a

 instance (Show a) = Show (Plist n a) where
 show Nil = Nil
 show (x :| xs) = show x ++  :|  ++ show xs

 pHead :: Plist (S n) a - a
 pHead (x :| _) = x

 pTail :: Plist (S n) a - Plist n a
 pTail (_ :| xs) = xs


 pConcat Nil ys = ys
 pConcat (x :| xs) ys = x :| pConcat xs ys


 Everything works except the last function (pConcat).  I figured that it
 should add the lengths of its arguments together, so I created a class
 Add as shown in the Haskell Wiki at
 http://www.haskell.org/haskellwiki/Type_arithmetic.  But now I'm stuck.
 When I try to load this module I get:

 Plist.hs:32:8:
 GADT pattern match in non-rigid context for `Nil'
   Tell GHC HQ if you'd like this to unify the context
 In the pattern: Nil
 In the definition of `pConcat': pConcat Nil ys = ys
 Failed, modules loaded: none.

 (Line 32 is pConcat Nil ys = ys)

 So how do I do this?  Am I on the right track?  Can someone help improve
 my Oleg rating?

There are a couple issues that jump out at me. First, your second instance for 
Add is a bit off. It should be more like:

instance (Add n1 n2 t) = Add (S n1) n2 (S t)

Second, the reason you're getting that particular error with pConcat is that 
it doesn't have a type signature. Matching on GADTs requires one. However, 
fixing those here, I still got errors, and I'm not enough of a type 
class/fundep wizard to know what the problem is. Instead, I might suggest 
using type families for the type-level arithmetic:

type family Add n1 n2 :: *
type instance Add Zero   n2 = n2
type instance Add (S n1) n2 = S (Add n1 n2)

Then the signature of pConcat becomes:

pConcat :: Plist m a - Plist n a - Plist (Add m n) a

Which works fine. As an added bonus, the type family doesn't require 
undecidable instances like the type class does.

Type families are a bit iffy in 6.8.*, but they'll work all right for simple 
stuff like this, at least.

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


Re: [Haskell-cafe] Learning GADT types to simulate dependent types

2008-06-28 Thread Paul Johnson

Daniel Fischer wrote:


My Oleg rating isn't high either, and certainly you can do it more elegant, 
but



class Concat l1 l2 l3 | l1 l2 - l3, l1 l3 - l2 where
pConcat :: l1 a - l2 a - l3 a

instance Concat (Plist Zero) (Plist n) (Plist n) where
pConcat _ ys = ys

instance Concat (Plist n1) (Plist n2) (Plist t) =
Concat (Plist (S n1)) (Plist n2) (Plist (S t)) where
pConcat (x :| xs) ys = x :| pConcat xs ys


works, you don't even need the Add class then - btw, you'd want
instance Add n1 n2 t = Add (S n1) n2 (S t)
anyway.

  
Thanks, and also thanks to Dan Doel who showed how to do it with the new 
type families.  I'll stick with the Fundeps solution here for the moment 
until type families settle down, but that method is cleaner. 


I was also able to write this:


class Concat p1 p2 p3 | p1 p2 - p3, p1 p3 - p2 where
   pConcat :: p1 a - p2 a - p3 a
   pBogus :: p1 a - p2 a - p3 a

instance Concat (Plist Zero) (Plist n) (Plist n) where
   pConcat _ ys = ys
   pBogus _ ys = ys

instance Concat (Plist n1) (Plist n2) (Plist t) =
   Concat (Plist (S n1)) (Plist n2) (Plist (S t)) where
   pConcat (x :| xs) ys = x :| pConcat xs ys
   pBogus xs ys = ys

And indeed the second definition of pBogus gave me a compile-time type 
error because the length of the result didn't agree with the type length.


I'm going to be doing a presentation on Haskell for my boss soon, and 
this should definitely impress (he has a solid coding background).


Thanks again,

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


Re: Haskell on ARM (was Re: [Haskell-cafe] ANN: Topkata)

2008-06-28 Thread Malcolm Wallace

Just a random note. jhc works fine on ARM,


Another semi-random note: nhc12 and nhc13 (precursors to nhc98) were  
originally developed on an ARM with 2Mb of memory, way back in 1994-5.


Regards,
Malcolm

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


[Haskell-cafe] Ptr Word8 display question

2008-06-28 Thread Galchin, Vasili
Hi,

Suppose I have a value of type Ptr Word8 and also an Int which is the
length of the Ptr Word8(sorry if I am thinking too much in a C string frame
of mind). How can I display the Ptr Word8 value of the given length?

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


Re: [Haskell-cafe] Ptr Word8 display question

2008-06-28 Thread Antoine Latter
2008/6/28 Galchin, Vasili [EMAIL PROTECTED]:
 Hi,

 Suppose I have a value of type Ptr Word8 and also an Int which is the
 length of the Ptr Word8(sorry if I am thinking too much in a C string frame
 of mind). How can I display the Ptr Word8 value of the given length?

 Vasili


You're best bet would be to use 'peekArray' or 'withArrayLen' to get a
list of Word8 values, and then display that however you want.

withArrayLen: 
http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign-Marshal-Array.html#v%3AwithArrayLen

peekArray: 
http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign-Marshal-Array.html#v%3ApeekArray

I hope that helps!

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


Re: [Haskell-cafe] Ptr Word8 display question

2008-06-28 Thread Antoine Latter
2008/6/28 Galchin, Vasili [EMAIL PROTECTED]:
 Hi,

 Suppose I have a value of type Ptr Word8 and also an Int which is the
 length of the Ptr Word8(sorry if I am thinking too much in a C string frame
 of mind). How can I display the Ptr Word8 value of the given length?


You mentioned C style strings - if you need to interface with foreign
libraries which are expecting/providing actual C strings, you may also
want to look at the Foreign.C.String module:

http://haskell.org/ghc/docs/latest/html/libraries/base/Foreign-C-String.html

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