Re: Glasgow Haskell on different versions of Linux

2004-06-09 Thread Volker Stolz
In local.glasgow-haskell-users, you wrote:
 Christian Maeder wrote:
  What is ctype.h good for?

 A good question.  Its only use seems to be in
 ghc/rts/RtsFlags.c where it is used for functions
 like isdigit and isspace for decoding the RTS flags.
 Maybe it should be retired altogether.

 I'm rather puzzled how this works if ctype.h isn't
 there at all, as it seems to.

The functions are C89, so they should be present *somewhere* in libc
anywhere.
-- 
http://www-i2.informatik.rwth-aachen.de/stolz/ *** PGP *** S/MIME
Neu! Ă„ndern Sie den Anfangstag Ihrer Woche
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


compiling ghc-6.2.1

2004-06-09 Thread Christian Maeder
Christian Maeder wrote:
[EMAIL PROTECTED] - rpm -q gcc
gcc-3.3.3-41
make (in ghc-6.2.1) fails (in ghc/GC.c) with:
GC.c: In function `threadLazyBlackHole':
GC.c:4049: warning: use of cast expressions as lvalues is deprecated
make[2]: *** [GC.o] Fehler 1
The actual error not messed up by warnings is:
../../ghc/compiler/ghc-inplace -optc-O -optc-w -optc-Wall -optc-W 
-optc-Wstrict-prototypes -optc-Wmissing-prototypes 
-optc-Wmissing-declarations -optc-Winline -optc-Waggregate-return 
-optc-Wbad-function-cast -optc-I../includes -optc-I. -optc-Iparallel 
-optc-DCOMPILING_RTS -optc-fomit-frame-pointer -H16m -O -O2 -static 
-c GC.c -o GC.o
GC.c:1663: error: conflicting types for `evacuate'
GC.c:145: error: previous declaration of `evacuate'
make[2]: *** [GC.o] Fehler 1

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Glasgow Haskell on different versions of Linux

2004-06-09 Thread Glynn Clements

Volker Stolz wrote:

   What is ctype.h good for?
 
  A good question.  Its only use seems to be in
  ghc/rts/RtsFlags.c where it is used for functions
  like isdigit and isspace for decoding the RTS flags.
  Maybe it should be retired altogether.
 
  I'm rather puzzled how this works if ctype.h isn't
  there at all, as it seems to.
 
 The functions are C89, so they should be present *somewhere* in libc
 anywhere.

Actually, in GNU libc, isspace, isdigit etc are usually macros which
read a flag word from the __ctype_b array then and it with the
corresponding attribute mask.

  extern __const unsigned short int *__ctype_b; /* Characteristics.  */
  ...
  #define   __isctype(c, type) \
(__ctype_b[(int) (c)]  (unsigned short int) type)
  ...
  # define isdigit(c)   __isctype((c), _ISdigit)
  ...
  # define isspace(c)   __isctype((c), _ISspace)

However, glibc does export functions with those names, and you can
disable the macros by defining the __NO_CTYPE macro, with the result
that the binary depends upon isspace, isdigit etc rather than
__ctype_b.

I don't have glibc 2.3 here, but presumably __ctype_b has changed in
an incompatible manner (maybe there are more than 16 flags in 2.3, in
which case an unsigned short would no longer be sufficient).

-- 
Glynn Clements [EMAIL PROTECTED]
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Glasgow Haskell on different versions of Linux

2004-06-09 Thread George Russell
Volker Stolz wrote (snipped):
The functions are C89, so they should be present *somewhere* in libc
anywhere.
Yes, you're right.  Normally isspace and friends are used as macros,
but ANSI C requires them to be also available as functions so they
must be exported that way.
Therefore if you don't import ctype.h, what happens is that (isspace) is
implicitly assumed to be a function of type Int - Int, which (in this case)
happens to work.
The reason for the incompatibility is (see comments in ctype.h) something to
do with locales now being thread specific.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: compiling ghc-6.2.1

2004-06-09 Thread Christian Maeder
Christian Maeder wrote:
The actual error not messed up by warnings is:
../../ghc/compiler/ghc-inplace -optc-O -optc-w -optc-Wall -optc-W 
-optc-Wstrict-prototypes -optc-Wmissing-prototypes 
-optc-Wmissing-declarations -optc-Winline -optc-Waggregate-return 
-optc-Wbad-function-cast -optc-I../includes -optc-I. -optc-Iparallel 
-optc-DCOMPILING_RTS -optc-fomit-frame-pointer -H16m -O -O2 -static -c 
GC.c -o GC.o
GC.c:1663: error: conflicting types for `evacuate'
GC.c:145: error: previous declaration of `evacuate'
make[2]: *** [GC.o] Fehler 1
Sorry for answering my own question (or posing the question in the first 
place)

this problem is fixed in the latest ghc/rts/GC.c by:
// Use a register argument for evacuate, if available.
#if __GNUC__ = 2
#define REGPARM1 __attribute__((regparm(1)))
#else
#define REGPARM1
#endif
Christian
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Finalizers and FFI

2004-06-09 Thread Gracjan Polak
Hi all,
I would like to attach finalizer (written in Haskell) to some pointer. 
When the pointer won't be needed any more, finalizer should run. So here 
is the code:

module Main where
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.Marshal.Alloc
foreign import stdcall wrapper mkFin :: (Ptr a - IO ()) - IO (FunPtr 
(Ptr a - IO ()))

finDoIt ptr = putStrLn My finalizer
mkFinalizer = mkFin finDoIt
main = do
(ptr :: Ptr Int) - malloc
myFin - mkFinalizer
finptr - newForeignPtr myFin ptr
putStrLn End of script
This script ends with following output:
$ ./finalizers
End of script
Fail: loop
Also it seems to me that I'm not freeing finalizer stub. Is this code 
leaking memory?

How do I attach finalizer to object in the heap?
--
Pozdrawiam, Regards,
Gracjan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Finalizers and FFI

2004-06-09 Thread Arjan van IJzendoorn
HI Gracjan,
I would like to attach finalizer (written in Haskell) to some pointer. 
When the pointer won't be needed any more, finalizer should run. So 
here is the code:

import Foreign.ForeignPtr
I couldn't get finalisers to work either with the newForeignPtr from 
this module. I didn't know how to create a proper FunPtr. In 
Foreign.Concurrent there is a newForeignPtr that is easier to use:

newForeignPtr :: Ptr a - IO () - IO (ForeignPtr a)
This one worked beautifully for me. In your code something like:
import Foreign.ForeignPtr hiding (newForeignPtr)
import Foreign.Concurrent
   ... fptr - newForeignPtr ptr (finDoIt ptr)
Hope this helps,
  Arjan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Glasgow Haskell on different versions of Linux

2004-06-09 Thread Christian Maeder
I wrote:
since version 6.2 we have 2 binary distributions for (generic) linux:
for glibc 2.2 and glibc 2.3
Maybe this is no longer necessary. I've produced an installation (under 
glibc 2.2) that runs under glibc 2.2 and glibc 2.3.
I've now also successfully installed ghc-6.2.1 from source under glibc 
2.3 that works under glibc 2.2, too.

As also Volker Stolz suggested I've changed, after calling ./configure, 
a line in mk/config.h from

#define HAVE_CTYPE_H 1
to
/* #undef HAVE_CTYPE_H */
I'll try the same trick under glibc 2.3 later.
Yes, that basically did it. Thus the glibc 2.3 version (without ctype.h) 
should be sufficient as binary distribution in the future.

Christian
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Finalizers and FFI

2004-06-09 Thread Alastair Reid

  import Foreign.ForeignPtr

 I couldn't get finalisers to work either with the newForeignPtr from
 this module. I didn't know how to create a proper FunPtr.

You create a FunPtr using foreign import:

  foreign import ccall malloc.h free free_ptr :: FunPtr (Ptr a - IO ())

 In Foreign.Concurrent there is a newForeignPtr that is easier to use:

But, sadly, not portable.

--
Alastair Reid
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GMP

2004-06-09 Thread John Meacham
I was curious what the best way would be to access the various useful
GMP functions which are not exported for Integers. I was thinking of
making my own (strict) Integer type, but it would be much easier if I
can just use the FFI to import the required functions and get at the
mpz_t inside Integers somehow. 

I am not positive, but it looks like ghc seems to have primitives which
call the gmp functions internally rather than using the FFI.. At least I
didn't see an obvious example poking around in the library.

Has someone already done this? a Math.Integer.Advanced (or something)
library would be quite a useful addition to ghc.
John
-- 
John Meacham - repetae.netjohn 
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Data.Dynamic and dynamically loaded code

2004-06-09 Thread Donald Bruce Stewart
(lengthy)

Hey,

In the hs-plugins library I'm using Data.Dynamic to provide runtime type
checking of plugin values when they are loaded. There is a problem,
however: when using fromDyn/fromDynamic to check the type of the
plugin's value against the type the application loading the plugin
expects, they always report that types are unequal, even if they are the
same type on both sides.

So I'm reporting a limitation of the existing Data.Dynamic, and have a
couple of questions about why this exists.

The problem appears to be in the hash keys of the type representation
used to compare to types for equality. A dynamic value in the
(statically compiled) application never has the same key as its
equivalent type in the dynamically loaded code.  The type in the
dynamically-loaded plugin code is never recognised as having the same
type as in the application (static) code.

The following comment from Data.Typeable seems to be relevant:

-- In GHC we use the RTS's genSym function to get a new unique,
-- because in GHCi we might have two copies of the Data.Typeable
-- library running (one in the compiler and one in the running
-- program), and we need to make sure they don't share any keys.  
--
-- This is really a hack.  A better solution would be to centralise the
-- whole mutable state used by this module, i.e. both hashtables.  But
-- the current solution solves the immediate problem, which is that
-- dynamics generated in one world with one type were erroneously
-- being recognised by the other world as having a different type.

An example. The following code uses eval() to compile the string 7 + 8
to object code, and dynamically load the result.

  main = do i - eval 7 + 8 :: Int :: IO Int
putStrLn $ show i

When checking the dynamically loaded type using fromDynamic, we have
Int /= Int, which is obviously wrong. Running the equivalent code in
GHCi doesn't generate this error, nor does statically linked code. It is
only if we loadObj the plugin and check it against a type statically
compiled into the application doing the loading.

I currently work around this with a reimplemented Data.Dynamic that
compares the string representations of the types, which works mostly (so
that Int == Int, in the above code). However, when there is no
explicit type declaration in the dynamically loaded code, for
non-simple types, the *string* type representations differ. I.e. in the
following code:

main = do fn - eval \\(x::Int) - (x,x) :: IO (Int - (Int,Int))
  putStrLn $ show (fn 7)

we have type - Int (Int,Int) doesn't match Int - (Int,Int) (which
looks like a Core type in the first case). And for:

i - eval map (+1) [0..10::Int] :: [Int]

we have [] Int /= [Int]. So, the string comparison of types doesn't
always work.


So... for safe dynamically loaded plugins we need to fix Data.Dynamic to
provide the a unique integer key for types across both static and
dynamic code, I think. Does that seem like reasonable? 

And a question: why do we get different strings from TypeRep's when the
type is inferred? I can see that we are getting Core type reps, but why?
I would have thought that the TypeRep would still have to be constructed
in the same way as in an explicit declaration.

-- Don
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users