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

Don Stewart dons at galois.com
Sat Jun 28 03:44:51 EDT 2008


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 <dan.doel at gmail.com> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
-------------- next part --------------
Sat Jun 28 00:33:17 PDT 2008  Don Stewart <dons at galois.com>
  * Some inlining and unpacking for DVectors

New patches:

[Some inlining and unpacking for DVectors
Don Stewart <dons at galois.com>**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
-unsafeGetDot (C x) y = 
+unsafeGetDot (C x) y =
hunk ./Data/Vector/Dense/Operations.hs 157
+{-# INLINE unsafeGetDot #-}
hunk ./Data/Vector/Dense/Operations.hs 376
+
}

Context:

[blas.cabal: add Data.Matrix.Banded.Internal
Patrick Perry <patperry at stanford.edu>**20080529165336] 
[Data/Matrix/Banded/Internal.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080529165237] 
[TAG 0.4.1
Patrick Perry <patperry at stanford.edu>**20080613004842] 
[INSTALL: update description of custom installation
Patrick Perry <patperry at stanford.edu>**20080611221059] 
[blas.cabal: fix so that hackage doesn't complain
Patrick Perry <patperry at stanford.edu>**20080611221043] 
[blas.cabal: change version number to 0.4.1
Patrick Perry <patperry at stanford.edu>**20080611220330] 
[blas.cabal: add INSTALL
Patrick Perry <patperry at stanford.edu>**20080611220129] 
[INSTALL: initial version
Patrick Perry <patperry at stanford.edu>**20080611220104] 
[blas.cabal: change "gsl_cblas" to "gslcblas"
Patrick Perry <patperry at stanford.edu>**20080611220026] 
[blas.cabal: change default library for vecLib to cblas
Patrick Perry <patperry at stanford.edu>**20080611212059] 
[Setup.lhs: change '-lblas' to '-lcblas'
Patrick Perry <patperry at stanford.edu>**20080611212032] 
[blas.cabal: change 'other' flag to 'custom'; reverse order of atlas libs
Patrick Perry <patperry at stanford.edu>**20080611172206] 
[tests/Vector.hs: remove import of Debug.Trace
Patrick Perry <patperry at stanford.edu>**20080611164430] 
[tests/Matrix.hs: clean up cruft like using 'scale' instead of '*>'
Patrick Perry <patperry at stanford.edu>**20080611164406] 
[blas.cabal: add tests/Makefile
Patrick Perry <patperry at stanford.edu>**20080611163326] 
[tests/Makefile: initial version
Patrick Perry <patperry at stanford.edu>**20080611163303] 
[blas.cabal: add flags to configure which CBLAS to use
Patrick Perry <patperry at stanford.edu>**20080611162800] 
[BLAS/C/Level1.hs: add -fno-excess-precision flag for portability of acxpy implementation.
Patrick Perry <patperry at stanford.edu>**20080611070402] 
[tests/Matrix.hs: change exact comparison to relative comparison in scale elems test
Patrick Perry <patperry at stanford.edu>**20080611064931] 
[blas.cabal: removed trailing period from synopsis
Patrick Perry <patperry at stanford.edu>**20080605204707] 
[TAG 0.4
Patrick Perry <patperry at stanford.edu>**20080605204658] 
[TAG 0.4
Patrick Perry <patperry at stanford.edu>**20080605203651] 
[BLAS/Internal.hs: add trailing newline
Patrick Perry <patperry at stanford.edu>**20080605203537] 
[Data/Matrix/Dense/Internal.hs: fix error message for azipWith
Patrick Perry <patperry at stanford.edu>**20080529165127] 
[Data/Matrix/Dense/Internal.hs: remove spurious BLAS1 requirement for liftV and liftV2
Patrick Perry <patperry at stanford.edu>**20080529165028] 
[BLAS/Tensor/Immutable.hs: make BLAS1 a base class
Patrick Perry <patperry at stanford.edu>**20080529164955] 
[Data/Matrix/Dense.hs: add Dense Tensor class to export list
Patrick Perry <patperry at stanford.edu>**20080528225632] 
[Data/Matrix/Dense/IO.hs: add Dense Tensor class to export list
Patrick Perry <patperry at stanford.edu>**20080528225617] 
[Data/Matrix/Dense/Internal.hs: add Dense Tensor instances
Patrick Perry <patperry at stanford.edu>**20080528225540] 
[Data/Vector/Dense.hs: add Dense Tensor class to export list
Patrick Perry <patperry at stanford.edu>**20080528225501] 
[Data/Vector/Dense/IO.hs: add Dense Tensor class to export list
Patrick Perry <patperry at stanford.edu>**20080528225446] 
[Data/Vector/Dense/Internal.hs: add Dense Tensor instances
Patrick Perry <patperry at stanford.edu>**20080528225350] 
[blas.cabal: add BLAS.Tensor.Dense modules
Patrick Perry <patperry at stanford.edu>**20080528224313] 
[Data/Matrix/Dense/Internal.hs: documentation and whitespace
Patrick Perry <patperry at stanford.edu>**20080528224251] 
[BLAS/Tensor.hs: add BLAS.Tensor.Dense to export list
Patrick Perry <patperry at stanford.edu>**20080528224146] 
[BLAS/Tensor/ReadOnly.hs: remove newZero and newConstant
Patrick Perry <patperry at stanford.edu>**20080528224037] 
[BLAS/Tensor/Immutable.hs: remove zero and constant
Patrick Perry <patperry at stanford.edu>**20080528223958] 
[BLAS/Tensor/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528223919] 
[BLAS/Tensor/Dense/ReadOnly.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528223854] 
[BLAS/Tensor/Dense/Immutable.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528223837] 
[tests/TriMatrix.hs: use Matrix type alias instead of DMatrix Imm
Patrick Perry <patperry at stanford.edu>**20080528182454] 
[Test/QuickCheck/Matrix/Tri/Dense.hs: use Matrix type alias instead of DMatrix Imm
Patrick Perry <patperry at stanford.edu>**20080528182418] 
[Data/Matrix/Dense/Internsl.hs: change type aliases for Matrix and IOMatrix to use partial application
Patrick Perry <patperry at stanford.edu>**20080528182342] 
[Setup.lhs: add HermMatrix tests
Patrick Perry <patperry at stanford.edu>**20080528174326] 
[blas.cabal: add tests/HermMatrix.hs
Patrick Perry <patperry at stanford.edu>**20080528174311] 
[tests/HermMatrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528174201] 
[blas.cabal: add Test.QuickCheck.Matrix.Herm.Dense
Patrick Perry <patperry at stanford.edu>**20080528173009] 
[Test/QuickCheck/Matrix/Herm/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528172947] 
[blas.cabal: add Data.Matrix.Herm.Dense
Patrick Perry <patperry at stanford.edu>**20080528165116] 
[Data/Matrix/Herm/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528165055] 
[blas.cabal: add Data.Matrix.Herm
Patrick Perry <patperry at stanford.edu>**20080528161706] 
[Data/Matrix/Herm.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528161648] 
[Setup.lhs: add TriMatrix tests
Patrick Perry <patperry at stanford.edu>**20080528160613] 
[blas.cabal: add tests/TriMatrix.hs
Patrick Perry <patperry at stanford.edu>**20080528160559] 
[tests/TriMatrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080528160232] 
[blas.cabal: add FlexibleInstances to language extensions
Patrick Perry <patperry at stanford.edu>**20080528160040] 
[Data/Matrix/Tri/Dense.hs: fix bug in Tri operations for herm-ed matrices
Patrick Perry <patperry at stanford.edu>**20080528155941] 
[Data/Matrix/Tri/Dense.hs: add FlexibleInstances language pragma"
Patrick Perry <patperry at stanford.edu>**20080528155901] 
[Data/Matrix/Tri.hs: add FlexibleInstances language pragma"
Patrick Perry <patperry at stanford.edu>**20080528155835] 
[BLAS/Matrix/ReadOnly.hs: add FlexibleInstances language pragma"
Patrick Perry <patperry at stanford.edu>**20080528155810] 
[blas.cabal: add Test.QuickCheck.Matrix.Tri.Dense
Patrick Perry <patperry at stanford.edu>**20080527223853] 
[Test/QuickCheck/Matrix/Tri/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527223835] 
[Data/Matrix/Tri.hs: add Show instance
Patrick Perry <patperry at stanford.edu>**20080527223736] 
[blas.cabal: add Data.Matrix.Tri.Dense
Patrick Perry <patperry at stanford.edu>**20080527205857] 
[Data/Matrix/Tri/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527205841] 
[BLAS/Matrix/Solve/ReadOnly.hs: add IO to result types
Patrick Perry <patperry at stanford.edu>**20080527205646] 
[BLAS/Matrix/Solve/ReadOnly.hs: change dimension types
Patrick Perry <patperry at stanford.edu>**20080527204702] 
[BLAS/Matrix/Solve/Immutable.hs: change dimension types
Patrick Perry <patperry at stanford.edu>**20080527204647] 
[BLAS/Matrix.hs: export BLAS.Matrix.Solve
Patrick Perry <patperry at stanford.edu>**20080527204151] 
[blas.cabal: add BLAS.Matrix.Solve
Patrick Perry <patperry at stanford.edu>**20080527204059] 
[BLAS/Matrix/Solve.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527204054] 
[blas.cabal: add BLAS.Matrix.Solve.ReadOnly
Patrick Perry <patperry at stanford.edu>**20080527203801] 
[BLAS/Matrix/Solve/ReadOnly.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527203743] 
[blas.cabal: add BLAS.Matrix.Solve.Immutable
Patrick Perry <patperry at stanford.edu>**20080527203506] 
[BLAS/Matrix/Solve/Immutable.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527203446] 
[Data/Matrix/Tri.hs: fix bug in herm
Patrick Perry <patperry at stanford.edu>**20080527184453] 
[tests/Matrix.hs: change <> to <**>
Patrick Perry <patperry at stanford.edu>**20080527184357] 
[BLAS/Matrix/Immutable.hs: change <> to <**>
Patrick Perry <patperry at stanford.edu>**20080527184230] 
[Data/Matrix/Tri.hs: add lower, lowerU, upper, upperU
Patrick Perry <patperry at stanford.edu>**20080527173710] 
[blas.cabal: add Data.Matrix.Tri
Patrick Perry <patperry at stanford.edu>**20080527173220] 
[Data/Matrix/Tri.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527173203] 
[Setup.lhs: add Matrix tests
Patrick Perry <patperry at stanford.edu>**20080527074811] 
[blas.cabal: add tests/Matris.hs
Patrick Perry <patperry at stanford.edu>**20080527074751] 
[tests/Matrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527074707] 
[BLAS/Matrix/Immutable.hs: add FlexibleInstances language pragma"
Patrick Perry <patperry at stanford.edu>**20080527074607] 
[blas.cabal: add Test.QuickCheck.Matrix.Dense
Patrick Perry <patperry at stanford.edu>**20080527073038] 
[Test/QuickCheck/Matrix/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527073026] 
[blas.cabal: add Test.QuickCheck.Matrix
Patrick Perry <patperry at stanford.edu>**20080527072834] 
[Test/QuickCheck/Matrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527072817] 
[LICENSE: change copyright
Patrick Perry <patperry at stanford.edu>**20080527072206] 
[blas.cabal: add BLAS.Matrix
Patrick Perry <patperry at stanford.edu>**20080527071901] 
[BLAS/Matrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527071848] 
[Data/Matrix/Dense/IO.hs: add BLAS.Matrix.ReadOnly to export list
Patrick Perry <patperry at stanford.edu>**20080527071634] 
[blas.cabal: add BLAS.Matrix.ReadOnly
Patrick Perry <patperry at stanford.edu>**20080527071554] 
[BLAS/Matrix/ReadOnly.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527071537] 
[Data/Matrix/Dense.hs: add sapply and sapplyMat to exports
Patrick Perry <patperry at stanford.edu>**20080527071323] 
[Data/Matrix/Dense/Operations.hs: add unscaled versions of getApply and getApplyMat
Patrick Perry <patperry at stanford.edu>**20080527071034] 
[BLAS/Matrix/Immutable.hs: add precedence declaration for <>
Patrick Perry <patperry at stanford.edu>**20080527070727] 
[Data/Matrix/Dense.hs: add BLAS.Matrix.Immutable to export list
Patrick Perry <patperry at stanford.edu>**20080527065253] 
[blas.cabal: add BLAS.Matrix.Immutable
Patrick Perry <patperry at stanford.edu>**20080527065121] 
[BLAS/Matrix/Immutable.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527065100] 
[Data/Matrix/Dense/IO.hs: change BLAS.Matrix to BLAS.Matrix.Base
Patrick Perry <patperry at stanford.edu>**20080527064421] 
[Data/Matrix/Dense/Internal.hs: change BLAS.Matrix to BLAS.Matrix.Base
Patrick Perry <patperry at stanford.edu>**20080527064406] 
[Data/Matrix/Dense.hs: change BLAS.Matrix to BLAS.Matrix.Base
Patrick Perry <patperry at stanford.edu>**20080527064346] 
[blas.cabal: change BLAS.Matrix to BLAS.Matrix.Base
Patrick Perry <patperry at stanford.edu>**20080527064310] 
[BLAS/Matrix/Base.hs: renamed from BLAS/Matrix.hs
Patrick Perry <patperry at stanford.edu>**20080527064238] 
[blas.cabal: add Data.Matrix.Dense
Patrick Perry <patperry at stanford.edu>**20080527043155] 
[Data/Matrix/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527043139] 
[blas.cabal: change module ordering
Patrick Perry <patperry at stanford.edu>**20080527042123] 
[Data/Vector/Dense/IO.hs: whitespace
Patrick Perry <patperry at stanford.edu>**20080527042049] 
[blas.cabal: add Data.Matrix.Dense.IO
Patrick Perry <patperry at stanford.edu>**20080527042032] 
[Data/Matrix/Dense/IO.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527042002] 
[blas.cabal: add Data.Matrix.Dense.Operations
Patrick Perry <patperry at stanford.edu>**20080527041414] 
[Data/Matrix/Dense/Operations.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080527041352] 
[Data/Vector/Dense/Operations.hs: add rewrite rules for scale/plus and scale/minus
Patrick Perry <patperry at stanford.edu>**20080527035530] 
[blas.cabal: add Data.Matrix.Dense.Internal
Patrick Perry <patperry at stanford.edu>**20080526221959] 
[Data/Matrix/Dense/Internal.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526221936] 
[BLAS/Internal.hs: add checked matrix ops
Patrick Perry <patperry at stanford.edu>**20080526220230] 
[blas.cabal: whitespace
Patrick Perry <patperry at stanford.edu>**20080526203315] 
[blas.cabal: add BLAS.Matrix
Patrick Perry <patperry at stanford.edu>**20080526202844] 
[BLAS/Matrix.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526202826] 
[Setup.lhs: add tests
Patrick Perry <patperry at stanford.edu>**20080526202108] 
[blas.cabal: add tests/Vector.hs
Patrick Perry <patperry at stanford.edu>**20080526201445] 
[tests/Vector.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526201344] 
[BLAS/Elem/Base.hs: add norm1 to Elem class
Patrick Perry <patperry at stanford.edu>**20080526195928] 
[Data/Vector/Dense/IO.hs: refine export list
Patrick Perry <patperry at stanford.edu>**20080526195547] 
[Data/Vector/Dense.hs: add Scalable instance for Vector
Patrick Perry <patperry at stanford.edu>**20080526195404] 
[blas.cabal: add BLAS.Tensor.Scalable
Patrick Perry <patperry at stanford.edu>**20080526195052] 
[BLAS/Tensor.hs: add BLAS.Tensor.Scalable to export list
Patrick Perry <patperry at stanford.edu>**20080526195022] 
[BLAS/Tensor/Scalable.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526194951] 
[Data/Vector/Dense/IO.hs: change (*>) to scale
Patrick Perry <patperry at stanford.edu>**20080526194912] 
[Data/Vector/Dense/Operations.hs: change (*>) to scale
Patrick Perry <patperry at stanford.edu>**20080526194825] 
[BLAS/Tensor/Mutable.hs: add LANGUAGE pragma
Patrick Perry <patperry at stanford.edu>**20080526072058] 
[Test/QuickCheck/Vector/Dense.hs: remove scaledVector
Patrick Perry <patperry at stanford.edu>**20080526071641] 
[blas.cabal: add Test.QuickCheck.Vector.Dense
Patrick Perry <patperry at stanford.edu>**20080526071243] 
[Test/QuickCheck/Vector/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526071222] 
[blas.cabal: add Test.QuickCheck.Vector
Patrick Perry <patperry at stanford.edu>**20080526071031] 
[Test/QuickCheck/Vector.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526071009] 
[blas.cabal: add Test.QuickCheck.Complex
Patrick Perry <patperry at stanford.edu>**20080526070857] 
[Test/QuickCheck/Complex.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526070722] 
[Data/Vector/Dense.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526070434] 
[blas.cabal: add Data.Vector.Dense
Patrick Perry <patperry at stanford.edu>**20080526070357] 
[blas.cabal: add Data.Vector.Dense.IO
Patrick Perry <patperry at stanford.edu>**20080526065747] 
[Data/Vector/Dense/IO.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526065717] 
[blas.cabal: add Data.Vector.Dense.Operations
Patrick Perry <patperry at stanford.edu>**20080526064553] 
[BLAS/Vector.hs: change documentation for conj
Patrick Perry <patperry at stanford.edu>**20080526064532] 
[Data/Vector/Dense/Operations.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526064445] 
[BLAS/C/Types.hs: add functions to get CBLAS enumeration values
Patrick Perry <patperry at stanford.edu>**20080526062555] 
[BLAS/C/Level1.hs: get rid of inmax and nrm1
Patrick Perry <patperry at stanford.edu>**20080526034201] 
[blas.cabal: add Data.Vector.Dense.Internal
Patrick Perry <patperry at stanford.edu>**20080526033626] 
[Data/Vector/Dense/Internal.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526033601] 
[BLAS/Internal.hs: add checkedSubvector, checkedSubvectorWithStride, checkVecVecOp
Patrick Perry <patperry at stanford.edu>**20080526033245] 
[BLAS/Access.hs: haddock fix
Patrick Perry <patperry at stanford.edu>**20080526030529] 
[blas.cabal: add BLAS.Internal
Patrick Perry <patperry at stanford.edu>**20080526024412] 
[BLAS/Internal.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526024356] 
[blas.cabal: add BLAS.Access
Patrick Perry <patperry at stanford.edu>**20080526024102] 
[BLAS/Access.hs: initial versoin
Patrick Perry <patperry at stanford.edu>**20080526024041] 
[add BLAS.Vector
Patrick Perry <patperry at stanford.edu>**20080526023443] 
[BLAS/Vector.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526023427] 
[blas.cabal: hide Double and Zomplex CBLAS modules
Patrick Perry <patperry at stanford.edu>**20080526022240] 
[blas.cabal: add BLAS.Elem
Patrick Perry <patperry at stanford.edu>**20080526022136] 
[BLAS/Elem.hs: initial version
Patrick Perry <patperry at stanford.edu>**20080526022119] 
[blas.cabal: update name of BLAS.Elem.Base
Patrick Perry <patperry at stanford.edu>**20080526021822] 
[BLAS/C/Level1.hs: fixed import path for BLAS.Elem.Base
Patrick Perry <patperry at stanford.edu>**20080526021740] 
[BLAS/Elem/Base.hs: renamed from BLAS/Elem.hs
Patrick Perry <patperry at stanford.edu>**20080526021654] 
[blas.cabal: add BLAS.Tensor
Patrick Perry <patperry at stanford.edu>**20080526021507] 
[BLAS/Tensor.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526021440] 
[blas.cabal: add BLAS.Tensor.Mutable
Patrick Perry <patperry at stanford.edu>**20080526020815] 
[BLAS/Tenosr/Mutable.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526020758] 
[blas.cabal: add BLAS.Tensor.ReadOnly
Patrick Perry <patperry at stanford.edu>**20080526020232] 
[BLAS/Tensor/ReadOnly.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526020152] 
[BLAS/Tensor/Immutable.hs: fix import path for BLAS.Tensor.Base
Patrick Perry <patperry at stanford.edu>**20080526020107] 
[BLAS/Tensor/Base.hs: remove infix precedence for '*>'
Patrick Perry <patperry at stanford.edu>**20080526020029] 
[blas.cabal: updated Tensor modules
Patrick Perry <patperry at stanford.edu>**20080526015422] 
[BLAS/Tensor/Immutable.hs: renamed from BLAS/ITensor.hs
Patrick Perry <patperry at stanford.edu>**20080526015353] 
[BLAS/Tensor/Base.hs: renamed from BLAS/Tensor.hs
Patrick Perry <patperry at stanford.edu>**20080526015330] 
[blas.cabal: add BLAS/ITensor.hs
Patrick Perry <patperry at stanford.edu>**20080526014209] 
[BLAS/ITensor.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526014130] 
[blas.cabal: add BLAS/Tensor.hs
Patrick Perry <patperry at stanford.edu>**20080526013528] 
[BLAS/Tensor.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526013500] 
[blas.cabal: initial import
Patrick Perry <patperry at stanford.edu>**20080526012351] 
[Setup.lhs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012328] 
[LICENSE: initial import
Patrick Perry <patperry at stanford.edu>**20080526012314] 
[BLAS/C.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012224] 
[BLAS/C/Level3.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012154] 
[BLAS/C/Level2.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012146] 
[BLAS/C/Level1.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012138] 
[BLAS/C/Zomplex.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012120] 
[BLAS/C/Double.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012103] 
[BLAS/C/Types.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526012025] 
[BLAS/Types.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526011950] 
[BLAS/Elem.hs: initial import
Patrick Perry <patperry at stanford.edu>**20080526011851] 
Patch bundle hash:
6adf112a36feb0686f33a8d63513886101302a7d


More information about the Haskell-Cafe mailing list