Re: [Haskell-cafe] Problem with TemplateHaskell

2011-11-02 Thread Magicloud Magiclouds
On Tue, Nov 1, 2011 at 5:42 PM, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 Hi,
  I have code as following, to make a toDocument function (using
 Data.Bsin.=:) for a data structure.

 bson :: DecsQ - DecsQ
 bson decsq = do
  decs - decsq
  let datad = head decs
      DataD _ _ _ cons _ = datad
      to = mkName toDocument
      from = mkName fromDocument
  fund - mapM (\con -
                 case con of
                   RecC n types - do
                     let nvs = map (\(nv, _, _) -
                                     nv
                                   ) types
                     funD to [clause [conP n $ map varP nvs]
                              (normalB $ listE $ map (\nv -
                                                       infixE (Just $
 litE $ stringL $ show nv)
                                                              (varE $
 mkName =:)
                                                              $ Just $
 appE (varE $ mkName val)

     $ varE nv
                                                     ) nvs) []]
               ) cons
  return (datad : fund)

  Testing code is as:

 data T = T { a :: Int
           , b :: Char }

 *TH runQ (bson [d|data T = T {a :: Int, b :: Char}|])

 [DataD [] T_0 [] [RecC T_1 [(a_2,NotStrict,ConT
 GHC.Types.Int),(b_3,NotStrict,ConT GHC.Types.Char)]] [],FunD
 toDocument [Clause [ConP T_1 [VarP a_2,VarP b_3]] (NormalB (ListE
 [InfixE (Just (LitE (StringL a_2))) (VarE =:) (Just (AppE (VarE val)
 (VarE a_2))),InfixE (Just (LitE (StringL b_3))) (VarE =:) (Just
 (AppE (VarE val) (VarE b_3)))])) []]]

  So you see that, it changed the name from T/a/b to T_0/T_1/a_2/b_3.
 Why is that? I did not have code to modify original data declaration.
 --
 竹密岂妨流水过
 山高哪阻野云飞


Here is the code it actually generated:
test.hs:1:1: Splicing declarations
bson [d| data T = T {a :: Int, b :: String} |]
  ==
test.hs:(7,3)-(8,38)
data T_a1XY = T_a1XZ {a_a1Y0 :: Int, b_a1Y1 :: String}
toName (T_a1XZ a_a1Y0 b_a1Y1)
  = [(a_1627397516 =: a_a1Y0), (b_1627397517 =: b_a1Y1)]

How to avoid the name changing?
-- 
竹密岂妨流水过
山高哪阻野云飞
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] blog software in Haskell?

2011-11-02 Thread Ketil Malde
Simon Michael si...@joyful.com writes:

 Did someone mention hakyll already? 

Yes, Mihai, but thanks for the link.  I'll probably check it out when
I'm back from vacation.

Alistair: I'm already using gitit, but I think it's usage is a bit
different.  

Jason: I know about the various services, but I prefer to host it myself.

Thanks for all the suggestions, I'll let you know how it goes!

-k 
(Shaver of yaks)
-- 
If I haven't seen further, it is by standing in the footprints of giants

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


Re: [Haskell-cafe] Hackage feature request: E-mail author when a package breaks

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 01:08, Diego Souza dso...@bitforest.org wrote:
 The idea is simple: there are many different platforms that would be
 to expensive for one to support. So they ask the community for help,
 and then distribute the load amongst the perl community.

Duncan and co have been working towards something similar for a while
in the form of build reports. Cabal can submit a report of whether  a
build failed/succeeded and can opt to send a full log as well. The new
Hackage Server is capable of collecting these reports and taking
action based on them.

For example, you could setup Hackage server to detect patterns in
these build reports such as 80% of builds with GHC 7 are OK, but 100%
of builds with GHC 7.2 fail.

So far the infrastructure is there for creating and collecting
reports. I'm not sure whether reporting is turned on by *default* in
Cabal at the moment, which is something we might want to do. One thing
that I'm certain of is that there are no analyses that try to find
interesting patterns in the reports. If anyone is interested in the
issue that might be a good place to contribute and move things
forward.

Max

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


Re: [Haskell-cafe] Problem with TemplateHaskell

2011-11-02 Thread Max Bolingbroke
On 2 November 2011 07:42, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 How to avoid the name changing?

Maybe you should use nameBase rather than show?

Max

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


Re: [Haskell-cafe] Problem with TemplateHaskell

2011-11-02 Thread Magicloud Magiclouds
On Wed, Nov 2, 2011 at 4:08 PM, Max Bolingbroke
batterseapo...@hotmail.com wrote:
 On 2 November 2011 07:42, Magicloud Magiclouds
 magicloud.magiclo...@gmail.com wrote:
 How to avoid the name changing?

 Maybe you should use nameBase rather than show?

 Max


Yes, that is one of the problem.
And just now I found out that, the name changing occurred when using
quote, so at the very beginning, data T was not data T already.

-- 
竹密岂妨流水过
山高哪阻野云飞

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


[Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Hello,

I've got two very simple programs that draw a very simple picture using
cairo, doing a couple hundred thousand of cairo calls.
One program is in C++. The other is in Haskell and uses the cairo library
bindings.

The C++ program completes in a fraction of a second, the Haskell program
takes about 7-8 seconds to run. They produce exactly the same output.

What could be at fault here? Why are the cairo bindings working so slow? (I
suppose there isn't too much cairo-specific stuff here, perhaps it's a
general FFI question?)

#include cairo.h
int main() {
   cairo_surface_t *surface =
cairo_image_surface_create(CAIRO_FORMAT_ARGB32, 1024, 768);
   cairo_t *cr = cairo_create(surface);
   cairo_set_source_rgb(cr, 0, 255, 0);
   for(int x = 0; x  1024; x += 2) for(int y = 0; y  768; y += 2) {
   cairo_rectangle(cr, x, y, 1, 1);
   cairo_fill(cr);
   }
   cairo_surface_write_to_png(surface, picture.png);
   return 0;
}

module Main where

import qualified Graphics.Rendering.Cairo as C
import Control.Monad

main = C.withImageSurface C.FormatARGB32 1024 768 $ \s - do
 C.renderWith s $ do
   C.setSourceRGBA 0 255 0 255
   forM_ [0,2..1024] $ \x - do
 forM_ [0,2..768] $ \y - do
   C.rectangle x y 1 1
   C.fill
 C.surfaceWriteToPNG s picture.png

-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
I forgot to specify my environment.

Windows Server 2008 R2 x64, ghc 7.0.3.

However, I observed the same speed differences on a 64-bit ubuntu with ghc
6.12 - I profiled my application with cairo-trace, and cairo-perf-trace
drew in a fraction of a second the picture that my Haskell program spend a
dozen seconds drawing.

On Wed, Nov 2, 2011 at 1:17 PM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 Hello,

 I've got two very simple programs that draw a very simple picture using
 cairo, doing a couple hundred thousand of cairo calls.
 One program is in C++. The other is in Haskell and uses the cairo library
 bindings.

 The C++ program completes in a fraction of a second, the Haskell program
 takes about 7-8 seconds to run. They produce exactly the same output.

 What could be at fault here? Why are the cairo bindings working so slow?
 (I suppose there isn't too much cairo-specific stuff here, perhaps it's a
 general FFI question?)

 #include cairo.h
 int main() {
cairo_surface_t *surface =
 cairo_image_surface_create(CAIRO_FORMAT_ARGB32, 1024, 768);
cairo_t *cr = cairo_create(surface);
cairo_set_source_rgb(cr, 0, 255, 0);
for(int x = 0; x  1024; x += 2) for(int y = 0; y  768; y += 2) {
cairo_rectangle(cr, x, y, 1, 1);
cairo_fill(cr);
}
cairo_surface_write_to_png(surface, picture.png);
return 0;
 }

 module Main where

 import qualified Graphics.Rendering.Cairo as C
 import Control.Monad

 main = C.withImageSurface C.FormatARGB32 1024 768 $ \s - do
  C.renderWith s $ do
C.setSourceRGBA 0 255 0 255
forM_ [0,2..1024] $ \x - do
  forM_ [0,2..768] $ \y - do
C.rectangle x y 1 1
C.fill
  C.surfaceWriteToPNG s picture.png

 --
 Eugene Kirpichov
 Principal Engineer, Mirantis Inc. http://www.mirantis.com/
 Editor, http://fprog.ru/




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] HDBC SQLite error

2011-11-02 Thread Jurriën Stutterheim
I have just tried your suggestion (I explicitly committed right after opening a 
connection), but unfortunately it did not solve my problem. I've also tried 
compiling my app without threading, but it didn't seem to have any effect 
either.


On 1 Nov 2011, at 19:03, Alexander Danilov wrote:

 01.11.2011 20:30, Jurriën Stutterheim пишет:
 Hi all,
 
 
 I have recently switched one of my web applications to SQLite via HDBC. I 
 use it to store some user credentials and data. Initially it seemed to work 
 fine, until I tried logging in from two different browsers. That's when I 
 got the following error when trying to log in:
 
 SqlError {seState = , seNativeError = 5, seErrorMsg = step: database is 
 locked}
 
 My application only uses two functions (query and query', see [1]) directly, 
 and the authentication code[2] uses HDBC directly. I'm not sure why I'm 
 getting this error, because as far as I can see, I'm not keeping any 
 transactions open longer than I have to in the auth code. Does anyone have 
 an idea what might be wrong and how to fix it?
 
 
 Cheers,
 
 
 
 This is a problem of hdbc-sqlite package, author think, than it can't work 
 correctly without open transaction, so just commit after open database or 
 modify hdbc-sqlite like this:
 
 --- a/Database/HDBC/Sqlite3/Connection.hs
 +++ b/Database/HDBC/Sqlite3/Connection.hs
 @@ -75,7 +75,7 @@ genericConnect strAsCStrFunc fp =
 mkConn :: FilePath - Sqlite3 - IO Impl.Connection
 mkConn fp obj =
 do children - newMVar []
 -   begin_transaction obj children
 +--   begin_transaction obj children
ver - (sqlite3_libversion = peekCString)
return $ Impl.Connection {
 Impl.disconnect = fdisconnect obj children,
 
 
 ___
 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] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Claude Heiland-Allen

On 02/11/11 09:17, Eugene Kirpichov wrote:

Hello,

I've got two very simple programs that draw a very simple picture using
cairo, doing a couple hundred thousand of cairo calls.
One program is in C++. The other is in Haskell and uses the cairo library
bindings.

The C++ program completes in a fraction of a second, the Haskell program
takes about 7-8 seconds to run. They produce exactly the same output.

What could be at fault here? Why are the cairo bindings working so slow? (I
suppose there isn't too much cairo-specific stuff here, perhaps it's a
general FFI question?)


I filed a bug report about this some months ago, having noticed similar 
slowness:


gtk2hs ticket #1228 cairo performance is very bad
http://hackage.haskell.org/trac/gtk2hs/ticket/1228

My conclusion was that it isn't FFI being slow, but some other reason, 
possibly too much redirection / high level fanciness in the 
implementation of cairo bindings that the compiler can't see through to 
optimize aggressively, or possibly some Double / CDouble / realToFrac 
rubbishness.



Claude

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


Re: [Haskell-cafe] arr considered harmful

2011-11-02 Thread Ertugrul Soeylemez
Ryan Ingram ryani.s...@gmail.com wrote:

 I know it's a bit of an 'intentionally provocative' title, but with
 the recent discussions on Arrows I thought it timely to bring this up.

 Most of the conversion from arrow syntax into arrows uses 'arr' to
 move components around. However, arr is totally opaque to the arrow
 itself, and prevents describing some very useful objects as arrows.

I can totally understand your frustration, but on the other hand I have
to say that /not/ having 'arr' would break a lot of useful things at
least for me and probably for most programmers using AFRP.

One possible compromise is to move it into its own type class and also
offer specialized versions of it for plumbing in a yet simpler class.

class Arrow (~) = ArrowPair (~)
dup  :: a ~ (a, a)
swap :: (a, b) ~ (b, a)
...

class Arrow (~) = ArrowArr (~) where
arr :: (a - b) - (a ~ b)

This would enable some interesting optimization opportunities.  Perhaps
it also makes sense to turn ArrowArr into a subclass of ArrowPair.


Greets,
Ertugrul


-- 
nightmare = unsafePerformIO (getWrongWife = sex)
http://ertes.de/



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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Hi Claude,

I suspected that the issue could be about unsafe foreign imports - all
imports in the cairo bindings are safe.
I compiled myself a version of cairo bindings with the rectangle and
fill functions marked as unsafe.

Unfortunately that didn't help the case at all, even though the core
changed FFI calls from __pkg_ccall_GC to __pkg_ccall. The performance
stayed the same; the overhead is elsewhere.

On Wed, Nov 2, 2011 at 1:31 PM, Claude Heiland-Allen cla...@goto10.orgwrote:

 On 02/11/11 09:17, Eugene Kirpichov wrote:

 Hello,

 I've got two very simple programs that draw a very simple picture using
 cairo, doing a couple hundred thousand of cairo calls.
 One program is in C++. The other is in Haskell and uses the cairo library
 bindings.

 The C++ program completes in a fraction of a second, the Haskell program
 takes about 7-8 seconds to run. They produce exactly the same output.

 What could be at fault here? Why are the cairo bindings working so slow?
 (I
 suppose there isn't too much cairo-specific stuff here, perhaps it's a
 general FFI question?)


 I filed a bug report about this some months ago, having noticed similar
 slowness:

 gtk2hs ticket #1228 cairo performance is very bad
 http://hackage.haskell.org/**trac/gtk2hs/ticket/1228http://hackage.haskell.org/trac/gtk2hs/ticket/1228

 My conclusion was that it isn't FFI being slow, but some other reason,
 possibly too much redirection / high level fanciness in the implementation
 of cairo bindings that the compiler can't see through to optimize
 aggressively, or possibly some Double / CDouble / realToFrac rubbishness.


 Claude

 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Vincent Hanquez

On 11/02/2011 09:51 AM, Eugene Kirpichov wrote:

Hi Claude,

I suspected that the issue could be about unsafe foreign imports - all imports 
in the cairo bindings are safe.
I compiled myself a version of cairo bindings with the rectangle and fill 
functions marked as unsafe.


Unfortunately that didn't help the case at all, even though the core changed 
FFI calls from __pkg_ccall_GC to __pkg_ccall. The performance stayed the 
same; the overhead is elsewhere.



doing a ltrace, i think the reason is pretty obvious, there's a lot of GMP 
calls:

__gmpz_init(0x7f5043171730, 1, 0x7f5043171750, 0x7f5043171740, 0x7f50431d2508) = 
0x7f50431d2530
__gmpz_mul(0x7f5043171730, 0x7f5043171750, 0x7f5043171740, 0x7f50431d2538, 
0x7f50431d2508) = 1
__gmpz_init(0x7f5043171728, 1, 0x7f5043171748, 0x7f5043171738, 0x7f50431d2538) = 
0x7f50431d2568
__gmpz_mul(0x7f5043171728, 0x7f5043171748, 0x7f5043171738, 0x7f50431d2570, 
0x7f50431d2538) = 1

__gmpn_gcd_1(0x7f50431d2580, 1, 1, 1, 1) = 1
repeated thousand of time

before each call cairo calls.

just to make sure, the C version doesn't exhibit this behavior.

--
Vincent

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Oh. This is pretty crazy, I wonder what they're doing with GMP so much...

I modified the Haskell program to use cairo directly, even with safe calls,
and it now takes the same time as the C program.

{-# LANGUAGE ForeignFunctionInterface #-}
module Main where

import qualified Graphics.Rendering.Cairo as C
import Control.Monad
import Foreign
import Foreign.C.Types
import Foreign.C.String

foreign import ccall cairo.h cairo_image_surface_create
cairo_image_surface_create :: CInt - CInt - CInt - IO (Ptr ())
foreign import ccall cairo.h cairo_create cairo_create :: Ptr () - IO
(Ptr ())
foreign import ccall cairo.h cairo_set_source_rgb cairo_set_source_rgb ::
Ptr () - CDouble - CDouble - CDouble - IO ()
foreign import ccall cairo.h cairo_rectangle cairo_rectangle :: Ptr () -
CDouble - CDouble - CDouble - CDouble - IO ()
foreign import ccall cairo.h cairo_fill cairo_fill :: Ptr () - IO ()
foreign import ccall cairo.h cairo_surface_write_to_png
cairo_surface_write_to_png :: Ptr () - CString - IO ()

main = do
  s - cairo_image_surface_create 0 1024 768
  cr - cairo_create s
  cairo_set_source_rgb cr 0 255 0
  forM_ [0,2..1024] $ \x - do
forM_ [0,2..768] $ \y - do
  cairo_rectangle cr x y 1 1
  cairo_fill cr
  pic - newCString picture.png
  cairo_surface_write_to_png s pic

On Wed, Nov 2, 2011 at 1:58 PM, Vincent Hanquez t...@snarc.org wrote:

 On 11/02/2011 09:51 AM, Eugene Kirpichov wrote:

 Hi Claude,

 I suspected that the issue could be about unsafe foreign imports - all
 imports in the cairo bindings are safe.
 I compiled myself a version of cairo bindings with the rectangle and
 fill functions marked as unsafe.

 Unfortunately that didn't help the case at all, even though the core
 changed FFI calls from __pkg_ccall_GC to __pkg_ccall. The performance
 stayed the same; the overhead is elsewhere.

  doing a ltrace, i think the reason is pretty obvious, there's a lot of
 GMP calls:

 __gmpz_init(0x7f5043171730, 1, 0x7f5043171750, 0x7f5043171740,
 0x7f50431d2508) = 0x7f50431d2530
 __gmpz_mul(0x7f5043171730, 0x7f5043171750, 0x7f5043171740, 0x7f50431d2538,
 0x7f50431d2508) = 1
 __gmpz_init(0x7f5043171728, 1, 0x7f5043171748, 0x7f5043171738,
 0x7f50431d2538) = 0x7f50431d2568
 __gmpz_mul(0x7f5043171728, 0x7f5043171748, 0x7f5043171738, 0x7f50431d2570,
 0x7f50431d2538) = 1
 __gmpn_gcd_1(0x7f50431d2580, 1, 1, 1, 1) = 1
 repeated thousand of time

 before each call cairo calls.

 just to make sure, the C version doesn't exhibit this behavior.

 --
 Vincent


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
+gtk2hs-users

On Wed, Nov 2, 2011 at 2:10 PM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 Oh. This is pretty crazy, I wonder what they're doing with GMP so much...

 I modified the Haskell program to use cairo directly, even with safe
 calls, and it now takes the same time as the C program.

 {-# LANGUAGE ForeignFunctionInterface #-}
 module Main where

 import qualified Graphics.Rendering.Cairo as C
 import Control.Monad
 import Foreign
 import Foreign.C.Types
 import Foreign.C.String

 foreign import ccall cairo.h cairo_image_surface_create
 cairo_image_surface_create :: CInt - CInt - CInt - IO (Ptr ())
 foreign import ccall cairo.h cairo_create cairo_create :: Ptr () - IO
 (Ptr ())
 foreign import ccall cairo.h cairo_set_source_rgb cairo_set_source_rgb
 :: Ptr () - CDouble - CDouble - CDouble - IO ()
 foreign import ccall cairo.h cairo_rectangle cairo_rectangle :: Ptr ()
 - CDouble - CDouble - CDouble - CDouble - IO ()
 foreign import ccall cairo.h cairo_fill cairo_fill :: Ptr () - IO ()
 foreign import ccall cairo.h cairo_surface_write_to_png
 cairo_surface_write_to_png :: Ptr () - CString - IO ()

 main = do
   s - cairo_image_surface_create 0 1024 768
   cr - cairo_create s
   cairo_set_source_rgb cr 0 255 0
   forM_ [0,2..1024] $ \x - do
 forM_ [0,2..768] $ \y - do
   cairo_rectangle cr x y 1 1
   cairo_fill cr
   pic - newCString picture.png
   cairo_surface_write_to_png s pic

 On Wed, Nov 2, 2011 at 1:58 PM, Vincent Hanquez t...@snarc.org wrote:

 On 11/02/2011 09:51 AM, Eugene Kirpichov wrote:

 Hi Claude,

 I suspected that the issue could be about unsafe foreign imports - all
 imports in the cairo bindings are safe.
 I compiled myself a version of cairo bindings with the rectangle and
 fill functions marked as unsafe.

 Unfortunately that didn't help the case at all, even though the core
 changed FFI calls from __pkg_ccall_GC to __pkg_ccall. The performance
 stayed the same; the overhead is elsewhere.

  doing a ltrace, i think the reason is pretty obvious, there's a lot of
 GMP calls:

 __gmpz_init(0x7f5043171730, 1, 0x7f5043171750, 0x7f5043171740,
 0x7f50431d2508) = 0x7f50431d2530
 __gmpz_mul(0x7f5043171730, 0x7f5043171750, 0x7f5043171740,
 0x7f50431d2538, 0x7f50431d2508) = 1
 __gmpz_init(0x7f5043171728, 1, 0x7f5043171748, 0x7f5043171738,
 0x7f50431d2538) = 0x7f50431d2568
 __gmpz_mul(0x7f5043171728, 0x7f5043171748, 0x7f5043171738,
 0x7f50431d2570, 0x7f50431d2538) = 1
 __gmpn_gcd_1(0x7f50431d2580, 1, 1, 1, 1) = 1
 repeated thousand of time

 before each call cairo calls.

 just to make sure, the C version doesn't exhibit this behavior.

 --
 Vincent


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




 --
 Eugene Kirpichov
 Principal Engineer, Mirantis Inc. http://www.mirantis.com/
 Editor, http://fprog.ru/




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Vincent Hanquez

On 11/02/2011 10:10 AM, Eugene Kirpichov wrote:

Oh. This is pretty crazy, I wonder what they're doing with GMP so much...

I modified the Haskell program to use cairo directly, even with safe calls, 
and it now takes the same time as the C program.



yep, i ended up doing the exact same thing for testing,

foreign import ccall cairo_rectangle
  my_rectangle :: CI.Cairo - CDouble - CDouble - CDouble - CDouble - IO ()

and just replacing the rectangle call make almost all the difference for me 
(almost as fast as C)


--
Vincent

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Any idea how to debug why all the GMP calls?
I'm looking at even the auto-generated source for cairo bindings, but I
don't see anything at all that could lead to *thousands* of them.

On Wed, Nov 2, 2011 at 2:14 PM, Vincent Hanquez t...@snarc.org wrote:

 On 11/02/2011 10:10 AM, Eugene Kirpichov wrote:

 Oh. This is pretty crazy, I wonder what they're doing with GMP so much...

 I modified the Haskell program to use cairo directly, even with safe
 calls, and it now takes the same time as the C program.

  yep, i ended up doing the exact same thing for testing,

 foreign import ccall cairo_rectangle
  my_rectangle :: CI.Cairo - CDouble - CDouble - CDouble - CDouble -
 IO ()

 and just replacing the rectangle call make almost all the difference for
 me (almost as fast as C)

 --
 Vincent




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Felipe Almeida Lessa
On Wed, Nov 2, 2011 at 8:15 AM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Any idea how to debug why all the GMP calls?
 I'm looking at even the auto-generated source for cairo bindings, but I
 don't see anything at all that could lead to *thousands* of them.

Found them.  Look at the Types module and you'll see

  cFloatConv :: (RealFloat a, RealFloat b) = a - b
  cFloatConv  = realToFrac

This function (or its cousins peekFloatConv, withFloatConv...) are
used *everywhere*.

Looking at this module with ghc-core we see that GHC compiled a
generic version of cFloatConv:

Graphics.Rendering.Cairo.Types.$wcFloatConv
  :: forall a_a3TN b_a3TO.
 (RealFloat a_a3TN, RealFrac b_a3TO) =
 a_a3TN - b_a3TO
[GblId,
 Arity=3,

 Unf=Unf{Src=vanilla, TopLvl=True, Arity=3, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=IF_ARGS [3 3 0] 12 0}]
Graphics.Rendering.Cairo.Types.$wcFloatConv =
  \ (@ a_a3TN)
(@ b_a3TO)
(w_s5zg :: RealFloat a_a3TN)
(ww_s5zj :: RealFrac b_a3TO)
(w1_s5zA :: a_a3TN) -
fromRational
  @ b_a3TO
  ($p2RealFrac @ b_a3TO ww_s5zj)
  (toRational
 @ a_a3TN
 ($p1RealFrac
@ a_a3TN ($p1RealFloat @ a_a3TN w_s5zg))
 w1_s5zA)

Note that this is basically cFloatConv = fromRational . toRational.

*However*, GHC also compiled a Double - Double specialization:

Graphics.Rendering.Cairo.Types.cFloatConv1
  :: Double - Double
[GblId,
 Arity=1,

 Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
 Tmpl= \ (eta_B1 [Occ=Once!] :: Double) -
 case eta_B1 of _ { D# ww_a5v3 [Occ=Once] -
 case $w$ctoRational ww_a5v3
 of _ { (# ww2_a5v8 [Occ=Once], ww3_a5v9 [Occ=Once] #) -
 $wfromRat ww2_a5v8 ww3_a5v9
 }
 }}]
Graphics.Rendering.Cairo.Types.cFloatConv1 =
  \ (eta_B1 :: Double) -
case eta_B1 of _ { D# ww_a5v3 -
case $w$ctoRational ww_a5v3
of _ { (# ww2_a5v8, ww3_a5v9 #) -
$wfromRat ww2_a5v8 ww3_a5v9
}
}

...which is also equivalent to fromRational . toRational however with
the type class inlined!  Oh, god...

Cheers,

-- 
Felipe.

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


[Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Felipe Almeida Lessa
+gtk2hs-devel

On Wed, Nov 2, 2011 at 8:15 AM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Any idea how to debug why all the GMP calls?
 I'm looking at even the auto-generated source for cairo bindings, but I
 don't see anything at all that could lead to *thousands* of them.

Found them.  Look at the Types module and you'll see

 cFloatConv :: (RealFloat a, RealFloat b) = a - b
 cFloatConv  = realToFrac

This function (or its cousins peekFloatConv, withFloatConv...) are
used *everywhere*.

Looking at this module with ghc-core we see that GHC compiled a
generic version of cFloatConv:

Graphics.Rendering.Cairo.Types.$wcFloatConv
 :: forall a_a3TN b_a3TO.
    (RealFloat a_a3TN, RealFrac b_a3TO) =
    a_a3TN - b_a3TO
[GblId,
 Arity=3,

 Unf=Unf{Src=vanilla, TopLvl=True, Arity=3, Value=True,
        ConLike=True, Cheap=True, Expandable=True,
        Guidance=IF_ARGS [3 3 0] 12 0}]
Graphics.Rendering.Cairo.Types.$wcFloatConv =
 \ (@ a_a3TN)
   (@ b_a3TO)
   (w_s5zg :: RealFloat a_a3TN)
   (ww_s5zj :: RealFrac b_a3TO)
   (w1_s5zA :: a_a3TN) -
   fromRational
     @ b_a3TO
     ($p2RealFrac @ b_a3TO ww_s5zj)
     (toRational
        @ a_a3TN
        ($p1RealFrac
           @ a_a3TN ($p1RealFloat @ a_a3TN w_s5zg))
        w1_s5zA)

Note that this is basically cFloatConv = fromRational . toRational.

*However*, GHC also compiled a Double - Double specialization:

Graphics.Rendering.Cairo.Types.cFloatConv1
 :: Double - Double
[GblId,
 Arity=1,

 Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
        ConLike=True, Cheap=True, Expandable=True,
        Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
        Tmpl= \ (eta_B1 [Occ=Once!] :: Double) -
                case eta_B1 of _ { D# ww_a5v3 [Occ=Once] -
                case $w$ctoRational ww_a5v3
                of _ { (# ww2_a5v8 [Occ=Once], ww3_a5v9 [Occ=Once] #) -
                $wfromRat ww2_a5v8 ww3_a5v9
                }
                }}]
Graphics.Rendering.Cairo.Types.cFloatConv1 =
 \ (eta_B1 :: Double) -
   case eta_B1 of _ { D# ww_a5v3 -
   case $w$ctoRational ww_a5v3
   of _ { (# ww2_a5v8, ww3_a5v9 #) -
   $wfromRat ww2_a5v8 ww3_a5v9
   }
   }

...which is also equivalent to fromRational . toRational however with
the type class inlined!  Oh, god...

Cheers,

--
Felipe.

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


Re: [Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Yay!!!

I made a small change in Types.chs and got my original cairo-binding-based
program to be just as blazing fast. The only problem I have with this is
that I used multiparameter type classes.

Dear gtk2hs team! Is it possible to incorporate my changes? I'm pretty sure
people will be happy by an order-of-magnitude speedup. Probably the stuff
could be wrapped in #define's for those who aren't using GHC and can't use
multiparameter type classes?

I am pretty sure I could have done the same with rewrite rules, but I tried
for a while and to no avail.

FAILED SOLUTION: rewrite rules
cFloatConv :: (RealFloat a, RealFloat b) = a - b
cFloatConv  = realToFrac
{-# NOINLINE cFloatConv #-}
{-# RULES cFloatConv/float2Double cFloatConv = float2Double #-}
{-# RULES cFloatConv/double2Float cFloatConv = double2Float #-}
{-# RULES cFloatConv/self cFloatConv = id   #-}

For some reason, the rules don't fire. Anyone got an idea why?

SUCCEEDED SOLUTION: multiparameter type classes

I rewrote cFloatConv like this:

import GHC.Float
class (RealFloat a, RealFloat b) = CFloatConv a b where
  cFloatConv :: a - b
  cFloatConv = realToFrac

instance CFloatConv Double Double where cFloatConv = id
instance CFloatConv Double CDouble
instance CFloatConv CDouble Double
instance CFloatConv Float Float where cFloatConv = id
instance CFloatConv Float Double where cFloatConv = float2Double
instance CFloatConv Double Float where cFloatConv = double2Float

and replaced a couple of constraints in functions below by usage of
CFloatConv.


On Wed, Nov 2, 2011 at 2:25 PM, Felipe Almeida Lessa felipe.le...@gmail.com
 wrote:

 +gtk2hs-devel

 On Wed, Nov 2, 2011 at 8:15 AM, Eugene Kirpichov ekirpic...@gmail.com
 wrote:
  Any idea how to debug why all the GMP calls?
  I'm looking at even the auto-generated source for cairo bindings, but I
  don't see anything at all that could lead to *thousands* of them.

 Found them.  Look at the Types module and you'll see

  cFloatConv :: (RealFloat a, RealFloat b) = a - b
  cFloatConv  = realToFrac

 This function (or its cousins peekFloatConv, withFloatConv...) are
 used *everywhere*.

 Looking at this module with ghc-core we see that GHC compiled a
 generic version of cFloatConv:

 Graphics.Rendering.Cairo.Types.$wcFloatConv
  :: forall a_a3TN b_a3TO.
 (RealFloat a_a3TN, RealFrac b_a3TO) =
 a_a3TN - b_a3TO
 [GblId,
  Arity=3,

  Unf=Unf{Src=vanilla, TopLvl=True, Arity=3, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=IF_ARGS [3 3 0] 12 0}]
 Graphics.Rendering.Cairo.Types.$wcFloatConv =
  \ (@ a_a3TN)
(@ b_a3TO)
(w_s5zg :: RealFloat a_a3TN)
(ww_s5zj :: RealFrac b_a3TO)
(w1_s5zA :: a_a3TN) -
fromRational
  @ b_a3TO
  ($p2RealFrac @ b_a3TO ww_s5zj)
  (toRational
 @ a_a3TN
 ($p1RealFrac
@ a_a3TN ($p1RealFloat @ a_a3TN w_s5zg))
 w1_s5zA)

 Note that this is basically cFloatConv = fromRational . toRational.

 *However*, GHC also compiled a Double - Double specialization:

 Graphics.Rendering.Cairo.Types.cFloatConv1
  :: Double - Double
 [GblId,
  Arity=1,

  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
 Tmpl= \ (eta_B1 [Occ=Once!] :: Double) -
 case eta_B1 of _ { D# ww_a5v3 [Occ=Once] -
 case $w$ctoRational ww_a5v3
 of _ { (# ww2_a5v8 [Occ=Once], ww3_a5v9 [Occ=Once] #) -
 $wfromRat ww2_a5v8 ww3_a5v9
 }
 }}]
 Graphics.Rendering.Cairo.Types.cFloatConv1 =
  \ (eta_B1 :: Double) -
case eta_B1 of _ { D# ww_a5v3 -
case $w$ctoRational ww_a5v3
of _ { (# ww2_a5v8, ww3_a5v9 #) -
$wfromRat ww2_a5v8 ww3_a5v9
}
}

 ...which is also equivalent to fromRational . toRational however with
 the type class inlined!  Oh, god...

 Cheers,

 --
 Felipe.

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




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Sorry for re-sending, my previous attempt got ignored by gtk2hs-devel
mailing list as I wasn't subscribed. Now I am.

On Wed, Nov 2, 2011 at 3:14 PM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 Yay!!!

 I made a small change in Types.chs and got my original cairo-binding-based
 program to be just as blazing fast. The only problem I have with this is
 that I used multiparameter type classes.

 Dear gtk2hs team! Is it possible to incorporate my changes? I'm pretty
 sure people will be happy by an order-of-magnitude speedup. Probably the
 stuff could be wrapped in #define's for those who aren't using GHC and
 can't use multiparameter type classes?

 I am pretty sure I could have done the same with rewrite rules, but I
 tried for a while and to no avail.

 FAILED SOLUTION: rewrite rules
 cFloatConv :: (RealFloat a, RealFloat b) = a - b
 cFloatConv  = realToFrac
 {-# NOINLINE cFloatConv #-}
 {-# RULES cFloatConv/float2Double cFloatConv = float2Double #-}
 {-# RULES cFloatConv/double2Float cFloatConv = double2Float #-}
 {-# RULES cFloatConv/self cFloatConv = id   #-}

 For some reason, the rules don't fire. Anyone got an idea why?

 SUCCEEDED SOLUTION: multiparameter type classes

 I rewrote cFloatConv like this:

 import GHC.Float
 class (RealFloat a, RealFloat b) = CFloatConv a b where
   cFloatConv :: a - b
   cFloatConv = realToFrac

 instance CFloatConv Double Double where cFloatConv = id
 instance CFloatConv Double CDouble
 instance CFloatConv CDouble Double
 instance CFloatConv Float Float where cFloatConv = id
 instance CFloatConv Float Double where cFloatConv = float2Double
 instance CFloatConv Double Float where cFloatConv = double2Float

 and replaced a couple of constraints in functions below by usage of
 CFloatConv.


 On Wed, Nov 2, 2011 at 2:25 PM, Felipe Almeida Lessa 
 felipe.le...@gmail.com wrote:

 +gtk2hs-devel

 On Wed, Nov 2, 2011 at 8:15 AM, Eugene Kirpichov ekirpic...@gmail.com
 wrote:
  Any idea how to debug why all the GMP calls?
  I'm looking at even the auto-generated source for cairo bindings, but I
  don't see anything at all that could lead to *thousands* of them.

 Found them.  Look at the Types module and you'll see

  cFloatConv :: (RealFloat a, RealFloat b) = a - b
  cFloatConv  = realToFrac

 This function (or its cousins peekFloatConv, withFloatConv...) are
 used *everywhere*.

 Looking at this module with ghc-core we see that GHC compiled a
 generic version of cFloatConv:

 Graphics.Rendering.Cairo.Types.$wcFloatConv
  :: forall a_a3TN b_a3TO.
 (RealFloat a_a3TN, RealFrac b_a3TO) =
 a_a3TN - b_a3TO
 [GblId,
  Arity=3,

  Unf=Unf{Src=vanilla, TopLvl=True, Arity=3, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=IF_ARGS [3 3 0] 12 0}]
 Graphics.Rendering.Cairo.Types.$wcFloatConv =
  \ (@ a_a3TN)
(@ b_a3TO)
(w_s5zg :: RealFloat a_a3TN)
(ww_s5zj :: RealFrac b_a3TO)
(w1_s5zA :: a_a3TN) -
fromRational
  @ b_a3TO
  ($p2RealFrac @ b_a3TO ww_s5zj)
  (toRational
 @ a_a3TN
 ($p1RealFrac
@ a_a3TN ($p1RealFloat @ a_a3TN w_s5zg))
 w1_s5zA)

 Note that this is basically cFloatConv = fromRational . toRational.

 *However*, GHC also compiled a Double - Double specialization:

 Graphics.Rendering.Cairo.Types.cFloatConv1
  :: Double - Double
 [GblId,
  Arity=1,

  Unf=Unf{Src=InlineStable, TopLvl=True, Arity=1, Value=True,
 ConLike=True, Cheap=True, Expandable=True,
 Guidance=ALWAYS_IF(unsat_ok=True,boring_ok=False)
 Tmpl= \ (eta_B1 [Occ=Once!] :: Double) -
 case eta_B1 of _ { D# ww_a5v3 [Occ=Once] -
 case $w$ctoRational ww_a5v3
 of _ { (# ww2_a5v8 [Occ=Once], ww3_a5v9 [Occ=Once] #) -
 $wfromRat ww2_a5v8 ww3_a5v9
 }
 }}]
 Graphics.Rendering.Cairo.Types.cFloatConv1 =
  \ (eta_B1 :: Double) -
case eta_B1 of _ { D# ww_a5v3 -
case $w$ctoRational ww_a5v3
of _ { (# ww2_a5v8, ww3_a5v9 #) -
$wfromRat ww2_a5v8 ww3_a5v9
}
}

 ...which is also equivalent to fromRational . toRational however with
 the type class inlined!  Oh, god...

 Cheers,

 --
 Felipe.

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




 --
 Eugene Kirpichov
 Principal Engineer, Mirantis Inc. http://www.mirantis.com/
 Editor, http://fprog.ru/




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Felipe Almeida Lessa
On Wed, Nov 2, 2011 at 9:14 AM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Yay!!!
 I made a small change in Types.chs and got my original cairo-binding-based
 program to be just as blazing fast. The only problem I have with this is
 that I used multiparameter type classes.

Nice!  Looking forward to it being included in cairo codebase and
released on Hackage.  =D

Cheers,

-- 
Felipe.

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


Re: [Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Ivan Perez
Thanks a lot for this. I've been developing a Graphic Adventure IDE in
haskell that I'm about
to release. It uses Cairo to draw game-state diagrams and this will
sure solve my speed issues.

2011/11/2 Felipe Almeida Lessa felipe.le...@gmail.com:
 On Wed, Nov 2, 2011 at 9:14 AM, Eugene Kirpichov ekirpic...@gmail.com wrote:
 Yay!!!
 I made a small change in Types.chs and got my original cairo-binding-based
 program to be just as blazing fast. The only problem I have with this is
 that I used multiparameter type classes.

 Nice!  Looking forward to it being included in cairo codebase and
 released on Hackage.  =D

 Cheers,

 --
 Felipe.

 ___
 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] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Daniel Fischer
On Wednesday 02 November 2011, 10:19:08, Eugene Kirpichov wrote:
 I forgot to specify my environment.
 
 Windows Server 2008 R2 x64, ghc 7.0.3.
 
 However, I observed the same speed differences on a 64-bit ubuntu with
 ghc 6.12 - I profiled my application with cairo-trace, and
 cairo-perf-trace drew in a fraction of a second the picture that my
 Haskell program spend a dozen seconds drawing.

Just FYI,

$ uname -a
Linux linux-v7dw.site 2.6.37.6-0.7-desktop #1 SMP PREEMPT 2011-07-21 
02:17:24 +0200 x86_64 x86_64 x86_64 GNU/Linux

$ g++ -O3 -o csurf surf.cc -I/usr/include/cairo -cairo
$ time ./csurf 

real0m0.126s
user0m0.119s
sys 0m0.006s
$ ghc-7.0.4 -O2 hssurf.hs 
[1 of 1] Compiling Main ( hssurf.hs, hssurf.o )
Linking hssurf ...
$ time ./hssurf 

real0m5.857s
user0m5.840s
sys 0m0.011s
$ ghc -O2 hssurf.hs -o hssurf2
[1 of 1] Compiling Main ( hssurf.hs, hssurf.o )
Linking hssurf2 ...
$ time ./hssurf2 

real0m0.355s
user0m0.350s
sys 0m0.005s

(fromRational . toRational) is still slow, but nowhere as slow as it used 
to be.

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Jean-Marie Gaillourdet
Hi Eugene,

did you try using the SPECIALIZE pragma? It is part of the Haskell 98 and 
Haskell 2010 specifications. 

On 02.11.2011, at 12:14, Eugene Kirpichov wrote:

 Yay!!!
 
 I made a small change in Types.chs and got my original cairo-binding-based 
 program to be just as blazing fast. The only problem I have with this is that 
 I used multiparameter type classes.
 
 Dear gtk2hs team! Is it possible to incorporate my changes? I'm pretty sure 
 people will be happy by an order-of-magnitude speedup. Probably the stuff 
 could be wrapped in #define's for those who aren't using GHC and can't use 
 multiparameter type classes?
 
 I am pretty sure I could have done the same with rewrite rules, but I tried 
 for a while and to no avail.
 
 FAILED SOLUTION: rewrite rules
 cFloatConv :: (RealFloat a, RealFloat b) = a - b
 cFloatConv  = realToFrac
 {-# NOINLINE cFloatConv #-}
 {-# RULES cFloatConv/float2Double cFloatConv = float2Double #-}
 {-# RULES cFloatConv/double2Float cFloatConv = double2Float #-}
 {-# RULES cFloatConv/self cFloatConv = id   #-}


See [1] in GHC User Guide.

cFloatConv :: (RealFloat a, RealFloat b) = a - b
cFloatConv = realToFrac -- or try fromRational . toRational

{-# SPECIALIZE cFloatConv :: Float - Double #-}
{-# SPECIALIZE cFloatConv :: Double - Float #-}

I did not try to compile or even benchmark this code. But I think it might help 
in your case.

Cheers,
  Jean

[1]: 
http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html#specialize-pragma
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with TemplateHaskell

2011-11-02 Thread Magicloud Magiclouds
On Wed, Nov 2, 2011 at 4:50 PM, Magicloud Magiclouds
magicloud.magiclo...@gmail.com wrote:
 On Wed, Nov 2, 2011 at 4:08 PM, Max Bolingbroke
 batterseapo...@hotmail.com wrote:
 On 2 November 2011 07:42, Magicloud Magiclouds
 magicloud.magiclo...@gmail.com wrote:
 How to avoid the name changing?

 Maybe you should use nameBase rather than show?

 Max


 Yes, that is one of the problem.
 And just now I found out that, the name changing occurred when using
 quote, so at the very beginning, data T was not data T already.

 --
 竹密岂妨流水过
 山高哪阻野云飞


I kind of fingering out where am I wrong.
I should declare the data type in quote. I should make it outside the
template and using type name and reify to get it in bson.

-- 
竹密岂妨流水过
山高哪阻野云飞

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Hi,

No, I didn't, as I read in the GHC docs that it is deprecated in favor of
the RULES pragma (I wanted to replace specifically with floatToDouble and
doubleToFloat).

On Wed, Nov 2, 2011 at 5:24 PM, Jean-Marie Gaillourdet
j...@gaillourdet.netwrote:

 Hi Eugene,

 did you try using the SPECIALIZE pragma? It is part of the Haskell 98 and
 Haskell 2010 specifications.

 On 02.11.2011, at 12:14, Eugene Kirpichov wrote:

  Yay!!!
 
  I made a small change in Types.chs and got my original
 cairo-binding-based program to be just as blazing fast. The only problem I
 have with this is that I used multiparameter type classes.
 
  Dear gtk2hs team! Is it possible to incorporate my changes? I'm pretty
 sure people will be happy by an order-of-magnitude speedup. Probably the
 stuff could be wrapped in #define's for those who aren't using GHC and
 can't use multiparameter type classes?
 
  I am pretty sure I could have done the same with rewrite rules, but I
 tried for a while and to no avail.
 
  FAILED SOLUTION: rewrite rules
  cFloatConv :: (RealFloat a, RealFloat b) = a - b
  cFloatConv  = realToFrac
  {-# NOINLINE cFloatConv #-}
  {-# RULES cFloatConv/float2Double cFloatConv = float2Double #-}
  {-# RULES cFloatConv/double2Float cFloatConv = double2Float #-}
  {-# RULES cFloatConv/self cFloatConv = id   #-}


 See [1] in GHC User Guide.

 cFloatConv :: (RealFloat a, RealFloat b) = a - b
 cFloatConv = realToFrac -- or try fromRational . toRational

 {-# SPECIALIZE cFloatConv :: Float - Double #-}
 {-# SPECIALIZE cFloatConv :: Double - Float #-}

 I did not try to compile or even benchmark this code. But I think it might
 help in your case.

 Cheers,
  Jean

 [1]:
 http://www.haskell.org/ghc/docs/latest/html/users_guide/pragmas.html#specialize-pragma




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Felipe Almeida Lessa
On Wed, Nov 2, 2011 at 11:24 AM, Jean-Marie Gaillourdet
j...@gaillourdet.net wrote:
 Hi Eugene,

 did you try using the SPECIALIZE pragma? It is part of the Haskell 98 and 
 Haskell 2010 specifications.

I don't think it's going to make any difference, as the core already
have an specialized poor version.  See my first e-mail.

-- 
Felipe.

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


[Haskell-cafe] Haskell hackers send an idea to the off the beaten track workshop at POPL

2011-11-02 Thread David Walker
Haskell is an amazing language for implementing Domain-Specific Languages.  If 
you have an idea about a new domain-specific language you'd like to implement, 
a new problem that needs to be solved or any other new and unusual idea 
concerning programming language research, submit it to OBT: Off the Beaten 
Track:  Under-represented Problems for Programming Language Researchers.  This 
is a new, informal, lively workshop associated with POPL in Philadelphia, 
Saturday January 28.  It is easy to submit something, just write up a 1-page or 
2-page PDF on your idea and submit it here:  

http://www.cs.princeton.edu/~dpw/obt/

We are eager to have lots of 5-minute talks as well as longer talks interleaved 
with discussion.  Don't be shy:  submit your off-the-beaten-track problems and 
ideas.  The deadline is Nov 14.  See the web site or below for more info

Thanks,

David Walker
Program Chair

--
Dates:
--

Paper submissionMonday November 14, 2011 (11:59PM US EST)
Author notification Friday December 9, 2011
Conference  Saturday January 28, 2012

--
Scope:
--

Programming language researchers have the principles, tools, algorithms and 
abstractions to solve all kinds of problems, in all areas of computer science. 
However, identifying and evaluating new problems, particularly those that lie 
outside the typical core PL problems we all know and love, can be a significant 
challenge. Hence, the goal of this workshop is to identify and discuss problems 
that do not often show up in our top conferences, but where programming 
language researchers can make a substantial impact. The hope is that by holding 
such a forum and associating it directly with a top conference like POPL, we 
can slowly start to increase the diversity of problems that are studied by PL 
researchers and that by doing so we will increase the impact that our community 
has on the world.

While many workshops associated with POPL have become more like 
mini-conferences themselves, this is not the goal for Off the Beaten Track. The 
workshop will be informal and structured to encourage discussion. It will also 
be centered around problems and problem areas as opposed to fully-formed 
solutions.

A good submission is one that outlines a new problem or an interesting, 
underrepresented problem domain. Good submissions may also remind the PL 
community of problems that were once in vogue but have not recently been seen 
in top PL conferences. Good submissions do not need to propose complete or even 
partial solutions, though there should be some reason to believe that 
programming languages researchers have the tools necessary to search for 
solutions in the area at hand. Submissions that seem likely to stimulate 
discussion about the direction of programming language research are encouraged. 
Possible topics include any of the following.

Biology, chemistry, or other natural sciences
Art, music, graphics and animation
Networking, cloud computing, systems programming
Linguistics
Economics, law, politics or other social sciences
Web programming, social computing
Algorithms and complexity
Mathematics, statistics
Machine learning or artificial intelligence
Education
Unusual compilers; underrepresented programming languages
Surprise us

We certainly hope to see submissions on topics not mentioned above. The goal of 
the workshop is to be inclusive, not exclusive. Submissions are evaluated on 
the basis of creativity, novelty, clarity, possible impact and potential for 
stimulating discussion.

--
Submission Details
--

See the web site:  http://www.cs.princeton.edu/~dpw/obt/

-
Program Committee
-
Program Chair:

David Walker (Princeton University)

Program Committee:

Thomas Ball (Microsoft Research, Redmond)
Trevor Jim (ATT)
Julia Lawall (DIKU)
Boon Thau Loo (University of Pennsylvania)
Geoff Mainland (Microsoft Research, Cambridge)
Chung-chieh Shan (Cornell)

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Heh.

Guess what!
A simple {-# INLINE cFloatConv #-} helped to the same extent!

Axel, I think this change should be pretty easy to incorporate, and it
probably makes sense to inline all other functions in Types.chs too.

Would you like me to send the trivial darcs patch or the gtk2hs team
will take care of this?

On Wed, Nov 2, 2011 at 7:29 PM, Felipe Almeida Lessa
felipe.le...@gmail.com wrote:
 On Wed, Nov 2, 2011 at 11:24 AM, Jean-Marie Gaillourdet
 j...@gaillourdet.net wrote:
 Hi Eugene,

 did you try using the SPECIALIZE pragma? It is part of the Haskell 98 and 
 Haskell 2010 specifications.

 I don't think it's going to make any difference, as the core already
 have an specialized poor version.  See my first e-mail.

 --
 Felipe.




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/

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


[Haskell-cafe] Tell cabal-install to generate only shared libraries

2011-11-02 Thread Yves Parès
Hello,

When I tell cabal-install to build shared libraries (with Shared: True in
.cabal/config), it doubles the libraries installation time since it
compiles them twice, since it seems that is what GHC's flag -shared does.
Is there a way to generate only the .so and not the the .a libs?

Furthermore, I have the impression that the executables compiled by
cabal-install are always linked statically... Can I tell cabal-install to
activate the GHC's flag -dynamic for executables?

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


[Haskell-cafe] [ANNOUNCE] hierarchical-clustering-diagrams 0.1: diagrams of dendrograms

2011-11-02 Thread Felipe Almeida Lessa
Hello!

I'm pleased to announce the very first version of
hierarchical-clustering-diagrams [1].  This library builds upon Brent
Yorgey's great diagrams library to draw diagrams of dendrograms.  You
can see an example diagram at [2].

This library has already been tested with a Real World Big Data
dendrogram and has a pretty nice performance.  It generates a 20,000 x
5,000 px PNG in less than 15s on a 2 years-old Core 2 laptop.

Note that while this library depends on the hierarchical-clustering
library [3], nothing stops you from using any other method of creating
your dendrogram.  You only need to convert your dendrogram to the data
type provided by hierarchical-clustering, which should be
straightforward.  However, I'd love to hear if someone finds both
libraries useful =).

Cheers, =D

[1] http://hackage.haskell.org/package/hierarchical-clustering-diagrams
[2] 
https://patch-tag.com/r/felipe/hierarchical-clustering-diagrams/snapshot/current/content/pretty/example.png
[3] http://hackage.haskell.org/package/hierarchical-clustering-diagrams

-- 
Felipe.

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


[Haskell-cafe] The type class wilderness + Separating instances and implementations into separate packages

2011-11-02 Thread Ryan Newton
What is the right interface for a queue?  What is the right interface for a
random number generator?

I don't know, but in both cases you will find many packages on hackage
offering different takes on the matter.  In fact, there is a wilderness of
alternative interfaces.  We've had various discussions on this list about
the number of alternative packages.

I'm fine with lots of packages, but I think it would be great if not every
package introduced a new interface as well as a new implementation.  If we
could agree as a community on common interfaces to use for some basics,
that would probably go a long way towards taming the type class wilderness.
 People have mentioned this problem before with respect to Collections
generally.

One basic part of reaching such a goal is separating interface from
implementation.  I ran into the following problems just  in the last 24
hours.  In both cases I wanted to use a type class, but didn't want to
depend on the whole package it lived in:

   - I wanted to use the Benchmarkable class in Criterion in my package.
(Criterion deserving to be a standard package.)  But I can't get that
   typeclass without depending on the whole Criterion package, which has
   several dependencies.  And in fact on the machine I was on at the time some
   of those dependencies were broken, so I decided not to use Benchmarkable.
   - I wanted to use, or at least support, an existing class for Queues.  I
   found the following:

http://hackage.haskell.org/packages/archive/queuelike/1.0.9/doc/html/Data-MQueue-Class.html

I have no idea who uses this package.  But because this package (like most
packages) includes the implementation along with the interface it
introduces additional dependency liabilities.  In this case it failed to
build on GHC 7.2 so I quickly gave up on supporting that TypeClass.

How can we enumerate packages that at least purport to provide standard
interfaces that you should both use and pick up to implement?  On a Wiki
page?

  -Ryan

P.S. I'm working on mutable concurrent Deques right now and am trying to
follow my own prescription above by creating an abstract interface in a
separate package.  See below if you would like to offer feedback on that
interface.

--

My ultimate goal is an abstract-deque parameterizable interface that
abstracts over bounded/unbounded, concurrent/non-concurrent, single, 1.5,
and double-ended queues, which would include both, say, Michael  Scott
linked queues and the Chase-Lev work-stealing deques.  An aggregated queue
package could use type families to dispatch to the best available queue
implementation for a given configuration.

I've got a couple drafts of how this might work.  They're in different
branches here:


https://github.com/rrnewton/haskell-lockfree-queue/blob/master/AbstractDeque/Data/Concurrent/Deque/Class.hs

https://github.com/rrnewton/haskell-lockfree-queue/blob/one-type-class/AbstractDeque/Data/Concurrent/Deque/Class.hs

One of them uses an associated data type family, the other an unassociated
one.  The type family has a bunch (six) phantom type parameters, and
the unassociated one allows hiding those parameters at the expense of
introducing more type classes.

MegaQueue.hs will be used to aggregate together different queue
implementations.  The end result is that someone can create a new queue by
setting all the switches on the type, as follows:

 test = do
 q :: Deque NT T SingleEnd SingleEnd Bound Safe Int - newQ
 pushL q 33
 x - tryPopR q
 print x
 return q

With those settings, requiring only single-ended rather than double-ended
queues, the above code can use the LinkedQueue (Michael and
Scott) implementation included in that repo.
   That little test, by the way, segfaults for me on Mac OS under GHC 7.2.1
even WITHOUT using casMutVar# (It's using Data.CAS.Fake presently.)  I'll
file a bug report after I sanity check it some more.

Disregarding that... the big problem in this case is the* inability to
create overlapping type family instances.  *

In this case what we dearly WANT to do is specialize some subset of the
64-mode configuration space and then have a fallback.  You can take a
look at my struggling in MegaDeque.  Both of my approaches require
specifying explicitly the modes that you don't cover.

Worse, we may want to specialize on element type as well.  For example, for
simple scalar types (or even Storable types) it may be desirable to use
something foreign, like TBB queues.  But in that case, there's no way to
enumerate the types NOT specialized.  As far as I know there is no way for
type families to accomplish this (specialize, say Int, and have a
fallback for everything else).  In general, is there a recognized
work-around for this?  For example, is this a place where using functional
dependencies instead might do the trick?

Also, there are some software-engineering issues here with respect to* where
to put the instances*.  It would be nice to 

Re: [Haskell-cafe] happstack file serving

2011-11-02 Thread Jeremy Shaw
On Tue, Nov 1, 2011 at 9:48 AM, Gary Klindt gary.kli...@googlemail.com wrote:
 Hello all,

 I want to have a web application using one 'index.html' file with ajax
 requests and a happstack web server which response to server requests.
 For that purpose I need to use some javascript libraries in my directory
 tree. I tried:

 main = simpleHTTP nullConf $ msum [ serveFile (asContentType text/html)
 index.html
                                  , serveFile (asContentType
 text/javascript) javascript/js.js ]

As you discovered, serveDirectory is what you probably want. But,
let's say you really want to use serveFile for some reason.

The problem with  your code is that each of those lines will response
to *any* incoming request. You really want the first line to only
respond to requests for /index.html and the second to only respond to
requests for /javascript/js.js. So you would need to rewrite you
code like:

 simpleHTTP nullConf msum $
   [ dir index.html $ serveFile (asContentType text/html;
charset=UTF-8) index.html
   , dir javascript $ dir js.js $ serveFile (asContentType
text/javascript) javascript/js.js
   ]

That would allow you to request /index.html vs javascript/js.js. Now,
obviously it is annoying to have to specify the names of the files
twice. But that is because serveFile is not really intended to be used
that way.

serveFile is typically used when the name of the file in the request
is different from the name of the file on the disk. For example, let's
say we have an image gallery. When people upload images, they might
have very common names like DSC_0123.jpg. So, we might get file
collisions if we tried to use the original file name to store the
file. Instead, we might rename the file to same unique name that we
know won't have any collisions. But, we might have the url be
something like, /image/theuniqueid/DSC_0123.jpg. That way when someone
downloads the file, their original file name is still intact. That
means we need some way to serve a file from the disk where the name of
the file on the disk is not the same of the name of the file in the
URL.

For that scheme we would have something like:

dir image $
 path $ \uniqueid -
  anyPath $
do locationOnDisk - lookupDiskLocation uniqueId
serveFile guessContentTypeM locationOnDisk

where lookDiskLocation is some application specific function.

- jeremy

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


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread wren ng thornton

On 11/2/11 9:24 AM, Jean-Marie Gaillourdet wrote:

Hi Eugene,

did you try using the SPECIALIZE pragma? It is part of the Haskell 98 and 
Haskell 2010 specifications.


The problem with SPECIALIZE is that you still have to give a parametric 
definition for the function, whereas the whole point of specializing 
realToFrac is in order to use non-parametric definitions like the 
built-in machine ops.


--
Live well,
~wren

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


Re: [Haskell-cafe] Tell cabal-install to generate only shared libraries

2011-11-02 Thread Yves Parès
Apparently, disabling library vanilla causes GHC not to generate the .hi
files :
For instance when 'cabal install quickcheck --disable-library-vanilla':

Registering QuickCheck-2.4.1.1...
cabal: QuickCheck-2.4.1.1: file Test/QuickCheck/All.hi is missing (use
--force
to override)
QuickCheck-2.4.1.1: file Test/QuickCheck/Function.hi is missing (use --force
to override)
[...]
override)
QuickCheck-2.4.1.1: file Test/QuickCheck/State.hi is missing (use --force to
override)
QuickCheck-2.4.1.1: file Test/QuickCheck/Exception.hi is missing (use
--force
to override)
QuickCheck-2.4.1.1: cannot find libHSQuickCheck-2.4.1.1.a on library path
(use
--force to override)


2011/11/3 Ivan Perez ivanperezdoming...@gmail.com

 2011/11/2 Yves Parès limestr...@gmail.com:
  Hello,
 
  When I tell cabal-install to build shared libraries (with Shared: True
 in
  .cabal/config), it doubles the libraries installation time since it
 compiles
  them twice, since it seems that is what GHC's flag -shared does.
  Is there a way to generate only the .so and not the the .a libs?

 --disable-library-vanilla

Do not build ordinary libraries. This is useful in conjunction
 with --enable-library-profiling
to build only profiling libraries, rather than profiling and
 ordinary libraries.

 Haven't tried it myself. Maybe it works in combination with
 --enable-shared?

 From: http://haskell.org/ghc/docs/7.0.4/html/Cabal/builders.html

 
  Furthermore, I have the impression that the executables compiled by
  cabal-install are always linked statically... Can I tell cabal-install to
  activate the GHC's flag -dynamic for executables?

 The following two trac tickets mention a separate flag,
 named --enable-executable-dynamic:

 http://hackage.haskell.org/trac/hackage/ticket/600
 http://hackage.haskell.org/trac/hackage/ticket/869

 If that doesn't work, you can probably pass some argument to ghc with
 --with-ghc-option

 Cheers,
 Ivan

 
  Thanks.
 
  ___
  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] The type class wilderness + Separating instances and implementations into separate packages

2011-11-02 Thread Johan Tibell
These are all very good questions! Here's my stab at it:

On Wed, Nov 2, 2011 at 11:28 AM, Ryan Newton rrnew...@gmail.com wrote:

 What is the right interface for a queue?  What is the right interface for
 a random number generator?


For any given class I'd try to get a few experts/interested parties
together and discuss.


 I don't know, but in both cases you will find many packages on hackage
 offering different takes on the matter.  In fact, there is a wilderness of
 alternative interfaces.  We've had various discussions on this list about
 the number of alternative packages.


The lack of cohesion in our library offerings is a problem and so is the
lack of interfaces. We end up programming against concrete types way too
often.


 I'm fine with lots of packages, but I think it would be great if not every
 package introduced a new interface as well as a new implementation.  If we
 could agree as a community on common interfaces to use for some basics,
 that would probably go a long way towards taming the type class wilderness.
  People have mentioned this problem before with respect to Collections
 generally.


Aside: The problem with collections is that we don't have the programming
language means to do this well yet (although soon!). The issue is that we
want to declare a type class where the context of the methods depends on
the instance e.g.

class MapLike m where
type Ctx :: Context  -- Can't do this today!
insert Ctx = k - v - m - m

Java et all cheats in their container hierarchy by doing unsafe casts (i.e.
they never solved this problem)!


 One basic part of reaching such a goal is separating interface from
 implementation.  I ran into the following problems just  in the last 24
 hours.  In both cases I wanted to use a type class, but didn't want to
 depend on the whole package it lived in:

- I wanted to use the Benchmarkable class in Criterion in my package.
 (Criterion deserving to be a standard package.)  But I can't get that
typeclass without depending on the whole Criterion package, which has
several dependencies.  And in fact on the machine I was on at the time some
of those dependencies were broken, so I decided not to use Benchmarkable.
- I wanted to use, or at least support, an existing class for Queues.
 I found the following:


 http://hackage.haskell.org/packages/archive/queuelike/1.0.9/doc/html/Data-MQueue-Class.html


I think the best option at the moment is to break out type classes in their
own packages. That's what I did with hashable.

How can we enumerate packages that at least purport to provide standard
 interfaces that you should both use and pick up to implement?  On a Wiki
 page?


I would hope that we could get all the important interfaces into the
Haskell Platform eventually (and have all packages there use them).

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


[Haskell-cafe] Haskell Weekly News: Issue 206

2011-11-02 Thread Daniel Santa Cruz
Welcome to issue 206 of the HWN, a newsletter covering developments in
the Haskell community. This release covers the week of October 23 to
29, 2011.

A HTML version of this issue can be found at:
http://contemplatecode.blogspot.com/2011/11/haskell-weekly-news-issue-206.html

Announcements

   Edward Kmett extended an invitation to the Hac Boston, to be held
   between Jan 20 to 22, 2012 at MIT in Cambridge, MA.
   [1] http://goo.gl/cZpvu

   Brent Yorgey has released the lastest issue of the Monad.Reader.
   This is a special issue on parallelism and concurrency.
   [2] http://goo.gl/JqIpx

   Ganesh Sittampalam shared the haskell.org committee's first-year
   report.
   [3] http://goo.gl/O1vNQ

New and Updated Projects

   * diagrams (Brent Yorgey; 0.4) There are quite a few changes and
 improvements since the 0.1 release.
 [4] http://goo.gl/4nCE7

   * HasGP (Sean Holden; 0.1) A library for Gaussian process
 inference.
 [5] http://goo.gl/JAI8u

   * OpenGL (Jason Dagit) Updates to the following packages: OpenGL,
 OpenGLRaw, GLURaw, and GLUT.
 [6] http://goo.gl/mhTek

Quotes of the Week

   * DanBurton: are you using -XAbsurdInstances again?

   * ritchie: C has the power of assembly language and the convenience
 of ... assembly language.

   * RaptorRarr: Analogy puzzles are to intelligence as __ is to
 elephants

   * Eduard_Munteanu: Haskell Ain't Some Kludgy Enterprisey Lame
 Language

   * byorgey: Monads are not supposed to be anything. They just are.

   * kmc: 4:20 smoke MagicHash every day

Top Reddit Stories

   * Giving Haskell a Promotion
 (typed type-level programming/new kind system paper)
 Domain: research.microsoft.com, Score: 76, Comments: 29
 On Reddit: [7] http://goo.gl/W5Jbb
 Original: [8] http://goo.gl/1p4BU

   * Frameworks drive language adoption - Yesod Blog
 Domain: yesodweb.com, Score: 57, Comments: 15
 On Reddit: [9] http://goo.gl/BAOKH
 Original: [10] http://goo.gl/KEZU9

   * Snap 0.6 Released
 Domain: snapframework.com, Score: 57, Comments: 8
 On Reddit: [11] http://goo.gl/YdfTn
 Original: [12] http://goo.gl/3wTbZ

   * Code that writes code and conversation about conversations
 Domain: yesodweb.com, Score: 49, Comments: 23
 On Reddit: [13] http://goo.gl/3cjxL
 Original: [14] http://goo.gl/701ar

   * The Monad.Reader Issue 19: Parallelism and Concurrency
 Domain: themonadreader.files.wordpress.com, Score: 49, Comments: 8
 On Reddit: [15] http://goo.gl/D8AcV
 Original: [16] http://goo.gl/virTX

   * Zero-Analogy Monad Tutorial
 Domain: unknownparallel.com, Score: 48, Comments: 57
 On Reddit: [17] http://goo.gl/kwf8k
 Original: [18] http://goo.gl/RbAWG

   * Dear Redditor Vim-loving Haskeller(s):
 what cool vim plugins or features do you use?
 Domain: self.haskell, Score: 46, Comments: 35
 On Reddit: [19] http://goo.gl/oL6vH
 Original: [20] http://goo.gl/oL6vH

   * Rendering animated quasicrystals in parallel, with Haskell and Repa
 Domain: mainisusuallyafunction.blogspot.com, Score: 43, Comments: 12
 On Reddit: [21] http://goo.gl/aJzFN
 Original: [22] http://goo.gl/rEs6X

   * Why is there no cabal uninstall option?
 Domain: self.haskell, Score: 39, Comments: 26
 On Reddit: [23] http://goo.gl/2zy6P
 Original: [24] http://goo.gl/2zy6P

   * Quasicrystals rendered in real time using a pre-release
 or Repa3 [video].
 Domain: youtube.com, Score: 36, Comments: 0
 On Reddit: [25] http://goo.gl/SA7Zt
 Original: [26] http://goo.gl/YaJN8

Top StackOverflow Questions

   * How to make my Haskell program faster? Comparison with C
 votes: 28, answers: 4
 Read on SO: [27] http://goo.gl/s01Nc

   * Why is it faster to sum a Data.Sequence by divide-and-conquer,
 even with no parallelism?
 votes: 25, answers: 2
 Read on SO: [28] http://goo.gl/nR2eC

   * ST Monad == code smell?
 votes: 19, answers: 3
 Read on SO: [29] http://goo.gl/sQeYv

   * Algorithm for type checking ML-like pattern matching?
 votes: 19, answers: 3
 Read on SO: [30] http://goo.gl/Sl6Zy

   * Why does GHC think that this type variable is not injective?
 votes: 16, answers: 2
 Read on SO: [31] http://goo.gl/smdFX

   * Expression evaluation mode in haskell for scripting
 votes: 13, answers: 3
 Read on SO: [32] http://goo.gl/1UIAq

   * PCRE in Haskell - what, where, how?
 votes: 10, answers: 4
 Read on SO: [33] http://goo.gl/43Dtu

   * Non-Trivial Lazy Evaluation
 votes: 9, answers: 2
 Read on SO: [34] http://goo.gl/2BlZ4

   * How to get variable name in haskell
 votes: 7, answers: 2
 Read on SO: [35] http://goo.gl/we5N7

   * Is it possible to define type with callable objects in Haskell?
 votes: 7, answers: 3
 Read on SO: [36] http://goo.gl/qnNjb

Until next time,
Daniel Santa Cruz

References

   1. http://comments.gmane.org/gmane.comp.lang.haskell.cafe/93405
 

Re: [Haskell-cafe] Fwd: Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Eugene Kirpichov
Thanks! I'll definitely consider your library in the future, but for now,
as we can see, there's no necessity in rewriting cFloatConv at all - {-#
INLINE #-} suffices :)

On Thu, Nov 3, 2011 at 3:30 AM, wren ng thornton w...@freegeek.org wrote:

 On 11/2/11 7:14 AM, Eugene Kirpichov wrote:

 I rewrote cFloatConv like this:

 import GHC.Float
 class (RealFloat a, RealFloat b) =  CFloatConv a b where
   cFloatConv :: a -  b
   cFloatConv = realToFrac

 instance CFloatConv Double Double where cFloatConv = id
 instance CFloatConv Double CDouble
 instance CFloatConv CDouble Double
 instance CFloatConv Float Float where cFloatConv = id
 instance CFloatConv Float Double where cFloatConv = float2Double
 instance CFloatConv Double Float where cFloatConv = double2Float


 If you're going the MPTC route, I suggest you use 
 logfloat:Data.Number.**RealToFrac[1].
 I don't have the CDouble and CFloat instances, but I could add them. The
 instances themselves are only moderately more clever than yours ---namely
 using CPP for portability to non-GHC compilers--- but I think it's good for
 people to rally around one implementation of the solution instead of having
 a bunch of copies of the same thing, each poorly maintained because of the
 distributedness.


 [1] http://hackage.haskell.org/**packages/archive/logfloat/0.**
 12.1/doc/html/Data-Number-**RealToFrac.htmlhttp://hackage.haskell.org/packages/archive/logfloat/0.12.1/doc/html/Data-Number-RealToFrac.html

 --
 Live well,
 ~wren


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe




-- 
Eugene Kirpichov
Principal Engineer, Mirantis Inc. http://www.mirantis.com/
Editor, http://fprog.ru/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe