-- |Partial binding to CoreFoundation. -- At the moment only CFString is supported. {-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls #-} module System.MacOSX.CoreFoundation ( -- * types UInt8 , UInt16 , UInt32 , UInt64 , SInt8 , SInt16 , SInt32 , SInt64 , OSErr , OSStatus , UniChar , CFIndex , ItemCount , ByteCount -- , CFString , CFDataRef , CFStringRef , CFAllocatorRef , Boolean , Float32 , Float64 -- * CFString , newCFString , releaseCFString , peekCFString , withCFString -- * OSStatus , osStatusString , osStatusError , osStatusReport ) where -------------------------------------------------------------------------------- import Data.Bits import Data.Char import Data.Word import Data.Int import Control.Monad import Foreign import Foreign.C import Foreign.Marshal -------------------------------------------------------------------------------- type UInt8 = Word8 type UInt16 = Word16 type UInt32 = Word32 type UInt64 = Word64 type SInt8 = Int8 type SInt16 = Int16 type SInt32 = Int32 type SInt64 = Int64 type OSErr = SInt16 type OSStatus = SInt32 type Boolean = Bool type Float32 = Float type Float64 = Double type UniChar = UInt16 -- utf16 char, not utf32 !!! type CFIndex = SInt32 type ItemCount = UInt32 type ByteCount = UInt32 data CFData data CFString data CFAllocator type CFDataRef = Ptr CFData type CFStringRef = Ptr CFString type CFAllocatorRef = Ptr CFAllocator -------------------------------------------------------------------------------- kCFAllocatorDefault :: CFAllocatorRef kCFAllocatorDefault = nullPtr ----- error "handling" :) ----- osStatusString :: OSStatus -> String osStatusString osstatus = "OSStatus = " ++ show osstatus osStatusError :: OSStatus -> IO a osStatusError osstatus = fail $ osStatusString osstatus osStatusReport :: OSStatus -> IO () osStatusReport osstatus = when (osstatus/=0) $ putStrLn $ osStatusString osstatus ----- Base ----- -- CFDataRef CFDataCreate ( CFAllocatorRef allocator, const UInt8 *bytes, CFIndex length ); foreign import ccall unsafe "CFBase.h CFDataCreate" c_CFDataCreate :: CFAllocatorRef -> Ptr UInt8 -> CFIndex -> IO CFDataRef foreign import ccall unsafe "CFBase.h CFRelease" c_CFRelease :: Ptr a -> IO () ----- CFStrings ----- foreign import ccall unsafe "CFString.h CFStringGetLength" c_CFStringGetLength :: CFStringRef -> IO CFIndex foreign import ccall unsafe "CFString.h CFStringGetCharactersPtr" c_CFStringGetCharactersPtr :: CFStringRef -> IO (Ptr UniChar) foreign import ccall unsafe "CFString.h CFStringGetCharacterAtIndex" c_CFStringGetCharacterAtIndex :: CFStringRef -> CFIndex -> IO UniChar foreign import ccall unsafe "CFString.h CFStringCreateWithCharacters" c_CFStringCreateWithCharacters :: CFAllocatorRef -> Ptr UniChar -> CFIndex -> IO CFStringRef -- | Manually releasing a CFString. releaseCFString :: CFStringRef -> IO () releaseCFString = c_CFRelease -- | Peeks a CFString. peekCFString :: CFStringRef -> IO String peekCFString cfstring = do n <- c_CFStringGetLength cfstring p <- c_CFStringGetCharactersPtr cfstring -- print (n,p) if p /= nullPtr then forM [0..n-1] $ \i -> liftM (chr . fromIntegral) $ peekElemOff p (fromIntegral i) else forM [0..n-1] $ \i -> liftM (chr . fromIntegral) $ c_CFStringGetCharacterAtIndex cfstring i -- | Creates a new CFString. You have to release it manually. newCFString :: String -> IO CFStringRef newCFString string = do let n = length string allocaArray n $ \p -> do pokeArray p [ fromIntegral (ord c) | c <- string ] c_CFStringCreateWithCharacters kCFAllocatorDefault p (fromIntegral n) -- | Safe passing of a CFString to the OS (releases it afterwards). withCFString :: String -> (CFStringRef -> IO a) -> IO a withCFString string action = do cfstring <- newCFString string x <- action cfstring releaseCFString cfstring return x --------------------------------------------------------------------------------