ClockTime closure linking issue

2010-04-05 Thread Gracjan Polak

Hi all,

Probable bug in GHC, I want to inquire before I report it proper. Did anybody
see something like this:


c:\Sources\happstack\happstack\templates\projectcabal build
[1 of 1] Compiling Main ( Setup.hs, dist\setup\Main.o )
Linking .\dist\setup\setup.exe ...
Preprocessing executables for guestbook-1.0...
Building guestbook-1.0...
[11 of 11] Compiling Main ( src\Main.hs, dist\build\guestbook-server
\guestbook-server-tmp\Main.o )
Linking dist\build\guestbook-server\guestbook-server.exe ...
dist\build\guestbook-server\guestbook-server-tmp\GuestBook\State2.o:fake:(.text+
0x6d89): undefined reference to `happstackzm0zi4zi3_HappstackziStateziClockTime_
constrZMabmKZN_closure'
dist\build\guestbook-server\guestbook-server-tmp\GuestBook\State2.o:fake:(.text+
0x6dd1): undefined reference to `happstackzm0zi4zi3_HappstackziStateziClockTime_
dataTypeZMabmJZN_closure'
[...lots of same messages skipped...]
collect2: ld returned 1 exit status

Application is from

http://patch-tag.com/r/mae/happstack/snapshot/current/content/pretty/happstack/templates/project

The Glorious Glasgow Haskell Compilation System, version 6.12.1

System Windows Vista 32bit.

Help!

-- 
Gracjan




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


Re: ClockTime closure linking issue

2010-04-05 Thread Gracjan Polak


Jeremy Shaw jeremy at n-heptane.com writes:

 
 My first guess is that it is another instance of this bug:
 http://hackage.haskell.org/trac/ghc/ticket/3799


Seems like putting

documentation: True

into

C:\Users\gracjan\AppData\Roaming\cabal\config

makes this error stand out

-- 
Gracjan


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


Re: cabal-install-0.8 final testing

2009-12-21 Thread Gracjan Polak
Duncan Coutts duncan.coutts at googlemail.com writes:

   if flag(test)
   Buildable: True
   Build-depends: base5, bytestring, HUnit, directory
   else
   Buildable: False
 

Is this solution good for the time being? If so, I'll change it to make peace
and happiness prevail among cabal users.

Side question: mmaptest is meant to be devel/testing thing only that is not
build during normal usage. Is there a better way to achieve such purpose?

-- 
Gracjan


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


Re: cvsweb back up

2004-08-20 Thread Gracjan Polak

Is there any haddoc documentation for GHC (compiler part, not 
libraries)? I still have trouble finding my way through the source...

Simon Marlow wrote:
Thanks to Jeff Lewis, we now have cvsweb back up again.  
 
Browse on over to http://cvs.haskell.org/cgi-bin/cvsweb.cgi/fptools/ and
enjoy!

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


Re: cvsweb back up

2004-08-20 Thread Gracjan Polak

Simon Marlow wrote:
 On 20 August 2004 12:04, Gracjan Polak wrote:


Is there any haddoc documentation for GHC (compiler part, not
libraries)? I still have trouble finding my way through the source...


 Sorry, no.  You could probably run Haddock on the source, although we've
 never tried and there isn't any actual documentation.
I did want to do this myself, but I did not manage to compile haddoc 
under Windows :(.

Is there anybody having pre-build haddoc for windows? Or guide how to do 
this myself?

 There's the
 commentary which may help:

 http://www.cse.unsw.edu.au/~chak/haskell/ghc/comm/

Thanks, I'm going to read it :)
 Cheers,
Simon
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Lazy version of peekArray

2004-06-22 Thread Gracjan Polak
Hi,
I'm trying to make use of memory mapped files with Haskell. It is kind 
of fun, I managed to mmap a file (actualy CreateFileMapping, because I'm 
on a Windows box), managed to setup finalizers (those kind of work now, 
see my posts about finalizers and FFI).

Now I got to content... and here is the problem.
Data I want to read is large, mostly binary with parts that must be 
parsed. But peekArray is not lazy (is IO action), produces large lists 
in strict mode. So I had to write my own thing. Provided that underlying 
data does not change following unsafeLazyPeekArray and friends should be 
good.

Does anybody see any problems in following code? Maybe there is 
something obvious I do not see...

Those functions were designed to be list less, when used in producer 
consumer fashion list will not be generated (I hope). Is current state 
GHC compiler smart enough to optimize this efficiently? How can I help 
it with this task (maybe a pragma here and there?)

Anyway, the code. Maybe someone find it interesting:

unsafeLazyPeekArray size ptr = unsafeLazyPeekArrayOffset 0 size ptr
unsafeLazyPeekArrayOffset :: Storable a =
 Int - Int - ForeignPtr a - [a]
unsafeLazyPeekArrayOffset offset size ptr
| size = 0 = []
| otherwise = unsafePerformIO $ helper offset
  where
  helper index | index = size = return []
   | otherwise = unsafeInterleaveIO $ do
 x - withForeignPtr ptr (\xptr -
 peekElemOff xptr index)
 xs - helper (index+1)
 return (x:xs)
unsafeLazyPeekArrayOffset0 :: (Storable a, Eq a) =
Int - a - ForeignPtr a - [a]
unsafeLazyPeekArrayOffset0 offset marker ptr =
unsafePerformIO $ helper offset
where
helper index = unsafeInterleaveIO $ do
 x - withForeignPtr ptr (\xptr -
 peekElemOff xptr index)
 if x==marker
 then return []
 else do
 xs - helper (index+1)
 return (x:xs)

unsafeLazyPeekArray0 :: (Storable a, Eq a) = a - ForeignPtr a - [a]
unsafeLazyPeekArray0 marker ptr =
unsafeLazyPeekArrayOffset0 0 marker ptr

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


ObjectIO

2004-06-22 Thread Gracjan Polak
Hi,
In the following code only processInit and processClose get ever called, 
other callbacks are *never* invoked. Is this known problem? Do I miss 
something obvious?

How do I get the handle of main window?
Here is the code:
module Main where
import Graphics.UI.ObjectIO
processAttributes =
[ ProcessActivate processActivate
, ProcessDeactivate processDeactivate   
, ProcessClose processClose 
, ProcessOpenFiles processOpenFiles 
-- , ProcessWindowPos ItemPos   
-- , ProcessWindowSize Size 
, ProcessWindowResize processWindowResize   
--, ProcessToolbar [ToolbarItem ps] 
-- , ProcessNoWindowMenu
]
processInit ps = do
liftIO $ putStrLn processInit
return ps
processActivate ps = do
liftIO $ putStrLn processActivate
return ps
processDeactivate ps = do
liftIO $ putStrLn processDeactivate
return ps
processClose ps = do
liftIO $ putStrLn processClose
closeProcess ps
processOpenFiles files ps = do
liftIO $ putStrLn (processOpenFiles  ++ show files)
return ps
processWindowResize oldsize newsize ps = do
liftIO $ putStrLn (processWindowResize ++ show newsize)
return ps
main = do
startIO SDI () processInit processAttributes

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


Re: ObjectIO

2004-06-22 Thread Gracjan Polak

Gracjan Polak wrote:
Hi,
In the following code only processInit and processClose get ever called, 
other callbacks are *never* invoked. Is this known problem? Do I miss 
something obvious?
Forgotten: Windows 2000, GHC-6.2.1 :)
--
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-11 Thread Gracjan Polak

Krasimir Angelov wrote:
The problem here is that the external functions
(instances of type FunPtr) are always executed with
ccall convention regardless of stdcall declaration in
the foreign import. The workaround is to write simple
stub function in C with ccall convention.
You are right, I did not think about that. I would expect at least a 
warning from compiler in this case.

Compilation with stub function produced perfect result. It worked.
As far as I know ia32 assembly the only thing that the stub does is 
something like:

 subl needed_stack_space, %esp
This could be made automagicaly by GHC... OK, enough ranting :)
Other question: having myPtr :: FunPtr Int, how do I call it from 
Haskell? Is there a way to just invoke function pointer?


Warnings in compilation are also strange:
$ ghc -package win32  --make interlvIO.hs -o
interlvIO.exe
Chasing modules from: interlvIO.hs
Compiling Main ( interlvIO.hs,
interlvIO.o )
Linking ...
Warning: resolving _UnmapViewOfFile by linking to
[EMAIL PROTECTED]
Use --enable-stdcall-fixup to disable these warnings
Use --disable-stdcall-fixup to disable these fixups

Try to use -fvia-C to avoid the warnings. When the
program is compiled via the native code generator then
windows.h isn't included and this causes the problem.
-fvia-C removed warnings but the program crashes anyway without hand 
written stubs. At first I thought that those stdcall-fixups were in 
fact stdcall to ccall wrappers. OK, nevermind.

--
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-11 Thread Gracjan Polak

Niklas Sorensson wrote:
Arjan van IJzendoorn wrote:
 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:
 [deleted]

I seem to remeber running in to this problem a couple of years ago,
and if I remember correctly, I came to the conclusion that finalizers do
run at the end of the program, but *after* standard input is closed.
Yes, you are right. Thanks for the idea. Checked under GHC 6.2.
--
Gracjan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Finalizers and FFI

2004-06-11 Thread Gracjan Polak

Arjan van IJzendoorn wrote:

 foreign import ccall ... finaliserCreator :: IO (FunPtr (Ptr a - 
IO ()))

 and then

 finaliser - finaliserCreator


AFAIK this creates some dynamic machine code in malloce'd area, so there 
is need to free it afterward with freeHaskellFunPtr. Are you doing that? 
How? And when? I did not find any suitable place in my code to call 
freeHaskellFunPtr.

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


Open GL, GLUT

2004-06-11 Thread Gracjan Polak
Hi all,
I'd like to make some use of OpenGL with Haskell (under Win2000).
Here is some code:
module Main where
import Graphics.Rendering.OpenGL.GL
import Graphics.Rendering.OpenGL.GLU
import Graphics.UI.GLUT
main = do
ver - get gluVersion
putStrLn ver
getArgsAndInitialize
fullScreen
wnd - createWindow Hello World
vertex (Vertex2 (100::GLint) 100)
return ()
Compilation (linking) fails with:
$ ghc --make openglapp.hs -o openglapp.exe
Chasing modules from: openglapp.hs
Compiling Main ( openglapp.hs, openglapp.o )
Linking ...
c:/ghc/ghc-6.2/libHSGLUT.a(Initialization__158.o)(.text+0x123):ghc16024.hc: 
unde
fined reference to [EMAIL PROTECTED]'
c:/ghc/ghc-6.2/libHSGLUT.a(Window__61.o)(.text+0x33):ghc14736.hc: 
undefined refe
rence to [EMAIL PROTECTED]'
c:/ghc/ghc-6.2/libHSGLUT.a(Window__53.o)(.text+0x85):ghc14736.hc: 
undefined refe
rence to [EMAIL PROTECTED]'

Manually adding -lglut -lglut32 does not help. Libraries libglut32.a and 
libglut.a are there, they contain needed symbols but with '_' prepended, 
like [EMAIL PROTECTED]

Functions from GL and GLU link perfectly. They do even work correctly 
when run. Only GLUT ones do not :(

Has anybody compiled anything for GL recently? Google pointed me only to 
some old, not relevant any more, material.

Am I missing something obvious here?
GHC 6.2, installer for Window taken from www.haskell.org, Win2000 
Professional.

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


Re: Finalizers and FFI

2004-06-10 Thread Gracjan Polak

Arjan van IJzendoorn wrote:
 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:
 [deleted]
So here is the new code:
{-# OPTIONS -fglasgow-exts #-}
module Main where
import Foreign.Ptr
import Foreign.ForeignPtr hiding (newForeignPtr)
import Foreign.Marshal.Alloc
import Foreign.Concurrent
import System.Mem
myFinalizer = putStrLn My finalizer
subproc = do
(ptr :: Ptr Int) - malloc
finptr - newForeignPtr ptr myFinalizer
putStrLn End of subproc
main = do
subproc
performGC
putStrLn End of program
This program compiled under GHC 6.2 gives follwing output:
$ ./finalizers
End of subproc
End of program
So, this basically means that my finalizer did not get run :( Strange 
thing to me. Spec says 
(http://www.haskell.org/ghc/docs/latest/html/libraries/base/Foreign.Concurrent.html):

The finalizer will be executed after the last reference to the foreign 
object is dropped. Note that there is no guarantee on how soon the 
finalizer is executed after the last reference was dropped; this depends 
on the details of the Haskell storage manager. The only guarantee is 
that the finalizer runs before the program terminates.

It should run, in separate thread or not, it doesn't matter here.
Any ideas why doesn't it work?
--
Gracjan
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Finalizers and FFI

2004-06-10 Thread Gracjan Polak

Alastair Reid wrote:
You could give the finalizer thread a chance to run by calling 
Control.Concurrent.yield before exiting:

Thanks, it worked. This is ok for me, because my finalizer only closes 
some handles. Those are closed at program end anyway, so in this case I 
can live with it.

BUT: This can make some people unhappy. Isn't there a more deterministic 
 way to schedule finalizers? I've read about MVars etc, but this seems 
like an ugly hack around GC deficiency.

Do weak references have same problem?
Also documentation about newForeignPtr (in Control.Concurrent and in 
Foreign.ForeignPtr) is lying: The only guarantee is that the finaliser 
runs before the program terminates. Currently there is no guarantee :)

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


Re: Finalizers and FFI

2004-06-10 Thread Gracjan Polak

Alastair Reid wrote:
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 ())
foreign import stdcall windows.h UnmapViewOfFile
  funptrUnmapViewOfFile :: FunPtr (Ptr a - IO ())
Basically I'd love to do (in Windows world):
mapTheFileToMemory = do
   handle  - winOpenFile(...)
   mapping - winCreateFileMapping(...)
   view- winMapViewOfFile(...)
   finview - newForeignPtr funptrUnmapViewOfFile view
   return finview
Strangely enough my finalizer run always this time, no need to say 
performGC or yield'ing at the end of main. But it crashes my program :(

Warnings in compilation are also strange:
$ ghc -package win32  --make interlvIO.hs -o interlvIO.exe
Chasing modules from: interlvIO.hs
Compiling Main ( interlvIO.hs, interlvIO.o )
Linking ...
Warning: resolving _UnmapViewOfFile by linking to [EMAIL PROTECTED]
Use --enable-stdcall-fixup to disable these warnings
Use --disable-stdcall-fixup to disable these fixups
I did not find any of those flags. Searching sources downloaded from 
website today also does not say anything about stdcall fixups. Changing 
calling convention from stdcall to ccall in import clause did not help 
either.

At the end of (correct) run my program dies with:
interlvIO.exe: internal error: resumeThread: thread not found
Please report this as a bug to [EMAIL PROTECTED],
or http://www.sourceforge.net/projects/ghc/
So basically I have no idea how to make finalizer out of UnmapViewOfFile :(
Any ideas where to go now?
--
Gracjan
___
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