{-# LANGUAGE ForeignFunctionInterface #-} -- | -- Module : Mac.Carbon -- Maintainer : Yakov Z <> -- Stability : experimental -- module Mac.Carbon ( OSType, -- * Error Handler OSErr, OSStatus, -- * Window Manager WindowClass, WindowAttributes, Rect(..), WindowRef, CGrafPtr, kDocumentWindowClass, kWindowNoAttributes, -- ** Creating, Storing, and Closing Windows createNewWindow, -- ** Displaying Windows showWindow, -- ** Getting and Setting Window Structure Fields getWindowPort, -- * Component Manager -- ** Opening and Closing Components openDefaultComponent, -- * Memory Manager Handle, Size, -- ** Allocating and Releasing Relocatable Blocks of Memory disposeHandle, newHandle, TimeValue, Boolean, true, false, button ) where import Foreign.Ptr import Foreign.C.Types import Foreign.Storable #include -- | A numeric code used in Carbon to idndicate the return status of a function. -- -- Declared in IOMacOSTypes.h type OSErr = CShort -- | A numeric code used in Carbon to indicate the return status of a function. -- -- Declared in OSTypes.h type OSStatus = CInt type WindowClass = CInt kDocumentWindowClass :: WindowClass kDocumentWindowClass = (#const kDocumentWindowClass) type WindowAttributes = CInt kWindowNoAttributes :: WindowAttributes kWindowNoAttributes = (#const kWindowNoAttributes) data Rect = Rect { top :: CShort, left :: CShort, bottom :: CShort, right :: CShort } instance Storable Rect where sizeOf _ = #const sizeof(Rect) alignment _ = alignment (undefined :: CInt) -- ??? peek _ = error "Storable.peek(MacTypes.Rect) not implemented" poke p (Rect top' left' bottom' right') = do (#poke Rect, top) p top' (#poke Rect, left) p left' (#poke Rect, bottom) p bottom' (#poke Rect, right) p right' type CGrafPtr = Ptr () type WindowRef = Ptr () type OSType = CLong -- | type Handle = Ptr () type Size = CLong type Boolean = CInt type TimeValue = CInt true, false :: Boolean true = #const true false = #const false -- | Creates a window from parameter data. foreign import ccall unsafe "CreateNewWindow" createNewWindow :: WindowClass -> WindowAttributes -> {- const -} Ptr (Rect) -> Ptr (WindowRef) -> IO OSStatus -- | Make an invisible window visible. foreign import ccall unsafe "ShowWindow" showWindow :: WindowRef -> IO () foreign import ccall unsafe "GetWindowPort" getWindowPort :: WindowRef -> IO CGrafPtr -- | Opens a connection to a registered component of the component type and subtype specified by your application. foreign import ccall unsafe "OpenDefaultComponent" openDefaultComponent :: OSType -> OSType -> IO (Ptr a) -- | Allocates a new relocatable memory block of a specified size in the current heap zone. foreign import ccall unsafe "NewHandle" newHandle :: Size -> IO Handle -- | Releases memory occupied by a relocatable block. foreign import ccall unsafe "DisposeHandle" disposeHandle :: Handle -> IO () -- | foreign import ccall unsafe "Button" button :: IO Boolean