RE: 'undefined reference to `_imp__Addr_zdfNumAddrOff_closure' (?????????)

2000-09-27 Thread Simon Peyton-Jones



Reuben 
is looking into this. I think that 4.08 is ok.

Simon

  -Original Message-From: Heron 
  [mailto:[EMAIL PROTECTED]]Sent: 19 September 2000 
  05:46To: [EMAIL PROTECTED]Subject: 
  'undefined reference to `_imp__Addr_zdfNumAddrOff_closure' 
  (?)
  Hello,
  
  I am using GHC 4.08.1 onWin32. Every attempt to 
  compile the code below results in a message error on link phase. The message 
  is shown after the code.
  
  teste.hs
  
  Module Main(main) where
  
  import GlaExtsimport Storableimport 
  Addr
  
  main :: IO Addrmain = malloc 0 = 
  \addr - return (f 
  addr) f :: Addr - Addrf 
  addr = addr `plusAddr` (fromIntegral 1)
  -
  
  
  ERROR MESSAGE WHEN LINKING:
  
  teste.o(.text+0x4c):fake: undefined reference to 
  `_imp__Addr_zdfNumAddrOff_closure'teste.o(.text+0xaf):fake: undefined 
  reference to `_imp__Addr_zdfNumAddrOff_closure'
  ---
  
  Originally, I detected this error when using the 
  pointer arithmetic operations povided by Addr library.
  The code is only for present the error. It has no 
  real meaning ... butI think it is correct. 
  
  Can you help me to solve this problem, please ? 
  :-)
  
  Heron
  
  
  


Re: 'undefined reference to `_imp__Addr_zdfNumAddrOff_closure' (? ????????)

2000-09-27 Thread Marc van Dongen

Simon Peyton Jones ([EMAIL PROTECTED]) wrote:

[snip]
: Subject: 'undefined reference to `_imp__Addr_zdfNumAddrOff_closure'
[snip]
: I am using GHC  4.08.1 on Win32. Every attempt to compile the code below
: results in a message error on link phase. The message is shown after the
: code.

Appologies if I am too paranoid here---I've
been reinstalling software for the last 20
hours or so:-)

Are these C identifiers? They are a bit long.
ANSI C only guarantees that identifiers up to
the first 31 characters can be distinguished.
The identifier mentioned above has a length
of 32.


Regards,


Marc van Dongen




panic! (the `impossible' happened) :-O

2000-09-27 Thread root

Hi,

 I get the following message error when compiling a Haskell
program with GHC.

=

Compilation Dump for: /usr/local/lib/ghc-4.08.1/hsc /tmp/ghc6065.cpp 2
erros -fglasgow-exts -fignore-interface-pragmas -fomit-interface-pragmas
-fsimplify [ -fmax-simplifier-iterations4 ]
-fwarn-overlapping-patterns -fwarn-missing-methods -fwarn-missing-fields
-fwarn-deprecations -fwarn-duplicate-exports -fhi-version=408 -static
"-himap=.%.hi:/usr/local/lib/ghc-4.08.1/imports/lang%.hi:/usr/local/lib/ghc-4.08.1/imports/lang%.hi:/usr/local/lib/ghc-4.08.1/imports/std%.hi"
"-himap-sep=:" -hifile=/tmp/ghc6065.hi -olang=asm
-ofile=/tmp/ghc6065.s -F=/tmp/ghc6065_stb.c -FH=/tmp/ghc6065_stb.h +RTS
-H600 -K100


panic! (the `impossible' happened):
 cgEvalAlts: dodgy case of unboxed tuple type

Please report it as a compiler bug to [EMAIL PROTECTED]
=

  The source code that produces error is:

=

module MessagePassing where

import PackUnpack

foreign import forceSend :: Int# - Int# - IO ()
foreign import forceRecv :: Int# - Int# - IO ()

data Protocol t =  H t = H (# Int#, t #)

class Empacotavel t = Protocol t where

  send :: Int# - Int# - t - IO ()
  send trg# cha# v = pack' v 
 forceSend trg# cha#
 where
 pack' :: t - IO ()
 pack' v = return (I# (pack 0# v)) 
   return ()

  recv :: Int# - Int# - IO t
  recv src# cha# = forceRecv src# cha# 
   unpack' 0#
   where
   unpack' :: Int# - IO t
   unpack' i# = return (H (unpack 0#)) = \ (H
(# _, v #)) -
return v


instance Protocol Int
instance Protocol Char
instance Protocol Float
instance Protocol Double
instance Protocol Bool
instance Protocol Integer
instance Protocol ()
instance Protocol t = Protocol [t]
instance Protocol a = Protocol (Maybe a)
instance (Protocol a, Protocol b) = Protocol (Either a b)
instance Protocol Ordering
instance (Integral a, Protocol a) = Protocol (Ratio a)
instance (Protocol a, RealFloat a) = Protocol (Complex a)
instance (Ix a, Protocol a, Protocol b) = Protocol (Array a b)
instance (Protocol t, Protocol u) = Protocol (t,u)
instance (Protocol t, Protocol u, Protocol v) = Protocol (t,u,v)
instance (Protocol t, Protocol u, Protocol v, Protocol w) = Protocol
(t,u,v,w)
instance (Protocol t, Protocol u, Protocol v, Protocol w, Protocol x) =
Protocol (t,u,v,w,x)

instance Protocol Int8
instance Protocol Int16
instance Protocol Int32
instance Protocol Int64
instance Protocol Word8
instance Protocol Word16
instance Protocol Word32
instance Protocol Word64
--instance Protocol Dynamic
--instance (Ix ix, Protocol ix) = Protocol (ByteArray ix)
--instance (Ix ix, Protocol ix) = Protocol (MutableByteArray ix)



The  definition of the Empacotavel type class is presented below...


class Empacotavel t where

  pack :: Int# - t - Int#
  unpack :: Int# - (# Int#, t #)


Heron de Carvalho