Easily generating efficient instances for classes

2010-02-24 Thread Christian Höner zu Siederdissen
Hi,

I am thinking about how to easily generate instances for a class. Each
instance is a tuple with 1 or more elements. In addition there is a
second tuple with the same number of elements but different type. This
means getting longer and longer chains of something like (...,x3*x2,x2,0).

- template haskell?
- CPP and macros?

Consider arrays with fast access like Data.Vector, but with higher
dimensionality. Basically, I want (!) to fuse when used in Data.Vector
code.

A code abstract follows -- I will put this on hackage if there is
insterest. And please comment if you think of something how to improve
here.


Viele Gruesse,
Christian



-- | Primitive multidimensional tables without bounds-checking. Internally, we
-- used unboxed vectors. Construction expects the highest possible index in
-- each dimension, not the length (which is highest index +1). This choice
-- allows for easier construction using bounded types. Consider: "fromList True
-- False [] :: PrimTable Bool Bool" which creates a 2-element table.

-- | Fast lookup table: `a` encodes the storage index type, while (!) only
-- requires that the index value is (Enum).

data PrimTable a b = PrimTable
  {-# UNPACK #-} !a -- ^ the highest indices (every index starts at 
0 (or 0,0 ...))
  {-# UNPACK #-} !a -- ^ precalculated multiplication values
  {-# UNPACK #-} !(V.Vector b)  -- ^ storage space



-- | mutable fast lookup table

data MPrimTable s a b = MPrimTable
  {-# UNPACK #-} !a
  {-# UNPACK #-} !a
  {-# UNPACK #-} !(V.MVector s b)



class (V.Unbox b) => PrimTableOperations a b e where

  -- | Fast index operation using precomputed multiplication data. Does
  -- bounds-checking only using assert.
  (!) :: PrimTable a b -> e -> b
  {-# INLINE (!) #-}

  new :: (PrimMonad s) => e -> s (MPrimTable (PrimState s) a b)
  {-# INLINE new #-}

  newWith :: (PrimMonad s) => e -> b -> s (MPrimTable (PrimState s) a b)
  {-# INLINE newWith #-}

  read :: (PrimMonad s) => MPrimTable (PrimState s) a b -> e -> s b
  {-# INLINE read #-}

  write :: (PrimMonad s) => MPrimTable (PrimState s) a b -> e -> b -> s ()
  {-# INLINE write #-}

  fromList :: e -> b -> [(e,b)] -> PrimTable a b
  fromList dim init xs = runST $ do
mpt <- newWith dim init
mapM_ (\(k,v) -> write mpt k v) xs
unsafeFreeze mpt
  {-# INLINE fromList #-}






-- | Two-dimensional tables.

instance (Enum e, V.Unbox b) => PrimTableOperations (Int,Int) b (e,e) where

  (PrimTable (z2,z1) (n2,n1) arr) ! (k2,k1) =
arr `V.unsafeIndex` (fromEnum k2 * n2 + fromEnum k1)
  {-# INLINE (!) #-}

  new (z2',z1') = do
let z2 = fromEnum z2' +1
let z1 = fromEnum z1' +1
marr <- M.new $ z2 * z1
return $ MPrimTable (z2,z1) (z1,0) marr

  newWith (z2,z1) v = do
mpt <- new (z2,z1)
mapM_ (\k -> write mpt k v) [(k2,k1) | k2 <- [toEnum 0..z2], k1 <- [toEnum 
0..z1]]
return mpt

  read (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) =
M.read marr (fromEnum k2 * n2 + fromEnum k1)

  write (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) v =
M.write marr (fromEnum k2 * n2 + fromEnum k1) v



-- example

jarr :: PrimTable (Int,Int) Double
jarr = fromList (2 :: Int,2 :: Int) 0.0 
[((0,0),1.0),((0,1),2.0),((1,0),3.0),((1,1),4.0)]
runj = [jarr ! (k :: (Int,Int)) | k <- [(0,0),(0,1),(1,0),(1,1)]]



pgpmQXnina3fi.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Simon Marlow

On 24/02/2010 14:08, Christian Maeder wrote:

Simon Marlow schrieb:

On 24/02/2010 12:28, Christian Maeder wrote:

[...]

It is not sufficient for me to reinstall this package with this utf8
setting. (I think ghc-pkg needs to be fixed or maybe recompiled under
utf8.)


There was a missing hSetEncoding, so that ghc-pkg is writing this file
using the current locale rather than UTF-8, but reading it back as
UTF-8.  So I'm surprised that temporarily setting your locale to UTF-8
doesn't work around it - what happens?


No idea, the last step of installing is:

Registering syb-0.1.0.3...
/local/maeder/bin/ghc-pkg update - --global --no-user-package-conf -v2

The standard input passed to ghc-pkg is utf8 coded (independent of my
LANG setting), but the output file written
syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf is always ISO-8859.

HTH Christian


It does, thanks.  I now realise that the code is using binary mode 
accidentally, in fact it has an instance of this bug


  http://hackage.haskell.org/trac/ghc/ticket/3832

because ghc-pkg contains a copy of the code of openTempFile.  I'll fix 
it to use openTempFileWithDefaultPermissions, which does the right thing.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Christian Maeder
Simon Marlow schrieb:
> On 24/02/2010 12:28, Christian Maeder wrote:
[...]
>> It is not sufficient for me to reinstall this package with this utf8
>> setting. (I think ghc-pkg needs to be fixed or maybe recompiled under
>> utf8.)
> 
> There was a missing hSetEncoding, so that ghc-pkg is writing this file
> using the current locale rather than UTF-8, but reading it back as
> UTF-8.  So I'm surprised that temporarily setting your locale to UTF-8
> doesn't work around it - what happens?

No idea, the last step of installing is:

Registering syb-0.1.0.3...
/local/maeder/bin/ghc-pkg update - --global --no-user-package-conf -v2

The standard input passed to ghc-pkg is utf8 coded (independent of my
LANG setting), but the output file written
syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf is always ISO-8859.

HTH Christian
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Simon Marlow

On 24/02/2010 12:28, Christian Maeder wrote:


And you got that by just 'cabal install syb'?  What version of
cabal-install?  (cabal --version)


No, just by the Setup, configure, build, install procedure.

"ghc-pkg describe syb" and "ghc-pkg dump" create UTF-8 output.


Aha, I think I see where the bug is. Thanks folks, we'll have it fixed
in 6.12.2.  In the meantime you should use a UTF-8 locale, eg.
LANG=en_US.utf8.


It is not sufficient for me to reinstall this package with this utf8
setting. (I think ghc-pkg needs to be fixed or maybe recompiled under utf8.)


There was a missing hSetEncoding, so that ghc-pkg is writing this file 
using the current locale rather than UTF-8, but reading it back as 
UTF-8.  So I'm surprised that temporarily setting your locale to UTF-8 
doesn't work around it - what happens?


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Christian Maeder
Simon Marlow schrieb:
> On 24/02/2010 11:35, Christian Maeder wrote:
>> Simon Marlow schrieb:
> Both Cabal and ghc-pkg explicitly use UTF-8 for handling .cabal and
> package configuration files, so if you end up with a Latin-1 file in
> your package database then something has gone wrong.  If anyone can
> reproduce this problem then please submit a ticket.

 Indeed, I have a latin-1 file

 /local/maeder/lib/ghc-6.13.20100211/package.conf.d/syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf:


 ISO-8859 English text

 and my (accidental) setting is:

 lang=de...@euro

Right, this is a latin1 locale and the whole compiler was created with
this setting.

I think "ghc-pkg upate - ..." creates the latin1 file.

(I've some latin1 source files that need this setting.)

 LANGUAGE=
 LC_ALL=C

The LANGUAGE variable is properly a left-over typing error and not
relevant. And "LC_ALL" does not seem to take precedence over LANG on my
(SuSE) system.

>>> And you got that by just 'cabal install syb'?  What version of
>>> cabal-install?  (cabal --version)
>>
>> No, just by the Setup, configure, build, install procedure.
>>
>> "ghc-pkg describe syb" and "ghc-pkg dump" create UTF-8 output.
> 
> Aha, I think I see where the bug is. Thanks folks, we'll have it fixed
> in 6.12.2.  In the meantime you should use a UTF-8 locale, eg.
> LANG=en_US.utf8.

It is not sufficient for me to reinstall this package with this utf8
setting. (I think ghc-pkg needs to be fixed or maybe recompiled under utf8.)

Cheers Christian




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Simon Marlow

On 24/02/2010 11:35, Christian Maeder wrote:

Simon Marlow schrieb:

Both Cabal and ghc-pkg explicitly use UTF-8 for handling .cabal and
package configuration files, so if you end up with a Latin-1 file in
your package database then something has gone wrong.  If anyone can
reproduce this problem then please submit a ticket.


Indeed, I have a latin-1 file

/local/maeder/lib/ghc-6.13.20100211/package.conf.d/syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf:

ISO-8859 English text

and my (accidental) setting is:

lang=de...@euro
LANGUAGE=
LC_ALL=C


And you got that by just 'cabal install syb'?  What version of
cabal-install?  (cabal --version)


No, just by the Setup, configure, build, install procedure.

"ghc-pkg describe syb" and "ghc-pkg dump" create UTF-8 output.


Aha, I think I see where the bug is. Thanks folks, we'll have it fixed 
in 6.12.2.  In the meantime you should use a UTF-8 locale, eg. 
LANG=en_US.utf8.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Christian Maeder
Simon Marlow schrieb:
>>> Both Cabal and ghc-pkg explicitly use UTF-8 for handling .cabal and
>>> package configuration files, so if you end up with a Latin-1 file in
>>> your package database then something has gone wrong.  If anyone can
>>> reproduce this problem then please submit a ticket.
>>
>> Indeed, I have a latin-1 file
>>
>> /local/maeder/lib/ghc-6.13.20100211/package.conf.d/syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf:
>>
>> ISO-8859 English text
>>
>> and my (accidental) setting is:
>>
>> lang=de...@euro
>> LANGUAGE=
>> LC_ALL=C
> 
> And you got that by just 'cabal install syb'?  What version of
> cabal-install?  (cabal --version)

No, just by the Setup, configure, build, install procedure.

"ghc-pkg describe syb" and "ghc-pkg dump" create UTF-8 output.

Christian

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Simon Marlow

On 24/02/2010 10:07, Christian Maeder wrote:

Simon Marlow schrieb:

On 23/02/10 18:46, Christian Maeder wrote:

Ross Paterson schrieb:

On Tue, Feb 23, 2010 at 03:05:56PM -, Bayley, Alistair wrote:

Just a wild guess, but the package description has this non-ascii text:

author: Ralf Lämmel, Simon Peyton Jones

It could well be Latin-1 encoded, rather than UTF8.


No, syb-0.1.0.3/syb.cabal is UTF-8-encoded (conforming to the Cabal
docs).


My guess would be that the "locale" is not properly set. The environment
variable LANG should be set to something shown by "locale -a" (i.e
en_GB). Other LC_* variables should not be set.
The variables should not be "C" or "POSIX".

(I was able to install syb-0.1.0.3 without a problem)


Both Cabal and ghc-pkg explicitly use UTF-8 for handling .cabal and
package configuration files, so if you end up with a Latin-1 file in
your package database then something has gone wrong.  If anyone can
reproduce this problem then please submit a ticket.


Indeed, I have a latin-1 file

/local/maeder/lib/ghc-6.13.20100211/package.conf.d/syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf:
ISO-8859 English text

and my (accidental) setting is:

lang=de...@euro
LANGUAGE=
LC_ALL=C


And you got that by just 'cabal install syb'?  What version of 
cabal-install?  (cabal --version)


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Installing syb(-0.1.03) package in head version of Haskell

2010-02-24 Thread Christian Maeder
Simon Marlow schrieb:
> On 23/02/10 18:46, Christian Maeder wrote:
>> Ross Paterson schrieb:
>>> On Tue, Feb 23, 2010 at 03:05:56PM -, Bayley, Alistair wrote:
 Just a wild guess, but the package description has this non-ascii text:

 author: Ralf Lämmel, Simon Peyton Jones

 It could well be Latin-1 encoded, rather than UTF8.
>>>
>>> No, syb-0.1.0.3/syb.cabal is UTF-8-encoded (conforming to the Cabal
>>> docs).
>>
>> My guess would be that the "locale" is not properly set. The environment
>> variable LANG should be set to something shown by "locale -a" (i.e
>> en_GB). Other LC_* variables should not be set.
>> The variables should not be "C" or "POSIX".
>>
>> (I was able to install syb-0.1.0.3 without a problem)
> 
> Both Cabal and ghc-pkg explicitly use UTF-8 for handling .cabal and
> package configuration files, so if you end up with a Latin-1 file in
> your package database then something has gone wrong.  If anyone can
> reproduce this problem then please submit a ticket.

Indeed, I have a latin-1 file

/local/maeder/lib/ghc-6.13.20100211/package.conf.d/syb-0.1.0.3-2d8f18fd3343792a85816b191d973cea.conf:
ISO-8859 English text

and my (accidental) setting is:

lang=de...@euro
LANGUAGE=
LC_ALL=C

Cheers Christian

My ghc-6.12.1 uses syb-0.1.0.2 (which is ASCII)

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


create a DLL when using Gtk2hs

2010-02-24 Thread Paqui Lucio
Hi,
I am trying to generate a DLL for a Haskell program that imports
Graphics.UI.Gtk from the Gtk2hs package.
I have try to use the files .o that are in the Gtk2hs folder created by the
package installer, 
but it does not work. Does somebody knows, how to generate a DLL when this
package is used?
Thanks in advance,
Paqui

- 
Paqui Lucio
Dpto de LSI
Facultad de Informática
Paseo Manuel de Lardizabal, 1
20080-San Sebastián
SPAIN
-
e-mail: paqui.lu...@ehu.es
Tfn: (+34) (9)43 015049  
Fax: (+34) (9)43 015590
Web: http://www.sc.ehu.es/paqui
-

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users