I'm running into a strange problem when I build the X11 library using current 
ghc (built from repository yesterday using gcc 3.2).  The error message I get 
is:

   ghc-6.1: unknown package name: Main

The puzzling bit here is that I am compiling a part of a library using -c, I 
don't mention a package called Main and package.conf doesn't mention the word 
Main.  So why does the error message mention Main?

Any thoughts?

--
Alastair Reid

ps The command is

/usr/local/bin/ghc -H16m -O -Wall -cpp -fglasgow-exts -fffi -Iinclude -package 
haskell98 -package HSgreencard -package-name HSX11 -O -Rghc-timing  -package 
haskell98  -package HSgreencard -split-objs    -c Graphics/X11/Types.hs -o 
Graphics/X11/Types.o  -ohi Graphics/X11/Types.hi -v 2> /tmp/log2 1> /tmp/log1

and I'm including Types.hs, stdout and stderr as attachments
==================== Packages ====================
Package
   {name = "data",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/data"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSdata"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["haskell98", "lang", "util"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "haskell98",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HShaskell98"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "rts",
    auto = False,
    import_dirs = [],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSrts"],
    extra_libraries = ["m", "gmp", "dl"],
    include_dirs = ["/usr/local/lib/ghc-6.1/include"],
    c_includes = ["Stg.h"],
    package_deps = [],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts =
      ["-u",
       "GHCziBase_Izh_static_info",
       "-u",
       "GHCziBase_Czh_static_info",
       "-u",
       "GHCziFloat_Fzh_static_info",
       "-u",
       "GHCziFloat_Dzh_static_info",
       "-u",
       "GHCziPtr_Ptr_static_info",
       "-u",
       "GHCziWord_Wzh_static_info",
       "-u",
       "GHCziInt_I8zh_static_info",
       "-u",
       "GHCziInt_I16zh_static_info",
       "-u",
       "GHCziInt_I32zh_static_info",
       "-u",
       "GHCziInt_I64zh_static_info",
       "-u",
       "GHCziWord_W8zh_static_info",
       "-u",
       "GHCziWord_W16zh_static_info",
       "-u",
       "GHCziWord_W32zh_static_info",
       "-u",
       "GHCziWord_W64zh_static_info",
       "-u",
       "GHCziStable_StablePtr_static_info",
       "-u",
       "GHCziBase_Izh_con_info",
       "-u",
       "GHCziBase_Czh_con_info",
       "-u",
       "GHCziFloat_Fzh_con_info",
       "-u",
       "GHCziFloat_Dzh_con_info",
       "-u",
       "GHCziPtr_Ptr_con_info",
       "-u",
       "GHCziPtr_FunPtr_con_info",
       "-u",
       "GHCziStable_StablePtr_con_info",
       "-u",
       "GHCziBase_False_closure",
       "-u",
       "GHCziBase_True_closure",
       "-u",
       "GHCziPack_unpackCString_closure",
       "-u",
       "GHCziIOBase_stackOverflow_closure",
       "-u",
       "GHCziIOBase_heapOverflow_closure",
       "-u",
       "GHCziIOBase_NonTermination_closure",
       "-u",
       "GHCziIOBase_BlockedOnDeadMVar_closure",
       "-u",
       "GHCziIOBase_Deadlock_closure",
       "-u",
       "GHCziWeak_runFinalizzerBatch_closure",
       "-u",
       "__stginit_Prelude"],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "base",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSbase"],
    extra_libraries = ["HSbase_cbits"],
    include_dirs = [],
    c_includes = ["HsBase.h"],
    package_deps = ["rts"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "network",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSnetwork"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = ["HsNet.h"],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "haskell-src",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HShaskell-src"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["base", "haskell98"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "readline",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSreadline"],
    extra_libraries = ["readline", "ncurses"],
    include_dirs = [],
    c_includes = ["HsReadline.h"],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "unix",
    auto = True,
    import_dirs = ["/usr/local/lib/ghc-6.1/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSunix"],
    extra_libraries = ["HSunix_cbits", "dl"],
    include_dirs = [],
    c_includes = ["HsUnix.h"],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "lang",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/lang"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSlang"],
    extra_libraries = ["HSlang_cbits"],
    include_dirs = [],
    c_includes = ["HsLang.h"],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "concurrent",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/concurrent"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSconcurrent"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["base"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "posix",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/posix"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSposix"],
    extra_libraries = ["HSposix_cbits", "dl"],
    include_dirs = [],
    c_includes = ["HsPosix.h"],
    package_deps = ["lang", "unix"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "util",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/util"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSutil"],
    extra_libraries = ["HSutil_cbits"],
    include_dirs = [],
    c_includes = ["HsUtil.h"],
    package_deps = ["lang", "concurrent", "readline", "posix"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "text",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/text"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HStext"],
    extra_libraries = ["HStext_cbits"],
    include_dirs = [],
    c_includes = ["HsText.h"],
    package_deps = ["lang"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "net",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/net"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HSnet"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["network"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "hssource",
    auto = False,
    import_dirs = ["/usr/local/lib/ghc-6.1/hslibs-imports/hssource"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/ghc-6.1"],
    hs_libraries = ["HShssource"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["haskell-src"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "HSgreencard",
    auto = False,
    import_dirs = ["/usr/local/lib/greencard/ghc"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/greencard/ghc"],
    hs_libraries = ["HSHSgreencard"],
    extra_libraries = [],
    include_dirs = [],
    c_includes = [],
    package_deps = ["haskell98"],
    extra_ghc_opts = [],
    extra_cc_opts = [],
    extra_ld_opts = [],
    framework_dirs = [],
    extra_frameworks = []}
Package
   {name = "HSX11",
    auto = False,
    import_dirs = ["/usr/local/lib/HSX11-1.0/imports"],
    source_dirs = [],
    library_dirs = ["/usr/local/lib/HSX11-1.0"],
    hs_libraries = ["HSHSX11"],
    extra_libraries = ["HSX11_cbits", "X11"],
    include_dirs = [],
    c_includes = [],
    package_deps = ["haskell98", "HSgreencard", "haskell98"],
    extra_ghc_opts = [],
    extra_cc_opts = ["", "-I/usr/X11R6/include"],
    extra_ld_opts = ["", "-L/usr/X11R6/lib"],
    framework_dirs = [],
    extra_frameworks = []}


Glasgow Haskell Compiler, Version 6.1, for Haskell 98, compiled by GHC version 5.04.2
Using package config file: /usr/local/lib/ghc-6.1/package.conf
Hsc static flags: -static -inpackage=HSX11 -fglobalise-toplev-names -fignore-asserts 
-ffoldr-build-on -fdo-eta-reduction -fdo-lambda-eta-expansion -fcase-merge 
-flet-to-case -flet-no-escape
*** C pre-processor
gcc -E -undef -traditional "-v" "-I" "." "-I" "include" "-I" 
"/usr/local/lib/ghc-6.1/include" "-D__HASKELL1__=5" "-D__GLASGOW_HASKELL__=601" 
"-D__HASKELL98__" "-D__CONCURRENT_HASKELL__" "-DDONT_WANT_WIN32_DLL_SUPPORT" "-x" "c" 
"Graphics/X11/Types.hs" "-o" "/tmp/ghc11617.hscpp"
Reading specs from /usr/lib/gcc-lib/i386-linux/3.2.3/specs
Configured with: ../src/configure -v 
--enable-languages=c,c++,java,f77,proto,pascal,objc,ada --prefix=/usr 
--mandir=/usr/share/man --infodir=/usr/share/info 
--with-gxx-include-dir=/usr/include/c++/3.2 --enable-shared --with-system-zlib 
--enable-nls --without-included-gettext --enable-__cxa_atexit --enable-clocale=gnu 
--enable-java-gc=boehm --enable-objc-gc i386-linux
Thread model: posix
gcc version 3.2.3 20030316 (Debian prerelease)
 /usr/lib/gcc-lib/i386-linux/3.2.3/tradcpp0 -lang-c -v -I . -I include -I 
/usr/local/lib/ghc-6.1/include -iprefix /tmp/bin/../lib/gcc-lib/i386-linux/3.2.3/ 
-D__GNUC__=3 -D__GNUC_MINOR__=2 -D__GNUC_PATCHLEVEL__=3 -D__GXX_ABI_VERSION=102 
-D__NO_INLINE__ -D__STDC_HOSTED__=1 -Acpu=i386 -Amachine=i386 -Di386 -D__i386 
-D__i386__ -D__tune_i386__ -D__HASKELL1__=5 -D__GLASGOW_HASKELL__=601 -D__HASKELL98__ 
-D__CONCURRENT_HASKELL__ -DDONT_WANT_WIN32_DLL_SUPPORT Graphics/X11/Types.hs -o 
/tmp/ghc11617.hscpp
GNU traditional CPP version 3.2.3 20030316 (Debian prerelease)
*** Checking old interface for Graphics.X11.Types:
*** Parser:
*** Renamer/typechecker:
*** Desugar:
    Result size = 21466
*** Simplify:
    Result size = 16562
    Result size = 16562
*** Specialise:
    Result size = 16562
*** Float out (not lambdas, not constants):
    Result size = 16562
*** Float inwards:
    Result size = 16562
*** Simplify:
    Result size = 20235
    Result size = 10424
*** Simplify:
    Result size = 10424
*** Simplify:
    Result size = 10424
*** Demand analysis:
    Result size = 10424
*** Worker Wrapper binds:
    Result size = 10424
*** GlomBinds:
*** Simplify:
    Result size = 10424
*** Float out (not lambdas, constants):
    Result size = 11650
*** Common sub-expression:
    Result size = 11650
*** Float inwards:
    Result size = 11650
*** Simplify:
    Result size = 11650
*** Tidy Core:
    Result size = 11650
*** CorePrep:
    Result size = 14108
*** Stg2Stg:
*** CodeGen:
*** CodeOutput:
*** Deleting temp files
Deleting: /tmp/ghc11617.hc /tmp/ghc11617.hspp /tmp/ghc11617.hscpp
Warning: deleting non-existent /tmp/ghc11617.hc
Warning: deleting non-existent /tmp/ghc11617.hspp
ghc-6.1: unknown package name: Main
-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.X11.Xlib.Types
-- Copyright   :  (c) Alastair Reid, 1999-2003
-- License     :  BSD-style (see the file libraries/base/LICENSE)
-- 
-- Maintainer  :  [EMAIL PROTECTED]
-- Stability   :  provisional
-- Portability :  portable
--
-- A collection of type declarations for interfacing with Xlib.
--
-----------------------------------------------------------------------------

module Graphics.X11.Xlib.Types(
        module Graphics.X11.Xlib.Types
        ) where

import Foreign.GreenCard
import Graphics.X11.Types

import Control.Monad( zipWithM_ )
import Foreign(mallocBytes, Storable(..))



----------------------------------------------------------------
-- Types
----------------------------------------------------------------

type Pixel        = Word32
type Position     = Int32
type Dimension    = Word32
type ScreenNumber = Word32
type Byte         = Char
type Buffer       = Int


newtype Display    = Display    (Ptr Stub_Display)
newtype Screen     = Screen     (Ptr Stub_Screen)
newtype Visual     = Visual     (Ptr Stub_Visual)
newtype FontStruct = FontStruct (Ptr Stub_FontStruct)

data Stub_Display
data Stub_Screen
data Stub_Visual
data Stub_FontStruct


type GC = Ptr Stub_GC
data Stub_GC

type Point = 
  ( Position  -- x
  , Position  -- y
  )

type Segment = 
 ( Position -- x1
 , Position -- y1
 , Position -- x2
 , Position -- y2
 )

type Rectangle = 
 ( Position  -- x
 , Position  -- y
 , Dimension -- width
 , Dimension -- height
 )

type Arc =
 ( Position  
 , Position  
 , Dimension 
 , Dimension 
 , Int       
 , Int       
 )

type Color =
 ( Pixel 
 , Word16 
 , Word16 
 , Word16 
 , Word8 
 )

-- We can't use the similarily named library functions for several reasons:
-- 1) They deal with Ptrs instead of Ptr-Len pairs
-- 2) They require instances of Storable but we apply these functions
--    to type synonyms like 'Point = (Int,Int)' which cannot be
--    instances.

type Storable' a = 
  ( a -> Int                    -- sizeOf
  , Ptr a -> Int      -> IO a   -- peekElemOff
  , Ptr a -> Int -> a -> IO ()  -- pokeElemOff
  )

newArray' :: Storable' a -> [a] -> IO (Ptr a, Int)
newArray' (sz,_,wr) xs = do
  p <- mallocBytes (sz undefined * l)
  zipWithM_ (wr p) [0..] xs
  return (p, l)
 where
  l = length xs

peekArray' :: Storable' a -> (Ptr a, Int) -> IO [a]
peekArray' (_,rd,_) (p,l)
  | l <= 0    = return []
  | otherwise = f (l-1) []
 where
  f 0 acc = do e <- rd p 0; return (e:acc)
  f n acc = do e <- rd p n; f (n-1) (e:acc)

-- don't forget to use %end free(arg?) in conjunction with these guys
type ListPoint          = [Point]
type ListRectangle      = [Rectangle]
type ListArc            = [Arc]      
type ListSegment        = [Segment]  
type ListColor          = [Color]    
type ListPixel          = [Pixel]    
type ListWindow         = [Window]   
-- AC, 1/9/2000: Try to define types and marshalling code for Atom lists:
type ListAtom           = [Atom]

s_Pixel :: Storable' Pixel
s_Pixel  = (sizeOf, peekElemOff, pokeElemOff)

s_Window :: Storable' Window
s_Window = (sizeOf, peekElemOff, pokeElemOff)

s_Atom :: Storable' Atom
s_Atom   = (sizeOf, peekElemOff, pokeElemOff)

s_Point :: Storable' Point
s_Point = (const sizeOfPoint,readPoint,writePoint)

writePoint :: Ptr Point -> Int -> Point -> IO ()
writePoint s i gc_arg1 =
  case gc_arg1 of { (gc_arg2,gc_arg3) ->
  prim_writePoint s i gc_arg2 gc_arg3}
foreign import  ccall unsafe "Types_stub_ffi.h prim_writePoint" prim_writePoint :: Ptr 
a1 -> Int -> Int32 -> Int32 -> IO ()

readPoint :: Ptr Point -> Int -> IO Point
readPoint s i =
  prim_readPoint s i
  >>= \ gc_result ->
  access_prim_readPoint_gc_res1 gc_result >>= \ gc_res1 ->
  access_prim_readPoint_gc_res2 gc_result >>= \ gc_res2 ->
  (return ((gc_res1,gc_res2)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_readPoint" prim_readPoint :: Ptr 
a1 -> Int -> IO (Ptr r1)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readPoint_gc_res1 :: Ptr a1 
-> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readPoint_gc_res2 :: Ptr a1 
-> IO (Int32)

sizeOfPoint :: Int
sizeOfPoint =
  unsafePerformIO(
    prim_sizeOfPoint
    >>= \  res1  ->
    (return (res1)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_sizeOfPoint" prim_sizeOfPoint :: 
IO (Int)

s_Rectangle :: Storable' Rectangle
s_Rectangle = (const sizeOfRectangle, readRectangle, writeRectangle )

writeRectangle :: Ptr Rectangle -> Int -> Rectangle -> IO ()
writeRectangle s i gc_arg1 =
  case gc_arg1 of { (gc_arg2,gc_arg3,gc_arg4,gc_arg5) ->
  prim_writeRectangle s i gc_arg2 gc_arg3 gc_arg4 gc_arg5}
foreign import  ccall unsafe "Types_stub_ffi.h prim_writeRectangle" 
prim_writeRectangle :: Ptr a1 -> Int -> Int32 -> Int32 -> Word32 -> Word32 -> IO ()

readRectangle :: Ptr Rectangle -> Int -> IO Rectangle
readRectangle s i =
  prim_readRectangle s i
  >>= \ gc_result ->
  access_prim_readRectangle_gc_res1 gc_result >>= \ gc_res1 ->
  access_prim_readRectangle_gc_res2 gc_result >>= \ gc_res2 ->
  access_prim_readRectangle_gc_res3 gc_result >>= \ gc_res3 ->
  access_prim_readRectangle_gc_res4 gc_result >>= \ gc_res4 ->
  (return ((gc_res1,gc_res2,gc_res3,gc_res4)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_readRectangle" prim_readRectangle 
:: Ptr a1 -> Int -> IO (Ptr r1)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readRectangle_gc_res1 :: 
Ptr a1 -> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readRectangle_gc_res2 :: 
Ptr a1 -> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readRectangle_gc_res3 :: 
Ptr a1 -> IO (Word32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readRectangle_gc_res4 :: 
Ptr a1 -> IO (Word32)

sizeOfRectangle :: Int
sizeOfRectangle =
  unsafePerformIO(
    prim_sizeOfRectangle
    >>= \  res1  ->
    (return (res1)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_sizeOfRectangle" 
prim_sizeOfRectangle :: IO (Int)


s_Arc :: Storable' Arc
s_Arc = (const sizeOfArc, readArc, writeArc )

writeArc :: Ptr Arc -> Int -> Arc -> IO ()
writeArc s i gc_arg1 =
  case gc_arg1 of { (gc_arg2,gc_arg3,gc_arg4,gc_arg5,gc_arg6,gc_arg7) ->
  prim_writeArc s i gc_arg2 gc_arg3 gc_arg4 gc_arg5 gc_arg6 gc_arg7}
foreign import  ccall unsafe "Types_stub_ffi.h prim_writeArc" prim_writeArc :: Ptr a1 
-> Int -> Int32 -> Int32 -> Word32 -> Word32 -> Int -> Int -> IO ()

readArc :: Ptr Arc -> Int -> IO Arc
readArc s i =
  prim_readArc s i
  >>= \ gc_result ->
  access_prim_readArc_gc_res1 gc_result >>= \ gc_res1 ->
  access_prim_readArc_gc_res2 gc_result >>= \ gc_res2 ->
  access_prim_readArc_gc_res3 gc_result >>= \ gc_res3 ->
  access_prim_readArc_gc_res4 gc_result >>= \ gc_res4 ->
  access_prim_readArc_gc_res5 gc_result >>= \ gc_res5 ->
  access_prim_readArc_gc_res6 gc_result >>= \ gc_res6 ->
  (return ((gc_res1,gc_res2,gc_res3,gc_res4,gc_res5,gc_res6)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_readArc" prim_readArc :: Ptr a1 -> 
Int -> IO (Ptr r1)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res1 :: Ptr a1 
-> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res2 :: Ptr a1 
-> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res3 :: Ptr a1 
-> IO (Word32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res4 :: Ptr a1 
-> IO (Word32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res5 :: Ptr a1 
-> IO (Int)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readArc_gc_res6 :: Ptr a1 
-> IO (Int)

sizeOfArc :: Int
sizeOfArc =
  unsafePerformIO(
    prim_sizeOfArc
    >>= \  res1  ->
    (return (res1)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_sizeOfArc" prim_sizeOfArc :: IO 
(Int)


s_Segment :: Storable' Segment
s_Segment = (const sizeOfSegment, readSegment, writeSegment )

writeSegment :: Ptr Segment -> Int -> Segment -> IO ()
writeSegment s i gc_arg1 =
  case gc_arg1 of { (gc_arg2,gc_arg3,gc_arg4,gc_arg5) ->
  prim_writeSegment s i gc_arg2 gc_arg3 gc_arg4 gc_arg5}
foreign import  ccall unsafe "Types_stub_ffi.h prim_writeSegment" prim_writeSegment :: 
Ptr a1 -> Int -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()

readSegment :: Ptr Segment -> Int -> IO Segment
readSegment s i =
  prim_readSegment s i
  >>= \ gc_result ->
  access_prim_readSegment_gc_res1 gc_result >>= \ gc_res1 ->
  access_prim_readSegment_gc_res2 gc_result >>= \ gc_res2 ->
  access_prim_readSegment_gc_res3 gc_result >>= \ gc_res3 ->
  access_prim_readSegment_gc_res4 gc_result >>= \ gc_res4 ->
  (return ((gc_res1,gc_res2,gc_res3,gc_res4)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_readSegment" prim_readSegment :: 
Ptr a1 -> Int -> IO (Ptr r1)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readSegment_gc_res1 :: Ptr 
a1 -> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readSegment_gc_res2 :: Ptr 
a1 -> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readSegment_gc_res3 :: Ptr 
a1 -> IO (Int32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readSegment_gc_res4 :: Ptr 
a1 -> IO (Int32)

sizeOfSegment :: Int
sizeOfSegment =
  unsafePerformIO(
    prim_sizeOfSegment
    >>= \  res1  ->
    (return (res1)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_sizeOfSegment" prim_sizeOfSegment 
:: IO (Int)


s_Color :: Storable' Color
s_Color = (const sizeOfColor, readColor, writeColor )

writeColor :: Ptr Color -> Int -> Color -> IO ()
writeColor s i gc_arg1 =
  case gc_arg1 of { (gc_arg2,gc_arg3,gc_arg4,gc_arg5,gc_arg6) ->
  prim_writeColor s i gc_arg2 gc_arg3 gc_arg4 gc_arg5 gc_arg6}
foreign import  ccall unsafe "Types_stub_ffi.h prim_writeColor" prim_writeColor :: Ptr 
a1 -> Int -> Word32 -> Word16 -> Word16 -> Word16 -> Word8 -> IO ()

readColor :: Ptr Color -> Int -> IO Color
readColor s i =
  prim_readColor s i
  >>= \ gc_result ->
  access_prim_readColor_gc_res1 gc_result >>= \ gc_res1 ->
  access_prim_readColor_gc_res2 gc_result >>= \ gc_res2 ->
  access_prim_readColor_gc_res3 gc_result >>= \ gc_res3 ->
  access_prim_readColor_gc_res4 gc_result >>= \ gc_res4 ->
  access_prim_readColor_gc_res5 gc_result >>= \ gc_res5 ->
  (return ((gc_res1,gc_res2,gc_res3,gc_res4,gc_res5)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_readColor" prim_readColor :: Ptr 
a1 -> Int -> IO (Ptr r1)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readColor_gc_res1 :: Ptr a1 
-> IO (Word32)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readColor_gc_res2 :: Ptr a1 
-> IO (Word16)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readColor_gc_res3 :: Ptr a1 
-> IO (Word16)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readColor_gc_res4 :: Ptr a1 
-> IO (Word16)
foreign import ccall unsafe "Types_stub_ffi.h" access_prim_readColor_gc_res5 :: Ptr a1 
-> IO (Word8)

sizeOfColor :: Int
sizeOfColor =
  unsafePerformIO(
    prim_sizeOfColor
    >>= \  res1  ->
    (return (res1)))
foreign import  ccall unsafe "Types_stub_ffi.h prim_sizeOfColor" prim_sizeOfColor :: 
IO (Int)

type XSetWindowAttributesPtr = Ptr Stub_SWA
data Stub_SWA
--  toXSetWindowAttributesPtr   :: Addr -> XSetWindowAttributesPtr,
--  fromXSetWindowAttributesPtr :: XSetWindowAttributesPtr -> Ptr

----------------------------------------------------------------
-- End
----------------------------------------------------------------

Reply via email to