You can subscribe to this list here.
2004 |
Jan
|
Feb
|
Mar
|
Apr
|
May
(127) |
Jun
(1) |
Jul
|
Aug
|
Sep
|
Oct
|
Nov
|
Dec
(6) |
---|---|---|---|---|---|---|---|---|---|---|---|---|
2005 |
Jan
|
Feb
|
Mar
(35) |
Apr
(23) |
May
|
Jun
(1) |
Jul
(48) |
Aug
(23) |
Sep
(10) |
Oct
(4) |
Nov
|
Dec
|
2006 |
Jan
|
Feb
|
Mar
(27) |
Apr
|
May
|
Jun
|
Jul
|
Aug
|
Sep
|
Oct
|
Nov
(7) |
Dec
|
2007 |
Jan
|
Feb
(16) |
Mar
(2) |
Apr
|
May
|
Jun
|
Jul
|
Aug
|
Sep
|
Oct
|
Nov
|
Dec
|
2008 |
Jan
|
Feb
|
Mar
|
Apr
|
May
|
Jun
|
Jul
|
Aug
|
Sep
(19) |
Oct
(25) |
Nov
(8) |
Dec
(25) |
2009 |
Jan
(6) |
Feb
(1) |
Mar
|
Apr
|
May
|
Jun
|
Jul
|
Aug
(25) |
Sep
(2) |
Oct
|
Nov
|
Dec
|
2010 |
Jan
|
Feb
|
Mar
|
Apr
|
May
|
Jun
(3) |
Jul
|
Aug
|
Sep
|
Oct
|
Nov
|
Dec
|
From: <cod...@go...> - 2010-06-18 00:35:17
|
Revision: 415 Author: wol...@gm... Date: Thu Jun 17 17:23:58 2010 Log: Fix Setup.hs http://code.google.com/p/hoc/source/detail?r=415 Modified: /trunk/hoc/Setup.hs ======================================= --- /trunk/hoc/Setup.hs Sun Sep 27 03:32:50 2009 +++ /trunk/hoc/Setup.hs Thu Jun 17 17:23:58 2010 @@ -81,7 +81,7 @@ -- system_libs = gnustepsysroot </> "Library/Libraries" return (gcclibdir, system_libs, system_headers) -customConfig :: (Either GenericPackageDescription PackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo +customConfig :: (GenericPackageDescription, HookedBuildInfo) -> ConfigFlags -> IO LocalBuildInfo customConfig pdbi cf = do cf <- setObjC2Flag cf |
From: <cod...@go...> - 2010-06-18 00:32:21
|
Revision: 416 Author: wol...@gm... Date: Thu Jun 17 17:26:14 2010 Log: Apply the relevant part of fix-bindings.patch as supplied by bickfordb to allow people to select their Mac OS X SDK via an environment variable when creating bindings. Also update the README accordingly. http://code.google.com/p/hoc/source/detail?r=416 Modified: /trunk/hoc/Bindings/make-bindings-macos.sh /trunk/hoc/README.txt ======================================= --- /trunk/hoc/Bindings/make-bindings-macos.sh Sun Oct 19 13:32:25 2008 +++ /trunk/hoc/Bindings/make-bindings-macos.sh Thu Jun 17 17:26:14 2010 @@ -1,3 +1,4 @@ +set -x function build() { pushd HOC-$1 @@ -10,7 +11,12 @@ ARGUMENTS=$* OPTS= -IFGEN=hoc-ifgen +IFGEN="hoc-ifgen" + +if [ "$HOC_SDK" != "" ]; +then + IFGEN="$IFGEN -s $HOC_SDK" +fi set -e mkdir -p Generated ======================================= --- /trunk/hoc/README.txt Sun Sep 27 03:10:58 2009 +++ /trunk/hoc/README.txt Thu Jun 17 17:26:14 2010 @@ -51,7 +51,7 @@ 2. Create the bindings: cd Bindings - sudo sh make-bindings-macos.sh + sudo HOC_SDK=MacOSX10.5 sh make-bindings-macos.sh cd .. 3. Build the hoc-wrap tool: |
From: <cod...@go...> - 2010-06-18 00:27:13
|
Revision: 414 Author: wol...@gm... Date: Thu Jun 17 17:23:19 2010 Log: Apply a mixture of patches contributed by pedromartins.pt and Torsten Kemps-Benedix to fix issue 23 and its duplicate, issue 25. http://code.google.com/p/hoc/source/detail?r=414 Modified: /trunk/hoc/HOC/HOC/CannedCIFs.hs /trunk/hoc/HOC/HOC/DeclareClass.hs /trunk/hoc/HOC/HOC/DeclareSelector.hs /trunk/hoc/HOC/HOC/FFICallInterface.hs /trunk/hoc/HOC/HOC/ID.hs /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs /trunk/hoc/InterfaceGenerator2/ExpandSynonyms.hs /trunk/hoc/InterfaceGenerator2/THTraversal.hs ======================================= --- /trunk/hoc/HOC/HOC/CannedCIFs.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/CannedCIFs.hs Thu Jun 17 17:23:19 2010 @@ -14,6 +14,8 @@ import Foreign.C import Language.Haskell.TH +import Control.Arrow + -- removes all foralls (leaving in type variables) and de-sugars all type -- synonyms. expandSynonyms :: Type -> Q Type @@ -77,58 +79,14 @@ = ForallT names cxt (substTy mapping' t) where mapping' = filter (not . (`elem` names) . fst) mapping substTy mapping (VarT name) - = fromMaybe (VarT name) (lookup name mapping) + = fromMaybe (VarT name) (lookup name (map (first extractName) mapping)) substTy mapping (AppT a b) = AppT (substTy mapping a) (substTy mapping b) substTy _ other = other -expandSynonymsOrig - = flip expandSynonyms1 [] - where - -- unwrap the AppT, expand b, push b' onto the pending list - expandSynonyms1 (AppT a b) pending - = do - b' <- expandSynonyms1 b [] - expandSynonyms1 a (b' : pending) - -- grab the types, expand them, then fold up the expanded types - -- and everything that is pending (thus removing the ForallT) - expandSynonyms1 (ForallT vars ctx t) pending - = do - t' <- expandSynonyms1 t [] - return $ foldl AppT t' pending - -- n is a type synonym, removed it by substuting pending arguments - expandSynonyms1 (ConT n) pending - = do - info <- reify n - case info of - TyConI (TySynD _ args body) -> - expandSynonyms1 (substTy taken body) rest - where - taken = zip args pending - rest = drop (length taken) pending - _ -> return $ foldl AppT (ConT n) pending - -- this is the simple type termination condition. - -- return Q (AppT (AppT A B) C) - -- which is to say ((A B) C) - expandSynonyms1 other pending -- VarT, TupleT, ArrowT, ListT - = return $ foldl AppT other pending - - -- use mapping to replace all occurances of types. - -- the ForallT has to exclude names that were used as polymorphic type - -- names, since they are unrelated to the types we're intended to - -- substitute. - substTy mapping (ForallT names cxt t) - = ForallT names cxt (substTy mapping' t) - where mapping' = filter (not . (`elem` names) . fst) mapping - substTy mapping (VarT name) - = case lookup name mapping of - Just t -> t - Nothing -> VarT name - substTy mapping (AppT a b) - = AppT (substTy mapping a) (substTy mapping b) - substTy _ other - = other +extractName (PlainTV n) = n +extractName (KindedTV n _) = n toplevelConstructor (AppT a b) = toplevelConstructor a @@ -166,9 +124,6 @@ --runIO (putStrLn "Input" >> ppQ qt >> putStrLn "expandSynonyms:") t <- expandSynonyms =<< qt --runIO (ppAST t) - --t' <- expandSynonymsOrig =<< qt - --runIO (putStrLn "expandSynonymsOrig:" >> ppAST t) - --assertQ (t == t') "t and t' are not equal" -- arrowsToList -- -- converts a type of a->b->c->d-> IO e to an ======================================= --- /trunk/hoc/HOC/HOC/DeclareClass.hs Thu Aug 20 17:27:38 2009 +++ /trunk/hoc/HOC/HOC/DeclareClass.hs Thu Jun 17 17:23:19 2010 @@ -16,25 +16,25 @@ declareClass name super = sequence $ [ -- data $(phantomName) a - dataD (cxt []) (mkName phantomName) [mkName "a"] + dataD (cxt []) (mkName phantomName) [PlainTV (mkName "a")] -- the constructor is only here to work around -- GHC sourceforge bug #1244882. [return $ NormalC (mkName (phantomName ++ "dummy")) []] [], -- type $(name) a = $(super) ($(phantomName) a) - tySynD (mkName name) [mkName "a"] + tySynD (mkName name) [PlainTV (mkName "a")] (conT (mkName super) `appT` (conT (mkName phantomName) `appT` varT (mkName "a"))), -- type $(metaClassName) a = $(superMetaClassName) ($(phantomName) a) - tySynD (mkName metaClassName) [mkName "a"] + tySynD (mkName metaClassName) [PlainTV (mkName "a")] (conT (mkName superMetaClassName) `appT` (conT (mkName phantomName) `appT` varT (mkName "a"))), -- type $(metaMetaClassName) a = $(superMetaMetaClassName) ($(phantomName) a) - tySynD (mkName metaMetaClassName) [mkName "a"] + tySynD (mkName metaMetaClassName) [PlainTV (mkName "a")] (conT (mkName superMetaMetaClassName) `appT` (conT (mkName phantomName) `appT` varT (mkName "a"))), ======================================= --- /trunk/hoc/HOC/HOC/DeclareSelector.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/DeclareSelector.hs Thu Jun 17 17:23:19 2010 @@ -143,12 +143,12 @@ retained, liftForalls $ (if needInstance - then ForallT (map mkName ["target", "inst"]) - [ConT (mkName className) `AppT` VarT (mkName "target"), - ConT (mkName "ClassAndObject") - `AppT` VarT (mkName "target") `AppT` VarT (mkName "inst")] - else ForallT [mkName "target"] - [ConT (mkName className) `AppT` VarT (mkName "target")]) $ + then ForallT (map (PlainTV . mkName) ["target", "inst"]) + [ClassP (mkName className) [VarT (mkName "target")], + ClassP (mkName "ClassAndObject") [VarT (mkName "target"), + VarT (mkName "inst")]] + else ForallT [PlainTV $ mkName "target"] + [ClassP (mkName className) [VarT (mkName "target")]]) $ replaceResult ( (ArrowT `AppT` (fromMaybe (VarT $ mkName "target") targetType)) `AppT` covariantResult @@ -257,15 +257,15 @@ |]) [], -- type $(imptypeName) target inst = arg1 -> arg2 -> target -> IO result - tySynD (mkName imptypeName) (map mkName ["target","inst"]) + tySynD (mkName imptypeName) (map (PlainTV . mkName) ["target","inst"]) (return $ makeImpType typeSig), -- class Object a => $(className) a - classD (cxt [conT ''MessageTarget `appT` varT (mkName "a")]) - (mkName className) [mkName "a"] [] [], + classD (cxt [classP ''MessageTarget [varT (mkName "a")]]) + (mkName className) [PlainTV $ mkName "a"] [] [], -- instance $(className) a => $(className) (SuperTarget a) - instanceD (cxt [conT (mkName className) `appT` varT (mkName "a")]) + instanceD (cxt [classP (mkName className) [varT (mkName "a")]]) (conT (mkName className) `appT` (conT ''SuperTarget `appT` varT (mkName "a"))) [], ======================================= --- /trunk/hoc/HOC/HOC/FFICallInterface.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/FFICallInterface.hs Thu Jun 17 17:23:19 2010 @@ -133,8 +133,6 @@ makeFFIType _ = return ffi_type_float instance FFITypeable CDouble where makeFFIType _ = return ffi_type_double -instance FFITypeable CLDouble where - makeFFIType _ = return ffi_type_longdouble -- ### FIXME: this should be autoconfigured. -- The following are correct for Mac OS X ======================================= --- /trunk/hoc/HOC/HOC/ID.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/ID.hs Thu Jun 17 17:23:19 2010 @@ -1,4 +1,4 @@ -{-# LANGUAGE ForeignFunctionInterface, RecursiveDo, +{-# LANGUAGE ForeignFunctionInterface, DoRec, MultiParamTypeClasses, FlexibleInstances #-} module HOC.ID where @@ -196,15 +196,17 @@ -- notice that wptr's finalizer definition requires new_sptr, which -- cannot be created till after the wptr; -- so we use 'mdo' (it's much more pratical than fixM) -makeNewHSO immortal p = mdo - haskellData <- makeNewHaskellData p - dPutWords ["got haskell data", show haskellData] - let haskellObj = HSO p (fromMaybe [] haskellData) - finalizer | immortal = Nothing - | otherwise = Just $ finalizeID p new_sptr - wptr <- mkWeakPtr haskellObj finalizer - new_sptr <- newStablePtr wptr - setHaskellPart p new_sptr (if immortal then 1 else 0) +makeNewHSO immortal p = + do + rec + haskellData <- makeNewHaskellData p + dPutWords ["got haskell data", show haskellData] + let haskellObj = HSO p (fromMaybe [] haskellData) + finalizer | immortal = Nothing + | otherwise = Just $ finalizeID p new_sptr + wptr <- mkWeakPtr haskellObj finalizer + new_sptr <- newStablePtr wptr + setHaskellPart p new_sptr (if immortal then 1 else 0) return haskellObj finalizeID :: Ptr ObjCObject -> StablePtr (Weak HSO) -> IO () ======================================= --- /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs Thu Jun 17 17:23:19 2010 @@ -27,7 +27,7 @@ gput0 = case constrRep (toConstr thing) of IntConstr i -> put i FloatConstr f -> put f - StringConstr s -> put s + CharConstr c -> put c AlgConstr i -> do putWord8 (fromIntegral i) gmapM (\x -> gput x >> return x) thing @@ -53,9 +53,9 @@ FloatRep -> do f <- get return $ mkFloatConstr dataType f - StringRep -> do - s <- get - return $ mkStringConstr dataType s + CharRep -> do + c <- get + return $ mkCharConstr dataType c AlgRep constrs -> do i <- getWord8 return (constrs !! (fromIntegral i - 1)) ======================================= --- /trunk/hoc/InterfaceGenerator2/ExpandSynonyms.hs Sun Dec 23 16:43:07 2007 +++ /trunk/hoc/InterfaceGenerator2/ExpandSynonyms.hs Thu Jun 17 17:23:19 2010 @@ -3,6 +3,10 @@ import Language.Haskell.TH +import Control.Arrow + +extractName (PlainTV n) = n +extractName (KindedTV n _) = n expandSynonyms typ = typ >>= flip expandSynonyms1 [] where @@ -33,7 +37,7 @@ = ForallT names cxt (substTy mapping' t) where mapping' = filter (not . (`elem` names) . fst) mapping substTy mapping (VarT name) - = case lookup name mapping of + = case lookup name (map (first extractName) mapping) of Just t -> t Nothing -> VarT name substTy mapping (AppT a b) ======================================= --- /trunk/hoc/InterfaceGenerator2/THTraversal.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/InterfaceGenerator2/THTraversal.hs Thu Jun 17 17:23:19 2010 @@ -5,6 +5,7 @@ import Control.Monad.State import qualified Data.Map as Map +import Data.List import ExpandSynonyms @@ -47,7 +48,7 @@ --let conNames = map conName cons - let environment' = Map.fromList (zip (map nameBaseWorkaround argNames) argTypes) + let environment' = Map.fromList (zip (map nameBaseWorkaround (map extractName argNames)) argTypes) `Map.union` environment log $ "dataD " ++ show n ++ " " ++ show environment' matches <- mapM (makeCaseForCon environment') cons @@ -143,10 +144,17 @@ loop (AppT ty arg) args = loop ty (arg : args) loop ty0 args = (ty0, args) + expandVars :: Map.Map String Type -> Type -> Type expandVars environment (ForallT names cxt ty) - = ForallT names (map (expandVars environment') cxt) $ expandVars environment' ty + = ForallT names (map (buildPred . expandVars environment') (map extractCxt cxt)) $ expandVars environment' ty where - environment' = foldr Map.delete environment $ map nameBaseWorkaround names + buildPred t = let buildPredTypes (AppT (ConT n) t) = [t] + buildPredTypes (AppT a@(AppT _ _) t) = t:(buildPredTypes a) + extractName (AppT (ConT n) _) = n + extractName (AppT a _) = extractName a + in ClassP (extractName t) (buildPredTypes t) + extractCxt (ClassP n ts) = foldl' AppT (ConT n) ts + environment' = foldr Map.delete environment $ map (nameBaseWorkaround . extractName) names expandVars environment (VarT name) = case Map.lookup (nameBaseWorkaround name) environment of Just ty -> ty |
From: <cod...@go...> - 2009-09-27 10:33:26
|
Revision: 413 Author: wol...@gm... Date: Sun Sep 27 03:32:50 2009 Log: Fix build issue on Snow Leopard by forcing 32-bit mode for cbits build (issue #22) Thanks to AntoineVanGelderJnr for the patch. http://code.google.com/p/hoc/source/detail?r=413 Modified: /trunk/hoc/Setup.hs ======================================= --- /trunk/hoc/Setup.hs Mon Aug 17 15:34:07 2009 +++ /trunk/hoc/Setup.hs Sun Sep 27 03:32:50 2009 @@ -174,7 +174,7 @@ ++ ["-l" ++ lib | lib <- extraLibs buildInfo] ++ ["-framework " ++ fw | fw <- frameworks buildInfo] - let cmd = "gcc -r -nostdlib -I`ghc --print-libdir`/include " + let cmd = "gcc -m32 -r -nostdlib -I`ghc --print-libdir`/include " ++ unwords cflags ++ " HOC_cbits/*.m -o " ++ cbitsObjectFile |
From: <cod...@go...> - 2009-09-27 10:12:26
|
Revision: 412 Author: wol...@gm... Date: Sun Sep 27 03:10:58 2009 Log: fix build instructions (issue #21) http://code.google.com/p/hoc/source/detail?r=412 Modified: /trunk/hoc/README.txt ======================================= --- /trunk/hoc/README.txt Tue Aug 11 13:37:27 2009 +++ /trunk/hoc/README.txt Sun Sep 27 03:10:58 2009 @@ -37,36 +37,35 @@ 1. Build the HOC library and the interface generator: - cabal configure - cabal build - cabal install + runhaskell Setup.hs configure + runhaskell Setup.hs build + sudo runhaskell Setup.hs install To run the unit tests, use: - cabal configure -fTests - cabal build + runhaskell Setup.hs configure -fTests + runhaskell Setup.hs build ./dist/build/hoc-test/hoc-test - cabal install + sudo runhaskell Setup.hs install 2. Create the bindings: cd Bindings - sh make-bindings-macos.sh + sudo sh make-bindings-macos.sh cd .. 3. Build the hoc-wrap tool: cd Tools - cabal configure - cabal build - cabal install + runhaskell Setup.hs configure + runhaskell Setup.hs build + sudo runhaskell Setup.hs install cd .. -Depending on your setup, you will need to add "sudo" in front of the -"cabal install" commands and in front of the make-bindings command. -You can also add additional Cabal configure options after "cabal configure" -and after "sh make-bindings-macos.sh". +Depending on your setup, you might be able to leae out the "sudo". +You can also add additional Cabal configure options after "configure" +commands, and after "sh make-bindings-macos.sh" (like, e.g. --user). Authors ======= |
From: <cod...@go...> - 2009-08-23 08:57:54
|
Revision: 411 Author: wol...@gm... Date: Sun Aug 23 01:56:37 2009 Log: improve handling of backslashes and comments in the preprocessor multi-line preprocessor directives no longer mess up line numbers. multi-line comments in multi-line preprocessor directives no longer cause trouble. http://code.google.com/p/hoc/source/detail?r=411 Modified: /trunk/hoc/InterfaceGenerator2/Preprocessor.hs /trunk/hoc/Tests/TestPreprocessor.hs ======================================= --- /trunk/hoc/InterfaceGenerator2/Preprocessor.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/InterfaceGenerator2/Preprocessor.hs Sun Aug 23 01:56:37 2009 @@ -144,6 +144,7 @@ unblockComments ('/' : '*' : xs) = "/*" ++ handleComment xs where handleComment ('*' : '/' : xs) = "*/" ++ unblockComments xs + handleComment ('\\': '\n' : xs) = "*/\\\n/*" ++ handleComment xs handleComment ('\n' : xs) = "*/\n/*" ++ handleComment xs handleComment (c : xs) = c : handleComment xs handleComment [] = [] @@ -153,14 +154,26 @@ parseDirectives = map (\l -> case parse line "" l of Left e -> Text $ l ++ "// " ++ show (show e) Right x -> x) . handleBackslashes . lines . unblockComments - -handleBackslashes [] = [] -handleBackslashes (l : ls) - | null l = [] : handleBackslashes ls - | last l == '\\' = case handleBackslashes ls of - (l2 : ls') -> (l ++ '\n' : l2) : ls' - ls' -> ls' - | otherwise = l : handleBackslashes ls + +handleBackslashes = f . map reverse where + f :: [String] -> [String] + f [] = [] + f ls@(firstLine:otherLines) + | null backslashed = reverse firstLine : f otherLines + | otherwise = [reverse (concat (line : reverse backslashed))] + ++ replicate (length backslashed) "" + ++ f rest + where + backslashed :: [String] + backslashed = map (drop 1) $ takeWhile bs ls + unbackslashed = dropWhile bs ls + line :: String + rest:: [String] + (line,rest) = case unbackslashed of + (l:r) -> (l,r) + [] -> ("",[]) + bs ('\\':_) = True + bs _ = False preprocess :: String -> String -> String preprocess fn f = execute fn $ parseDirectives f ======================================= --- /trunk/hoc/Tests/TestPreprocessor.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/Tests/TestPreprocessor.hs Sun Aug 23 01:56:37 2009 @@ -134,8 +134,24 @@ \#endif\n\ \#endif", - "defineBackslash" ~: success + "defineBackslash" ~: "#define FOO bar\\\n\ \ baz\n\ - \success" + \A" ==> + "//#define FOO bar\ + \ baz\n\ + \\n\ + \A", + + "defineArgBackslash" ~: + "#define FOO(x,y) bar\\\n\ + \ baz\n\ + \A" ==> + "//#define FOO(x,y) bar\ + \ baz\n\ + \\n\ + \A", + + "commentBackslash" ~: + "/* abc\\\ndef */\nghi\n" ==> "/* abc*//*def */\n\nghi\n" ] |
From: <cod...@go...> - 2009-08-21 00:28:42
|
Revision: 410 Author: wol...@gm... Date: Thu Aug 20 17:27:38 2009 Log: Rework mechanics of calls to super so that meta-class objects are never passed through the machinery in ID.hs. See issue #18 http://code.google.com/p/hoc/source/detail?r=410 Modified: /trunk/hoc/HOC/HOC/Class.hs /trunk/hoc/HOC/HOC/DeclareClass.hs /trunk/hoc/HOC/HOC/Super.hs /trunk/hoc/HOC_cbits/MemoryManagement.m /trunk/hoc/HOC_cbits/Statistics.m ======================================= --- /trunk/hoc/HOC/HOC/Class.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC/Class.hs Thu Aug 20 17:27:38 2009 @@ -1,6 +1,6 @@ {-# LANGUAGE ForeignFunctionInterface, EmptyDataDecls, MultiParamTypeClasses, FunctionalDependencies, - TypeSynonymInstances #-} + TypeSynonymInstances, FlexibleContexts #-} module HOC.Class where import HOC.Base @@ -23,22 +23,21 @@ getClassByName name = withCString name c_getClassByName -{-# NOINLINE unsafeGetClassObject #-} -- called from generated code, save space + -- called from generated code, save space: +{-# NOINLINE unsafeGetClassObject #-} unsafeGetClassObject name = unsafePerformIO $ getClassByName name >>= importImmortal - -unsafeGetMetaclassForClass :: Class a -> MetaClass a +{-# NOINLINE unsafeGetRawClassObject #-} +unsafeGetRawClassObject name = unsafePerformIO $ + getClassByName name + foreign import ccall unsafe "Class.h getClassForObject" c_getClassForObject :: Ptr ObjCObject -> IO (Ptr ObjCObject) getClassForObject obj = withExportedArgument obj c_getClassForObject -{-# NOINLINE unsafeGetMetaclassForClass #-} -unsafeGetMetaclassForClass obj = unsafePerformIO $ - getClassForObject obj >>= importImmortal - class (Object a, Object b) => ClassAndObject a b | a -> b, b -> a @@ -47,3 +46,15 @@ class Object cls => ClassObject cls where classObject :: cls + +class Object a => RawStaticClass a where + rawStaticClassForObject :: a -> Ptr ObjCObject + +instance RawStaticClass (ID a) => RawStaticClass (Class a) where + rawStaticClassForObject cls = + unsafePerformIO $ + c_getClassForObject (rawStaticClassForObject $ objdummy cls) + where + objdummy :: Class a -> ID a + objdummy = undefined + ======================================= --- /trunk/hoc/HOC/HOC/DeclareClass.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/DeclareClass.hs Thu Aug 20 17:27:38 2009 @@ -6,6 +6,12 @@ import HOC.TH +import Debug.Trace + +import HOC.Arguments +import Foreign.Ptr +import System.IO.Unsafe + declareClass :: String -> String -> Q [Dec] declareClass name super = sequence $ [ @@ -41,10 +47,6 @@ valD (return $ VarP (mkName classObjectName)) (normalB [| unsafeGetClassObject $(stringE name) |]) [], - -- $(metaClassObjectName) = unsafeGetMetaclassForClass $(classObjectName) - valD (return $ VarP (mkName metaClassObjectName)) - (normalB [| unsafeGetMetaclassForClass $(varE (mkName classObjectName)) |]) [], - -- $(superName) :: String sigD (mkName superName) [t| String |], @@ -61,12 +63,13 @@ -- where classObject = classObject instanceD (cxt []) (conT ''ClassObject `appT` metaClsType) [funD 'classObject [clause [] (normalB $ varE (mkName classObjectName)) []]], - - -- instance ClassObject metaMetaCls - -- where classObject = unsafeGetMetaclassForClass classObject - -- {- metaclass object, to support super calls in class methods -} - instanceD (cxt []) (conT ''ClassObject `appT` metaMetaClsType) - [funD 'classObject [clause [] (normalB $ varE (mkName metaClassObjectName)) []]] + + -- instance RawStaticClass (name ()) where + -- rawStaticClassForObject _ = unsafeGetRawClassObject "name" + instanceD (cxt []) (conT ''RawStaticClass `appT` clsType) + [funD 'rawStaticClassForObject [ + clause [wildP] (normalB $ + [| unsafeGetRawClassObject $(stringE name) |] ) []]] ] where phantomName = name ++ "_" @@ -78,7 +81,7 @@ superMetaMetaClassName | super == "ID" = "MetaClass" | otherwise = super ++ "MetaClass" classObjectName = "_" ++ name - metaClassObjectName = "_" ++ metaClassName + superName = "super_" ++ name metaMetaClsType = conT (mkName metaMetaClassName) `appT` [t| () |] ======================================= --- /trunk/hoc/HOC/HOC/Super.hs Wed Dec 10 06:52:25 2008 +++ /trunk/hoc/HOC/HOC/Super.hs Thu Aug 20 17:27:38 2009 @@ -25,7 +25,7 @@ -- super, which is sufficient to define a class hierarchy. class SuperClass sub super | sub -> super -data SuperTarget a = SuperTarget a (Class ()) +data SuperTarget a = SuperTarget a (Ptr ObjCObject) class Super sub super | sub -> super where super :: sub -> super @@ -43,7 +43,6 @@ => ObjCArgument (SuperTarget a) (Ptr ObjCObject) where withExportedArgument (SuperTarget obj cls) action = - withExportedArgument cls $ \cls -> withExportedArgument obj $ \p -> withExportedSuper p cls action @@ -55,19 +54,14 @@ castSuper :: SuperClass (ID sub) (ID super) => ID sub -> ID super castSuper = castObject -staticSuperclassForObject :: - ( SuperClass (ID sub) (ID super) - , ClassObject (Class super) - ) => ID sub -> Class super -staticSuperclassForObject obj = classObject - instance (Object (ID sub), Object (ID super), SuperClass (ID sub) (ID super), - ClassObject (Class super)) + RawStaticClass (ID super)) => Super (ID sub) (SuperTarget (ID super)) where - super obj = SuperTarget (castSuper obj) (castObject (staticSuperclassForObject obj)) + super obj = SuperTarget (castSuper obj) + (rawStaticClassForObject (castSuper obj)) instance MessageTarget a => MessageTarget (SuperTarget a) where - isNil (SuperTarget x cls) = isNil x || isNil cls + isNil (SuperTarget x cls) = isNil x || cls == nullPtr sendMessageWithRetval _ = superSendMessageWithRetval sendMessageWithoutRetval _ = superSendMessageWithoutRetval ======================================= --- /trunk/hoc/HOC_cbits/MemoryManagement.m Mon Aug 17 15:41:10 2009 +++ /trunk/hoc/HOC_cbits/MemoryManagement.m Thu Aug 20 17:27:38 2009 @@ -65,8 +65,9 @@ if(!selRetain) selRetain = getSelectorForName("retain"); #if DO_LOG - printf("retain %p, %p\n",obj,obj->isa); + printf("retain %p, %p\n",obj,getClassForObject(obj)); #endif + objc_msgSend(obj,selRetain); } @@ -75,8 +76,9 @@ if(!selRelease) selRelease = getSelectorForName("release"); #if DO_LOG - printf("release %p, %p\n",obj,obj->isa); + printf("release %p, %p\n",obj,getClassForObject(obj)); #endif + objc_msgSend(obj,selRelease); } ======================================= --- /trunk/hoc/HOC_cbits/Statistics.m Tue Feb 13 09:11:04 2007 +++ /trunk/hoc/HOC_cbits/Statistics.m Thu Aug 20 17:27:38 2009 @@ -37,7 +37,7 @@ obj = *(id*) args[0]; sel = *(SEL*) args[1]; - // printf("recordHOCEvent %d\n", what); + //printf("recordHOCEvent %d %p %s\n", what, obj, sel_get_name(sel)); #ifdef DO_TIMINGS static uint64_t saved; |
From: <cod...@go...> - 2009-08-20 23:26:55
|
Revision: 409 Author: wol...@gm... Date: Thu Aug 20 16:26:28 2009 Log: add flags for proper exception handling on GNUstep http://code.google.com/p/hoc/source/detail?r=409 Modified: /trunk/hoc/HOC.cabal ======================================= --- /trunk/hoc/HOC.cabal Tue Aug 11 11:23:05 2009 +++ /trunk/hoc/HOC.cabal Thu Aug 20 16:26:28 2009 @@ -73,7 +73,6 @@ -- whole point of this exercise. c-sources: HOC_cbits.o - if os(darwin) include-dirs: /usr/include/ffi frameworks: Foundation @@ -82,7 +81,9 @@ -- paths are inserted by Setup.hs extra-libraries: gnustep-base cpp-options: -DGNUSTEP - + cc-options: -fobjc-exceptions + -D_NATIVE_OBJC_EXCEPTIONS=1 + if flag(ObjC2) cpp-options: -D__OBJC2__=1 |
From: <cod...@go...> - 2009-08-20 23:09:53
|
Revision: 408 Author: wol...@gm... Date: Thu Aug 20 16:09:05 2009 Log: On GNUstep, clean up the stack frame chain in Invocation.m:callWithExceptions When the FFI call from Haskell to callWithExceptions() is made, %ebp contains not a stack frame link but rather some other value. When GNUstep's NSException tries to walk the stack to generate a stack trace, it segfaults. Therefore, we use GCC's __builtin_frame_address to retrieve the saved frame pointer value, save it elsewhere and reset the stack frame link to 0 so that GNUstep's stack trace just stops there. It is reset to the stored value upon exit. Fixes issue #19. http://code.google.com/p/hoc/source/detail?r=408 Modified: /trunk/hoc/HOC_cbits/Invocation.m ======================================= --- /trunk/hoc/HOC_cbits/Invocation.m Sat Jan 5 08:46:39 2008 +++ /trunk/hoc/HOC_cbits/Invocation.m Thu Aug 20 16:09:05 2009 @@ -8,10 +8,37 @@ NSException *callWithExceptions(ffi_cif *cif, void (*fn)(), void *rvalue, void **avalue) { +#ifdef GNUSTEP + // GHC messes up the stack frame chain. + // GNUstep generates exception stack traces on the assumption + // that the stack frame chain makes sense. + // Therefore, we move the frame pointer value left behind by + // GHC from its regular stack slot into a local variable and + // set the stack-frame link to 0 (temporarily). + + void **frame = __builtin_frame_address(0); + void *save = *frame; + + // We assume that + // *(void**)__builtin_frame_address(0) == __builtin_frame_address(1) + // which is true at least for i386, x86_64 and powerpc[64]. + assert(save == __builtin_frame_address(1)); + + *frame = 0; +#endif + + NSException *exception = nil; NS_DURING ffi_call(cif, fn, rvalue, avalue); NS_HANDLER - return localException; + exception = localException; NS_ENDHANDLER - return nil; -} + +#ifdef GNUSTEP + // restore old stack frame link + *frame = save; +#endif + + return exception; +} + |
From: <cod...@go...> - 2009-08-20 22:16:26
|
Revision: 407 Author: wol...@gm... Date: Thu Aug 20 15:15:27 2009 Log: Fix a mixup in sending messages to super on GNUstep: the "self" parameter was passed incorrectly to the superclass method implementation. http://code.google.com/p/hoc/source/detail?r=407 Modified: /trunk/hoc/HOC/HOC/MsgSend.hs ======================================= --- /trunk/hoc/HOC/HOC/MsgSend.hs Mon Aug 17 10:31:23 2009 +++ /trunk/hoc/HOC/HOC/MsgSend.hs Thu Aug 20 15:15:27 2009 @@ -10,7 +10,6 @@ import HOC.FFICallInterface import HOC.Arguments import HOC.Invocation - import Foreign objSendMessageWithRetval @@ -42,7 +41,7 @@ foreign import ccall "objc/objc.h objc_msg_lookup_super" objc_msg_lookup_super :: Ptr ObjCObject -> SEL -> IO (FunPtr ()) - + sndMsgCommon call cif args = do target <- peekElemOff args 0 >>= peek . castPtr selector <- peekElemOff args 1 >>= peek . castPtr @@ -50,10 +49,15 @@ call cif imp args sndMsgSuperCommon call cif args = do - super <- peekElemOff args 0 >>= peek . castPtr - peek (castPtr super) >>= pokeElemOff args 0 + arg0Ptr <- peekElemOff args 0 + super <- peek (castPtr arg0Ptr) + object <- peek (castPtr super) + poke (castPtr arg0Ptr) (object :: Ptr ObjCObject) + selector <- peekElemOff args 1 >>= peek . castPtr + imp <- objc_msg_lookup_super super selector + call cif imp args |
From: <cod...@go...> - 2009-08-17 22:41:49
|
Revision: 406 Author: wol...@gm... Date: Mon Aug 17 15:41:10 2009 Log: Make things compile under GNUstep (issue #17) http://code.google.com/p/hoc/source/detail?r=406 Modified: /trunk/hoc/HOC_cbits/Class.m /trunk/hoc/HOC_cbits/Ivars.h /trunk/hoc/HOC_cbits/Ivars.m /trunk/hoc/HOC_cbits/MemoryManagement.m /trunk/hoc/HOC_cbits/NewClass.m /trunk/hoc/HOC_cbits/RetainedHaskellPart.m ======================================= --- /trunk/hoc/HOC_cbits/Class.m Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC_cbits/Class.m Mon Aug 17 15:41:10 2009 @@ -34,16 +34,18 @@ Class root_class; for(root_class = super_class; - getSuperclassForClass(root_class) != nil; - root_class = getSuperclassForClass(root_class)) - ; + getSuperclassForClass(root_class) != nil; + root_class = getSuperclassForClass(root_class)) + ; return root_class; } Class getClassForObject(id object) { -#ifdef __OBJC2__ +#ifdef GNUSTEP + return object->class_pointer; +#elif defined(__OBJC2__) return object_getClass(object); #else return object->isa; ======================================= --- /trunk/hoc/HOC_cbits/Ivars.h Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC_cbits/Ivars.h Mon Aug 17 15:41:10 2009 @@ -1,6 +1,17 @@ #include <stdlib.h> #include <stdint.h> +#ifdef GNUSTEP +struct objc_ivar * +class_getInstanceVariable(Class cls, const char *name); + +struct objc_ivar * +object_getInstanceVariable(id obj, const char *name, void** out); + +struct objc_ivar * +object_setInstanceVariable(id obj, const char *name, void* val); +#endif + struct hoc_ivar { char *ivar_name; char *ivar_types; ======================================= --- /trunk/hoc/HOC_cbits/Ivars.m Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC_cbits/Ivars.m Mon Aug 17 15:41:10 2009 @@ -9,6 +9,49 @@ #include "Ivars.h" +#ifdef GNUSTEP +struct objc_ivar * +class_getInstanceVariable(Class cls, const char *name) +{ + struct objc_ivar *ivar = NULL; + + while(cls) + { + if(cls->ivars) + { + int i; + + for(i=0;i<cls->ivars->ivar_count;i++) + { + if(!strcmp(cls->ivars->ivar_list[i].ivar_name, name)) + return &cls->ivars->ivar_list[i]; + } + } + cls = cls->super_class; + } + return NULL; +} + +struct objc_ivar * +object_getInstanceVariable(id obj, const char *name, void** out) +{ + struct objc_ivar *ivar = class_getInstanceVariable(obj->class_pointer,name); + if(ivar) + *out = *(void**) ((char*)obj + ivar->ivar_offset); + return ivar; +} + +struct objc_ivar * +object_setInstanceVariable(id obj, const char *name, void* val) +{ + struct objc_ivar *ivar = class_getInstanceVariable(obj->class_pointer,name); + if(ivar) + *(void**) ((char*)obj + ivar->ivar_offset) = val; + return ivar; +} +#endif + + struct hoc_ivar_list * makeIvarList(int n) { struct hoc_ivar_list *list = ======================================= --- /trunk/hoc/HOC_cbits/MemoryManagement.m Thu Aug 13 08:45:30 2009 +++ /trunk/hoc/HOC_cbits/MemoryManagement.m Mon Aug 17 15:41:10 2009 @@ -48,6 +48,7 @@ #ifdef GNUSTEP #define objc_msgSend(self,sel) (*objc_msg_lookup(self,sel))(self,sel) +#define objc_msgSendSuper(super,sel) (*objc_msg_lookup_super(super,sel))(super->self,sel) #endif static SEL selRetain = 0; @@ -90,8 +91,13 @@ struct objc_super * super = calloc(1, sizeof(struct objc_super)); +#if GNUSTEP + super->self = obj; + super->class = cls; +#else super->receiver = obj; super->super_class = cls; +#endif objc_msgSendSuper(super, selRetain); } @@ -107,8 +113,13 @@ struct objc_super * super = calloc(1, sizeof(struct objc_super)); +#if GNUSTEP + super->self = obj; + super->class = cls; +#else super->receiver = obj; super->super_class = cls; +#endif objc_msgSendSuper(super, selRelease); } ======================================= --- /trunk/hoc/HOC_cbits/NewClass.m Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC_cbits/NewClass.m Mon Aug 17 15:41:10 2009 @@ -49,7 +49,7 @@ module->version = 8; module->size = sizeof(Module); - module->name = strdup(name); + module->name = strdup(new_class->name); module->symtab = symtab; symtab->cls_def_cnt = 1; symtab->defs[0] = new_class; ======================================= --- /trunk/hoc/HOC_cbits/RetainedHaskellPart.m Tue Oct 28 06:02:53 2003 +++ /trunk/hoc/HOC_cbits/RetainedHaskellPart.m Mon Aug 17 15:41:10 2009 @@ -6,49 +6,7 @@ #include <objc/objc-class.h> #endif #include "RetainedHaskellPart.h" - -#ifdef GNUSTEP -static struct objc_ivar * -object_findInstanceVar(id obj, const char *name) -{ - Class cls = obj->class_pointer; - struct objc_ivar *ivar = NULL; - - while(cls) - { - if(cls->ivars) - { - int i; - - for(i=0;i<cls->ivars->ivar_count;i++) - { - if(!strcmp(cls->ivars->ivar_list[i].ivar_name, name)) - return &cls->ivars->ivar_list[i]; - } - } - cls = cls->super_class; - } - return NULL; -} - -static struct objc_ivar * -object_getInstanceVariable(id obj, const char *name, void** out) -{ - struct objc_ivar *ivar = object_findInstanceVar(obj,name); - if(ivar) - *out = *(void**) ((char*)obj + ivar->ivar_offset); - return ivar; -} - -static struct objc_ivar * -object_setInstanceVariable(id obj, const char *name, void* val) -{ - struct objc_ivar *ivar = object_findInstanceVar(obj,name); - if(ivar) - *(void**) ((char*)obj + ivar->ivar_offset) = val; - return ivar; -} -#endif +#include "Ivars.h" void* getRetainedHaskellPart(id obj) { |
From: <cod...@go...> - 2009-08-17 22:34:42
|
Revision: 405 Author: wol...@gm... Date: Mon Aug 17 15:34:07 2009 Log: fix build system for GNUstep http://code.google.com/p/hoc/source/detail?r=405 Modified: /trunk/hoc/Setup.hs ======================================= --- /trunk/hoc/Setup.hs Tue Aug 11 11:23:05 2009 +++ /trunk/hoc/Setup.hs Mon Aug 17 15:34:07 2009 @@ -14,7 +14,7 @@ import System.Process import qualified System.Info -main = defaultMainWithHooks $ simpleUserHooks { +main = defaultMainWithHooks $ defaultUserHooks { confHook = customConfig, buildHook = customBuild } @@ -90,14 +90,15 @@ then return() else do (gcclibdir, system_libs, system_headers) <- gnustepPaths - writeFile "HOC.buildinfo" $ "extra-lib-dirs: " ++ gcclibdir ++ ", " ++ system_libs ++ "\n" + writeFile "HOC.buildinfo" $ unlines [ + "extra-lib-dirs: " ++ gcclibdir ++ ", " ++ system_libs, + "include-dirs: " ++ system_headers ] return lbi customBuild :: PackageDescription -> LocalBuildInfo -> UserHooks -> BuildFlags -> IO () customBuild pd lbi hooks buildFlags = do let Just libInfo = library pd - extraFlags <- buildCBits (libBuildInfo libInfo) -- add compiler flags required by C parts of HOC; @@ -126,7 +127,9 @@ -- After having "compiled" HOC_cbits.o in this way, Cabal will link -- HOC_cbits.o as part of the library, which is what we want. - let Just pr = lookupKnownProgram "ghc" (withPrograms lbi) + --print ((\(ProgramConfiguration a b) -> (a,b)) $ withPrograms lbi) + let -- Just pr = lookupKnownProgram "ghc" (withPrograms lbi) + pr = simpleProgram "ghc" Just conf = lookupProgram pr (withPrograms lbi) ghcLocation = programLocation conf @@ -161,18 +164,22 @@ buildCBits :: BuildInfo -> IO [(CompilerFlavor, [String])] buildCBits buildInfo = do putStrLn "Compiling HOC_cbits..." + system ("mkdir -p " ++ takeDirectory cbitsObjectFile) let cflags = cppOptions buildInfo ++ ccOptions buildInfo - ++ ["-I" ++ dir | dir <- includeDirs buildInfo] + ++ ["-I" ++ dir | dir <- includeDirs buildInfo] extraGHCflags = [cbitsObjectFile] + ++ ["-L" ++ lib | lib <- extraLibDirs buildInfo] ++ ["-l" ++ lib | lib <- extraLibs buildInfo] ++ ["-framework " ++ fw | fw <- frameworks buildInfo] - exitCode <- system $ "gcc -r -nostdlib -I`ghc --print-libdir`/include " + let cmd = "gcc -r -nostdlib -I`ghc --print-libdir`/include " ++ unwords cflags ++ " HOC_cbits/*.m -o " ++ cbitsObjectFile + exitCode <- system cmd + case exitCode of ExitSuccess -> return () _ -> fail "Failed in C compilation." |
From: <cod...@go...> - 2009-08-17 17:32:31
|
Revision: 404 Author: wol...@gm... Date: Mon Aug 17 10:31:23 2009 Log: fix various warnings, unused imports http://code.google.com/p/hoc/source/detail?r=404 Modified: /trunk/hoc/HOC/HOC/Arguments.hs /trunk/hoc/HOC/HOC/Base.hs /trunk/hoc/HOC/HOC/CEnum.hs /trunk/hoc/HOC/HOC/CStruct.hs /trunk/hoc/HOC/HOC/CannedCIFs.hs /trunk/hoc/HOC/HOC/DeclareClass.hs /trunk/hoc/HOC/HOC/DeclareSelector.hs /trunk/hoc/HOC/HOC/Dyld.hs /trunk/hoc/HOC/HOC/ExportClass.hs /trunk/hoc/HOC/HOC/ExternFunctions.hs /trunk/hoc/HOC/HOC/FFICallInterface.hs /trunk/hoc/HOC/HOC/ID.hs /trunk/hoc/HOC/HOC/MsgSend.hs /trunk/hoc/HOC/HOC/NewClass.hs /trunk/hoc/HOC/HOC/NewlyAllocated.hs /trunk/hoc/HOC/HOC/SelectorMarshaller.hs /trunk/hoc/HOC/HOC/SelectorNameMangling.hs /trunk/hoc/HOC/HOC/StdArgumentTypes.hs /trunk/hoc/HOC/HOC/THDebug.hs /trunk/hoc/HOC/HOC/Unicode.hs /trunk/hoc/HOC/HOC/Utilities.hs /trunk/hoc/HOC/HOC.hs /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs /trunk/hoc/InterfaceGenerator2/THTraversal.hs /trunk/hoc/InterfaceGenerator2/Traversals.hs ======================================= --- /trunk/hoc/HOC/HOC/Arguments.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/Arguments.hs Mon Aug 17 10:31:23 2009 @@ -3,11 +3,9 @@ UndecidableInstances, ScopedTypeVariables #-} module HOC.Arguments where -import HOC.Base import HOC.FFICallInterface import Foreign.Storable -import Foreign.ForeignPtr import Foreign.Ptr import Foreign.Marshal.Array import System.IO.Unsafe(unsafePerformIO) @@ -67,8 +65,8 @@ `appT` ty `appT` ty) `whereQ` [d| {- withExportedArgument = flip ($) -} - exportArgument = return - importArgument = return + exportArgument x = return x + importArgument x = return x objCTypeString _ = str |] return [argInst] ======================================= --- /trunk/hoc/HOC/HOC/Base.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC/Base.hs Mon Aug 17 10:31:23 2009 @@ -3,7 +3,6 @@ import Foreign import Foreign.C.String -import Control.Monad(when) import Control.Exception(bracket) -- The SEL Type ======================================= --- /trunk/hoc/HOC/HOC/CEnum.hs Sat Nov 1 06:12:45 2008 +++ /trunk/hoc/HOC/HOC/CEnum.hs Mon Aug 17 10:31:23 2009 @@ -58,8 +58,8 @@ ], instanceD (cxt []) (conT ''ObjCArgument `appT` conT typ `appT` [t| CInt |]) `whereQ` [d| - exportArgument = return . fromCEnum - importArgument = return . toCEnum + exportArgument x = return (fromCEnum x) + importArgument x = return (toCEnum x) objCTypeString _ = "i" |] ] ++ [ ======================================= --- /trunk/hoc/HOC/HOC/CStruct.hs Tue Oct 7 16:07:50 2008 +++ /trunk/hoc/HOC/HOC/CStruct.hs Mon Aug 17 10:31:23 2009 @@ -1,4 +1,4 @@ -{-# OPTIONS -fglasgow-exts -fth #-} +{-# LANGUAGE TemplateHaskell #-} module HOC.CStruct( declareCStruct, declareCStructWithTag ) where import HOC.Arguments ( ObjCArgument(..) ) @@ -7,7 +7,6 @@ import HOC.FFICallInterface import Control.Monad.State -import Data.Bits import Data.Maybe ( fromMaybe ) import Foreign ======================================= --- /trunk/hoc/HOC/HOC/CannedCIFs.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/CannedCIFs.hs Mon Aug 17 10:31:23 2009 @@ -5,13 +5,11 @@ import HOC.Arguments ( getCifForSelector ) import HOC.ID ( ID ) import HOC.TH ( fromSameModuleAs_v ) -import HOC.THDebug -import Control.Monad (when) +-- import HOC.THDebug import Data.List ( intersperse ) import Data.Maybe ( catMaybes, fromMaybe ) import Data.Word ( Word ) -import Data.Generics import Foreign ( Ptr ) import Foreign.C import Language.Haskell.TH ======================================= --- /trunk/hoc/HOC/HOC/DeclareClass.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC/DeclareClass.hs Mon Aug 17 10:31:23 2009 @@ -1,15 +1,11 @@ {-# LANGUAGE TemplateHaskell #-} module HOC.DeclareClass(declareClass) where -import HOC.Base -import HOC.Arguments import HOC.Class import HOC.Super import HOC.TH -import Foreign.Ptr - declareClass :: String -> String -> Q [Dec] declareClass name super = sequence $ [ ======================================= --- /trunk/hoc/HOC/HOC/DeclareSelector.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/DeclareSelector.hs Mon Aug 17 10:31:23 2009 @@ -1,22 +1,17 @@ {-# LANGUAGE TemplateHaskell, EmptyDataDecls #-} module HOC.DeclareSelector where -import HOC.Base import HOC.Arguments -import HOC.Class import HOC.Invocation import HOC.SelectorNameMangling -import HOC.MsgSend -import HOC.FFICallInterface import HOC.SelectorMarshaller -import HOC.StdArgumentTypes +import HOC.StdArgumentTypes () import HOC.ID -import HOC.NewlyAllocated(NewlyAllocated) +import HOC.NewlyAllocated (NewlyAllocated) import HOC.Super import HOC.CannedCIFs import HOC.MessageTarget -import Data.Char(isUpper, toLower, toUpper) import Data.Maybe(fromMaybe) import Control.Monad(MonadPlus(mplus)) @@ -29,6 +24,7 @@ data Retained a $(makeMarshallers 4) +marshallersUpTo :: Int marshallersUpTo = 4 {-# NOINLINE method0 #-} @@ -77,7 +73,7 @@ className = "Has_" ++ haskellName imptypeName = "ImpType_" ++ haskellName - nArgs = countArgs typeSig + nArgs = countArgs typeSig :: Int -- isPure is a boolean that indicates if the resultType of our type -- signature is not in the IO mondad ======================================= --- /trunk/hoc/HOC/HOC/Dyld.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/Dyld.hs Mon Aug 17 10:31:23 2009 @@ -6,7 +6,6 @@ import GHC.Exts(Ptr(..), Addr#) import Foreign -import Foreign.C.String import System.Posix.DynamicLinker lookupSymbol :: String -> IO (FunPtr a) ======================================= --- /trunk/hoc/HOC/HOC/ExportClass.hs Thu Aug 13 08:45:30 2009 +++ /trunk/hoc/HOC/HOC/ExportClass.hs Mon Aug 17 10:31:23 2009 @@ -1,7 +1,6 @@ {-# LANGUAGE TemplateHaskell, MultiParamTypeClasses, FunctionalDependencies #-} module HOC.ExportClass where -import Foreign import Foreign.C.String import Control.Concurrent.MVar import Data.Dynamic @@ -10,10 +9,10 @@ import Data.Char(toUpper) import HOC.Base -import HOC.ID import HOC.MessageTarget import HOC.Arguments import HOC.Invocation +import HOC.ID import HOC.SelectorMarshaller import HOC.Class import HOC.NewClass ======================================= --- /trunk/hoc/HOC/HOC/ExternFunctions.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/ExternFunctions.hs Mon Aug 17 10:31:23 2009 @@ -52,7 +52,7 @@ -- ### FIXME: Code Duplication from DeclareSelector.hs countArgs (ForallT vars ctxt ty) = countArgs ty countArgs ((ArrowT `AppT` _) `AppT` rest) = 1 + countArgs rest - countArgs other = 0 + countArgs other = 0 :: Int resultType (ForallT vars ctxt ty) = resultType ty resultType ((ArrowT `AppT` _) `AppT` rest) = resultType rest ======================================= --- /trunk/hoc/HOC/HOC/FFICallInterface.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/FFICallInterface.hs Mon Aug 17 10:31:23 2009 @@ -75,10 +75,6 @@ promotedPeek p = peek (castPtr p :: Ptr CLong) >>= return . fromIntegral - where - size = sizeOf (pointee p) - pointee :: Ptr p -> p - pointee = undefined promotedAlloca f = alloca (\intPtr -> f $ castPtr (intPtr :: Ptr CLong)) ======================================= --- /trunk/hoc/HOC/HOC/ID.hs Thu Aug 13 08:45:30 2009 +++ /trunk/hoc/HOC/HOC/ID.hs Mon Aug 17 10:31:23 2009 @@ -7,17 +7,17 @@ import HOC.FFICallInterface(FFICif) import Control.Concurrent.MVar -import Control.Exception(evaluate,assert) -import Control.Monad(when, join) +import Control.Exception(evaluate) +import Control.Monad(when) import System.IO.Unsafe(unsafePerformIO) import System.Mem.Weak import Foreign.Ptr import Foreign.StablePtr -import Foreign.C.Types(CInt,CUInt,CChar {- ObjC BOOL is typedefed to char -}) +import Foreign.C.Types(CInt,CUInt) import Foreign.Storable import Foreign.Marshal.Alloc(alloca) import Data.Dynamic -import Data.Maybe(fromMaybe, isJust) +import Data.Maybe(fromMaybe) data ID a = ID HSO | Nil ======================================= --- /trunk/hoc/HOC/HOC/MsgSend.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/MsgSend.hs Mon Aug 17 10:31:23 2009 @@ -12,7 +12,6 @@ import HOC.Invocation import Foreign -import Control.Monad.Fix(mfix) objSendMessageWithRetval :: ObjCArgument a b ======================================= --- /trunk/hoc/HOC/HOC/NewClass.hs Thu Aug 13 08:45:30 2009 +++ /trunk/hoc/HOC/HOC/NewClass.hs Mon Aug 17 10:31:23 2009 @@ -18,7 +18,6 @@ import HOC.ID import HOC.FFICallInterface import HOC.Arguments -import HOC.Class import Foreign.C.String import Foreign.C.Types ======================================= --- /trunk/hoc/HOC/HOC/NewlyAllocated.hs Wed Dec 10 06:52:25 2008 +++ /trunk/hoc/HOC/HOC/NewlyAllocated.hs Mon Aug 17 10:31:23 2009 @@ -17,13 +17,11 @@ import HOC.Arguments ( ObjCArgument(..) ) import HOC.Class import HOC.ID -import HOC.MessageTarget( Object(..), MessageTarget(..) ) +import HOC.MessageTarget( MessageTarget(..) ) import HOC.MsgSend import HOC.Super import Foreign.Ptr ( Ptr, nullPtr ) -import System.IO.Unsafe ( unsafePerformIO ) - data NewlyAllocated a = NewlyAllocated (Ptr ObjCObject) ======================================= --- /trunk/hoc/HOC/HOC/SelectorMarshaller.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/SelectorMarshaller.hs Mon Aug 17 10:31:23 2009 @@ -9,16 +9,12 @@ ) where import HOC.Base -import HOC.Arguments import HOC.ID -import HOC.Class import HOC.Invocation -import HOC.SelectorNameMangling -import HOC.MsgSend import HOC.FFICallInterface import HOC.MessageTarget -import Foreign ( withArray, Ptr, nullPtr ) +import Foreign ( withArray ) import System.IO.Unsafe ( unsafePerformIO ) import GHC.Base ( unpackCString# ) ======================================= --- /trunk/hoc/HOC/HOC/SelectorNameMangling.hs Sun Sep 28 10:35:32 2008 +++ /trunk/hoc/HOC/HOC/SelectorNameMangling.hs Mon Aug 17 10:31:23 2009 @@ -1,6 +1,5 @@ module HOC.SelectorNameMangling where -import Data.List(intersperse) import Data.Char(isUpper, toUpper, toLower) -- addObject:forKey: -> addObjectForKey ======================================= --- /trunk/hoc/HOC/HOC/StdArgumentTypes.hs Fri Jan 9 17:28:12 2009 +++ /trunk/hoc/HOC/HOC/StdArgumentTypes.hs Mon Aug 17 10:31:23 2009 @@ -5,14 +5,12 @@ module HOC.StdArgumentTypes where import HOC.Base -import HOC.Invocation import HOC.Arguments import HOC.FFICallInterface import Control.Exception ( bracket ) import Foreign import Foreign.C.Types -import Foreign.C.String import HOC.Unicode ======================================= --- /trunk/hoc/HOC/HOC/THDebug.hs Sun Aug 24 21:31:51 2008 +++ /trunk/hoc/HOC/HOC/THDebug.hs Mon Aug 17 10:31:23 2009 @@ -1,4 +1,4 @@ -{-# OPTIONS -fno-monomorphism-restriction #-} +{-# LANGUAGE NoMonomorphismRestriction #-} module HOC.THDebug ( ======================================= --- /trunk/hoc/HOC/HOC/Unicode.hs Thu Mar 16 21:32:04 2006 +++ /trunk/hoc/HOC/HOC/Unicode.hs Mon Aug 17 10:31:23 2009 @@ -53,7 +53,6 @@ ) where -import Data.Char( toUpper ) import Data.Word( Word8 ) -- ------------------------------------------------------------ @@ -143,7 +142,7 @@ -- | -- conversion from Unicode strings (UString) to UTF8 encoded strings. -unicodeToUtf8 :: String -> UTF8String +unicodeToUtf8 :: UString -> UTF8String unicodeToUtf8 = concatMap unicodeCharToUtf8 -- | ======================================= --- /trunk/hoc/HOC/HOC/Utilities.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/Utilities.hs Mon Aug 17 10:31:23 2009 @@ -3,7 +3,6 @@ import HOC.Base import HOC.Arguments -import HOC.ID import HOC.TH import HOC.ExportClass import Foreign.Ptr ======================================= --- /trunk/hoc/HOC/HOC.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC.hs Mon Aug 17 10:31:23 2009 @@ -69,15 +69,12 @@ import HOC.Base import HOC.Arguments -import HOC.Invocation import HOC.ID import HOC.MessageTarget import HOC.Class import HOC.DeclareClass import HOC.ExportClass -import HOC.SelectorMarshaller import HOC.DeclareSelector -import HOC.StdArgumentTypes import HOC.ExportClass import HOC.Utilities import HOC.NewlyAllocated ======================================= --- /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs Wed Oct 1 14:40:28 2008 +++ /trunk/hoc/InterfaceGenerator2/BinaryInstances.hs Mon Aug 17 10:31:23 2009 @@ -1,4 +1,4 @@ -{-# LANGUAGE PatternGuards, PatternSignatures, ExistentialQuantification #-} +{-# LANGUAGE PatternGuards, ScopedTypeVariables, ExistentialQuantification #-} module BinaryInstances() where import Data.Binary ======================================= --- /trunk/hoc/InterfaceGenerator2/THTraversal.hs Sun Dec 23 16:43:07 2007 +++ /trunk/hoc/InterfaceGenerator2/THTraversal.hs Mon Aug 17 10:31:23 2009 @@ -1,4 +1,4 @@ -{-# OPTIONS -fth #-} +{-# LANGUAGE TemplateHaskell #-} module THTraversal where import Language.Haskell.TH ======================================= --- /trunk/hoc/InterfaceGenerator2/Traversals.hs Sun Dec 23 16:43:07 2007 +++ /trunk/hoc/InterfaceGenerator2/Traversals.hs Mon Aug 17 10:31:23 2009 @@ -1,4 +1,4 @@ -{-# OPTIONS -cpp -fth -fglasgow-exts #-} +{-# LANGUAGE CPP, TemplateHaskell, RelaxedPolyRec #-} module Traversals where #define TEMPLATES 1 |
From: <cod...@go...> - 2009-08-17 17:28:20
|
Revision: 403 Author: wol...@gm... Date: Mon Aug 17 10:26:56 2009 Log: minor documentation corrections/updates http://code.google.com/p/hoc/source/detail?r=403 Modified: /trunk/hoc/docs/Appendices.pod /trunk/hoc/docs/Tools.pod ======================================= --- /trunk/hoc/docs/Appendices.pod Thu Mar 31 19:26:57 2005 +++ /trunk/hoc/docs/Appendices.pod Mon Aug 17 10:26:56 2009 @@ -2,22 +2,9 @@ =head2 Building HOC -HOC is distributed as a standard UNIX tarball (F<.tar.bz2> file), and -uses GNU I<autoconf> for its build system. Building HOC should -be a simple matter of the standard autoconf build mantra: - - ./configure - make - make install - See the F<README.txt> file in the HOC distribution for the most up-to-date build information. -Building HOC from a CVS repository is only slightly more -involved: see the F<BUILDING.CVS> file in your checked out CVS -directory (which is not included in proper release tarball) for -more information. - =head2 Template Haskell in a Nutshell I<Template Haskell is an extension to Haskell 98 that allows you ======================================= --- /trunk/hoc/docs/Tools.pod Wed May 19 09:18:28 2004 +++ /trunk/hoc/docs/Tools.pod Mon Aug 17 10:26:56 2009 @@ -1,17 +1,13 @@ =head1 Tools -=head2 F<hocwrap> - -The F<hocwrap> tool takes an executable and "wraps" it in a Mac OS -X F<.app> application bundle. You'll need to tell hocwrap where the -bundle's F<Contents/> directory using the C<-c> command-line parameter. -F<hocwrap> can also run the resulting application bundle using GHCi in an -interactive fashion: more documentation about this will be coming in the -future, but for now, check out the I<Browser> and I<Editor> applications' -F<Makefile>s in HOC's F<Samples/> directory, for an idea of how to use the -GHCi interaction feature. - -See C<hocwrap --help> for the definitive reference on F<hocwrap>. +=head2 F<hoc-wrap> + +The F<hoc-wrap> tool takes an executable and "wraps" it in a Mac OS +X F<.app> application bundle. It expects to find a F<Contents/> folder +that already contains all the necessary ingredients for the bundle, +except for the executable itself, in the current directory. + +See C<hoc-wrap --help> for the definitive reference on F<hocwrap>. =for comment Modeline for vi(m) vi:sw=2 tw=65 |
From: <cod...@go...> - 2009-08-13 15:50:25
|
Revision: 402 Author: jam...@us... Date: Thu Aug 13 08:45:30 2009 Log: Merging ObjC2 branch to trunk (r380 and related changes) http://code.google.com/p/hoc/source/detail?r=402 Modified: / /trunk/hoc /trunk/hoc/HOC/HOC/ExportClass.hs /trunk/hoc/HOC/HOC/ID.hs /trunk/hoc/HOC/HOC/NewClass.hs /trunk/hoc/HOC_cbits/MemoryManagement.h /trunk/hoc/HOC_cbits/MemoryManagement.m /trunk/hoc/InterfaceGenerator2/Output.hs ======================================= --- /trunk/hoc/HOC/HOC/ExportClass.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC/ExportClass.hs Thu Aug 13 08:45:30 2009 @@ -130,8 +130,8 @@ ivars <- makeDefaultIvarList imethods <- makeMethodList (nIMethods+3) cmethods <- makeMethodList nCMethods - setHaskellRetainMethod imethods 0 - setHaskellReleaseMethod imethods 1 + setHaskellRetainMethod imethods 0 super + setHaskellReleaseMethod imethods 1 super setHaskellDataMethod imethods 2 super ( Just ($(typedInitIvars) >>= return . toDyn) ) ======================================= --- /trunk/hoc/HOC/HOC/ID.hs Sat Nov 1 04:27:26 2008 +++ /trunk/hoc/HOC/HOC/ID.hs Thu Aug 13 08:45:30 2009 @@ -8,7 +8,7 @@ import Control.Concurrent.MVar import Control.Exception(evaluate,assert) -import Control.Monad(when) +import Control.Monad(when, join) import System.IO.Unsafe(unsafePerformIO) import System.Mem.Weak import Foreign.Ptr @@ -21,6 +21,12 @@ data ID a = ID HSO | Nil +dPutStrLn = if {--} False --} True + then putStrLn + else const $ return () + +dPutWords = dPutStrLn . unwords + nil = Nil castObject (ID a) = ID a @@ -58,6 +64,13 @@ -- don't we love globals? This needs -fno-cse to be truely safe. objectMapLock = unsafePerformIO $ newMVar () {-# NOINLINE objectMapLock #-} + +withObjectMapLock taker action = do + dPutWords [">", "withObjectMapLock", taker] + res <- withMVar objectMapLock $ \_ -> action + dPutWords ["<", "withObjectMapLock", taker] + return res + -- given a pointer to an ObjCObject, return a stablePtr to a Weak reference to -- a HSO @@ -91,13 +104,21 @@ getRetainedHaskellPart :: Ptr ObjCObject -> IO (StablePtr HSO) foreign import ccall unsafe "RetainedHaskellPart.h setRetainedHaskellPart" setRetainedHaskellPart :: Ptr ObjCObject -> StablePtr HSO -> IO () - -foreign import ccall unsafe "NSObjectReferenceCount.h NSIncrementExtraRefCount" - nsIncrementExtraRefCount :: Ptr ObjCObject -> IO () -foreign import ccall unsafe "NSObjectReferenceCount.h NSDecrementExtraRefCountWasZero" - nsDecrementExtraRefCountWasZero :: Ptr ObjCObject -> IO CChar{-BOOL-} -foreign import ccall unsafe "NSObjectReferenceCount.h NSExtraRefCount" - nsExtraRefCount :: Ptr ObjCObject -> IO CUInt +replaceRetainedHaskellPart :: Ptr ObjCObject -> StablePtr HSO -> IO () +replaceRetainedHaskellPart self newHSO = do + dPutWords ["replaceRetainedHaskellPart", show self, show (castStablePtrToPtr newHSO)] + oldHSO <- getRetainedHaskellPart self + when (oldHSO /= newHSO) $ do + when (castStablePtrToPtr oldHSO /= nullPtr) $ do + freeStablePtr oldHSO + setRetainedHaskellPart self newHSO + +foreign import ccall "MemoryManagement.h retainSuper" + retainSuper :: Ptr ObjCObject -> Ptr ObjCObject -> IO () +foreign import ccall "MemoryManagement.h releaseSuper" + releaseSuper :: Ptr ObjCObject -> Ptr ObjCObject -> IO () +foreign import ccall unsafe "MemoryManagement.h retainCount" + retainCount :: Ptr ObjCObject -> IO CUInt -- Since finalizers are executed in arbitrary threads, we must -- ensure that we establish an autoreleasepool for the duration @@ -147,54 +168,52 @@ importImmortal = importArgument' True --- this is where the mogic happens. +-- this is where the magic happens. importArgument' immortal p | p == nullPtr = return Nil - -- objectMapLock is a global, thanks to unsafePerformIO - | otherwise = withMVar objectMapLock $ \_ -> do - sptr <- getHaskellPart p - mbHaskellObj <- - if castStablePtrToPtr sptr /= nullPtr - then do - wptr <- deRefStablePtr sptr - deRefWeak wptr - else - return Nothing - case mbHaskellObj of - -- if the HSO already exists, we're done! - Just haskellObj -> return $ ID haskellObj - -- notice that the finalizer definition requires new_sptr - Nothing -> mdo {- it's much more pratical than fixM -} - haskellData <- makeNewHaskellData p - let haskellObj = HSO p (fromMaybe [] haskellData) - finalizer | isJust haskellData = Just $ finalizeHaskellID p new_sptr - | immortal = Nothing - | otherwise = Just $ finalizeID p new_sptr - wptr <- mkWeakPtr haskellObj finalizer - new_sptr <- newStablePtr wptr - setHaskellPart p new_sptr (if immortal then 1 else 0) - - case haskellData of - Just _ -> haskellObject_retain p - Nothing -> retainObject p - - return $ ID haskellObj + | otherwise = do + (haskellObj, retain) <- withObjectMapLock "importArgument'" $ do + mbHaskellObj <- lookupHSO p + case mbHaskellObj of + -- if the HSO already exists, we're done! + Just haskellObj -> return (haskellObj, False) + -- otherwise create one and (outside the lock) retain p + Nothing -> do + haskellObj <- makeNewHSO immortal p + return (haskellObj, True) + when retain (retainObject p) + return (ID haskellObj) + +lookupHSO p = do + sptr <- getHaskellPart p + if castStablePtrToPtr sptr /= nullPtr + then do + wptr <- deRefStablePtr sptr + deRefWeak wptr + else + return Nothing + +-- notice that wptr's finalizer definition requires new_sptr, which +-- cannot be created till after the wptr; +-- so we use 'mdo' (it's much more pratical than fixM) +makeNewHSO immortal p = mdo + haskellData <- makeNewHaskellData p + dPutWords ["got haskell data", show haskellData] + let haskellObj = HSO p (fromMaybe [] haskellData) + finalizer | immortal = Nothing + | otherwise = Just $ finalizeID p new_sptr + wptr <- mkWeakPtr haskellObj finalizer + new_sptr <- newStablePtr wptr + setHaskellPart p new_sptr (if immortal then 1 else 0) + return haskellObj finalizeID :: Ptr ObjCObject -> StablePtr (Weak HSO) -> IO () finalizeID cObj sptr = do - withMVar objectMapLock $ \_ -> removeHaskellPart cObj sptr + withObjectMapLock "finalizeID" $ removeHaskellPart cObj sptr + releaseObjectWithPool cObj freeStablePtr sptr -finalizeHaskellID :: Ptr ObjCObject -> StablePtr (Weak HSO) -> IO () -finalizeHaskellID cObj sptr = do - withMVar objectMapLock $ \_ -> removeHaskellPart cObj sptr - extraRefs <- nsExtraRefCount cObj - -- putStrLn "destroy haskelll object" - assert (extraRefs == 0) (deallocObjectWithPool cObj) - freeStablePtr sptr - --- makeNewHaskellData p = do stable <- getNewHaskellData p if (castStablePtrToPtr stable == nullPtr) @@ -204,77 +223,74 @@ freeStablePtr stable return (Just dat) -haskellObject_retain_IMP :: FFICif -> Ptr () -> Ptr (Ptr ()) -> IO (Ptr ObjCObject) -haskellObject_retain_IMP cif ret args = do +haskellObject_retain_IMP :: Ptr ObjCObject -> FFICif -> Ptr () -> Ptr (Ptr ()) -> IO (Ptr ObjCObject) +haskellObject_retain_IMP super cif ret args = do selfPtr <- peekElemOff args 0 self <- peek (castPtr selfPtr) :: IO (Ptr ObjCObject) poke (castPtr ret) self -- retain returns self - -- putStrLn "retain haskell object_IMP" - withMVar objectMapLock $ \_ -> haskellObject_retain self + dPutWords ["haskellObject_retain_IMP", show super, "<FFICif>", show ret, show args] + haskellObject_retain self super return nullPtr -- no exception -haskellObject_retain self = do - -- putStrLn "retain haskell object" - nsIncrementExtraRefCount self - - stablePtrToHaskellSelf <- getRetainedHaskellPart self - when (castStablePtrToPtr stablePtrToHaskellSelf == nullPtr) $ do - stableWeakPtrToHaskellSelf <- getHaskellPart self - when (castStablePtrToPtr stableWeakPtrToHaskellSelf /= nullPtr) $ do - weakPtrToHaskellSelf <- deRefStablePtr stableWeakPtrToHaskellSelf - mbHaskellSelf <- deRefWeak weakPtrToHaskellSelf - case mbHaskellSelf of - Just haskellSelf -> do - stablePtrToHaskellSelf <- newStablePtr haskellSelf - setRetainedHaskellPart self stablePtrToHaskellSelf - Nothing -> - -- The weak pointer will only be dealloced when there are - -- no known references from ObjC and no references from Haskell. - -- So if we get here, it's not my bug (hopefully). - -- When an object is exported (returned or passed as a parameter) - -- from Haskell, it is retained and autoreleased, so passing an - -- object from Haskell to Objective C and immediately forgetting - -- the reference (before ObjC has a chance to retain it) is safe. - - error "Error: Retaining Haskell Object that has already been released" +haskellObject_retain self super = do + dPutWords ["haskellObject_retain", show self, show super] + retainSuper self super + dPutStrLn "retained super" + + withObjectMapLock "haskellObject_retain" $ do + stablePtrToHaskellSelf <- getRetainedHaskellPart self + when (castStablePtrToPtr stablePtrToHaskellSelf == nullPtr) $ do + stableWeakPtrToHaskellSelf <- getHaskellPart self + when (castStablePtrToPtr stableWeakPtrToHaskellSelf /= nullPtr) $ do + weakPtrToHaskellSelf <- deRefStablePtr stableWeakPtrToHaskellSelf + mbHaskellSelf <- deRefWeak weakPtrToHaskellSelf + case mbHaskellSelf of + Just haskellSelf -> do + stablePtrToHaskellSelf <- newStablePtr haskellSelf + setRetainedHaskellPart self stablePtrToHaskellSelf + Nothing -> + -- The weak pointer will only be dealloced when there are + -- no known references from ObjC and no references from Haskell. + -- So if we get here, it's not my bug (hopefully). + -- When an object is exported (returned or passed as a parameter) + -- from Haskell, it is retained and autoreleased, so passing an + -- object from Haskell to Objective C and immediately forgetting + -- the reference (before ObjC has a chance to retain it) is safe. + + error "Error: Retaining Haskell Object that has already been released" -haskellObject_release_IMP :: FFICif -> Ptr () -> Ptr (Ptr ()) -> IO (Ptr ObjCObject) -haskellObject_release_IMP cif ret args = do +haskellObject_release_IMP :: Ptr ObjCObject -> FFICif -> Ptr () -> Ptr (Ptr ()) -> IO (Ptr ObjCObject) +haskellObject_release_IMP super cif ret args = do selfPtr <- peekElemOff args 0 self <- peek (castPtr selfPtr) :: IO (Ptr ObjCObject) - -- putStrLn "release haskell object_IMP" - withMVar objectMapLock $ \_ -> haskellObject_release self + dPutWords ["haskellObject_release_IMP", show super, "<FFICif>", show ret, show args] + haskellObject_release super self return nullPtr -- no exception -haskellObject_release self = do - -- putStrLn "release haskell object" - wasZero <- nsDecrementExtraRefCountWasZero self - -- nobody else should call NSDecrementExtraRefCountWasZero anyway, - -- and we're protected from ourselves by the objectMapLock - -- ==> no race condition here - refCount <- nsExtraRefCount self - - when (refCount == 0) $ do +haskellObject_release super self = do + dPutWords ["haskellObject_release", show super, show self] + retainCount+1 <- retainCount self + -- retainCount+1 because we want to know the retainCount after we + -- release; if it's about to become zero, then we won't be + -- able to call retainCount on self after the call to releaseSuper. + releaseSuper self super + -- retainCount should now contain the current retain count. + + when (retainCount == 1) $ withObjectMapLock "haskellObject_release" $ do -- no extra references -- Only the reference from the Haskell part remains, -- which means we do no longer want to have a stable pointer -- (if we have one, that is) - stablePtrToHaskellSelf <- getRetainedHaskellPart self - when (castStablePtrToPtr stablePtrToHaskellSelf /= nullPtr) $ do - freeStablePtr stablePtrToHaskellSelf - setRetainedHaskellPart self (castPtrToStablePtr nullPtr) - - when (wasZero /= 0) $ do - deallocObject self + replaceRetainedHaskellPart self (castPtrToStablePtr nullPtr) -- this is the implementation of the __getHaskellData__ selector. getHaskellData_IMP :: Ptr ObjCObject -> Maybe (IO Dynamic) -> FFICif -> Ptr () -> Ptr (Ptr ()) -> IO (Ptr ObjCObject) getHaskellData_IMP super mbDat cif ret args = do - -- putStrLn "__getHaskellData__" selfPtr <- peekElemOff args 0 self <- peek (castPtr selfPtr) :: IO (Ptr ObjCObject) + dPutWords ["__getHaskellData__", show self, show super] superDataStable <- getNewHaskellDataForClass self super superData <- if castStablePtrToPtr superDataStable == nullPtr then do ======================================= --- /trunk/hoc/HOC/HOC/NewClass.hs Sun Dec 21 13:42:00 2008 +++ /trunk/hoc/HOC/HOC/NewClass.hs Thu Aug 13 08:45:30 2009 @@ -101,14 +101,14 @@ releaseCif = getCifForSelector (undefined :: ID () -> IO ()) getHaskellDataSelector = getSelectorForName "__getHaskellData__" -getHaskellDataCif = getCifForSelector (undefined :: Class () -> ID () -> IO (ID ())) +getHaskellDataCif = getCifForSelector (undefined :: ID () -> IO (ID ())) -- actually -> IO (Ptr ()) ... -setHaskellRetainMethod methodList idx = - setMethodInList methodList idx retainSelector "@@:" retainCif haskellObject_retain_IMP - -setHaskellReleaseMethod methodList idx = - setMethodInList methodList idx releaseSelector "v@:" releaseCif haskellObject_release_IMP +setHaskellRetainMethod methodList idx super = + setMethodInList methodList idx retainSelector "@@:" retainCif (haskellObject_retain_IMP super) + +setHaskellReleaseMethod methodList idx super = + setMethodInList methodList idx releaseSelector "v@:" releaseCif (haskellObject_release_IMP super) setHaskellDataMethod methodList idx super mbDat = setMethodInList methodList idx getHaskellDataSelector "^v@:#" getHaskellDataCif (getHaskellData_IMP super mbDat) ======================================= --- /trunk/hoc/HOC_cbits/MemoryManagement.h Tue Sep 9 00:05:17 2008 +++ /trunk/hoc/HOC_cbits/MemoryManagement.h Thu Aug 13 08:45:30 2009 @@ -8,6 +8,11 @@ void retainObject(id obj); void releaseObject(id obj); + +void retainSuper(id obj, Class cls); +void releaseSuper(id obj, Class cls); +unsigned int retainCount(id obj); + void deallocObject(id obj); void autoreleaseObject(id obj); ======================================= --- /trunk/hoc/HOC_cbits/MemoryManagement.m Tue Sep 9 00:05:17 2008 +++ /trunk/hoc/HOC_cbits/MemoryManagement.m Thu Aug 13 08:45:30 2009 @@ -1,3 +1,11 @@ +#ifdef GNUSTEP +#include <objc/objc-api.h> +#else +#include <objc/objc-runtime.h> +#endif + +#include <stdlib.h> + #include "MemoryManagement.h" #define DO_LOG 0 @@ -44,6 +52,7 @@ static SEL selRetain = 0; static SEL selRelease = 0; +static SEL selRetainCount = 0; static SEL selDealloc = 0; static SEL selAutorelease = 0; static SEL selAlloc = 0; @@ -55,7 +64,7 @@ if(!selRetain) selRetain = getSelectorForName("retain"); #if DO_LOG - printf("retain %p, %p\n",obj,obj->class_pointer); + printf("retain %p, %p\n",obj,obj->isa); #endif objc_msgSend(obj,selRetain); } @@ -65,10 +74,60 @@ if(!selRelease) selRelease = getSelectorForName("release"); #if DO_LOG - printf("release %p, %p\n",obj,obj->class_pointer); + printf("release %p, %p\n",obj,obj->isa); #endif objc_msgSend(obj,selRelease); } + +void retainSuper(id obj, Class cls) +{ + if(!selRetain) + selRetain = getSelectorForName("retain"); + +#if DO_LOG + printf("retain super %p, %p\n",obj,cls); +#endif + + struct objc_super * super = calloc(1, sizeof(struct objc_super)); + + super->receiver = obj; + super->super_class = cls; + + objc_msgSendSuper(super, selRetain); +} + +void releaseSuper(id obj, Class cls) +{ + if(!selRelease) + selRelease = getSelectorForName("release"); + +#if DO_LOG + printf("release super %p, %p\n",obj,cls); +#endif + + struct objc_super * super = calloc(1, sizeof(struct objc_super)); + + super->receiver = obj; + super->super_class = cls; + + objc_msgSendSuper(super, selRelease); +} + +unsigned int retainCount(id obj) { + unsigned int rc; + +#if DO_LOG + printf("retainCount %p = ",obj); +#endif + if(!selRetainCount) + selRetainCount = getSelectorForName("retainCount"); + + rc = (unsigned int) objc_msgSend(obj,selRetainCount); +#if DO_LOG + printf("%d\n",rc); +#endif + return rc; +} void deallocObject(id obj) { ======================================= --- /trunk/hoc/InterfaceGenerator2/Output.hs Tue Aug 11 10:37:55 2009 +++ /trunk/hoc/InterfaceGenerator2/Output.hs Thu Aug 13 08:45:30 2009 @@ -66,7 +66,8 @@ <+> textBS (eHaskellName e) <> text "MetaClass") pprHsBoot entityPile modName entities - = text "module" <+> textBS modName <+> text "where" $+$ + = text "{-# OPTIONS -fglasgow-exts #-}" $+$ + text "module" <+> textBS modName <+> text "where" $+$ text "import HOC" $+$ vcat imports $+$ vcat classes @@ -84,7 +85,9 @@ <+> parens (textBS name <> char '_' <+> char 'a') $+$ text "type" <+> textBS name <> text "MetaClass" <+> char 'a' <+> equals <+> text (maybe "MetaClass" ( (++ "MetaClass") . BS.unpack . eHaskellName ) mbSuper) - <+> parens (textBS name <> char '_' <+> char 'a') + <+> parens (textBS name <> char '_' <+> char 'a') $+$ + text "instance" <+> text "ClassObject" <+> parens (textBS name <> text "Class" <+> text "()") $+$ + text "_" <> textBS name <+> text "::" <+> textBS name <> text "Class" <+> text "()" | (name, mbSuper) <- classes0 ] |
From: <cod...@go...> - 2009-08-13 15:46:16
|
Revision: 401 Author: jam...@us... Date: Thu Aug 13 08:45:08 2009 Log: Fixed CIF types for methods registered in NewClass.hs http://code.google.com/p/hoc/source/detail?r=401 Modified: / /branches/objc2/hoc/HOC/HOC/NewClass.hs ======================================= --- /branches/objc2/hoc/HOC/HOC/NewClass.hs Fri Jan 9 18:06:02 2009 +++ /branches/objc2/hoc/HOC/HOC/NewClass.hs Thu Aug 13 08:45:08 2009 @@ -95,13 +95,13 @@ return list retainSelector = getSelectorForName "retain" -retainCif = getCifForSelector (undefined :: Class () -> ID () -> IO (ID ())) +retainCif = getCifForSelector (undefined :: ID () -> IO (ID ())) releaseSelector = getSelectorForName "release" -releaseCif = getCifForSelector (undefined :: Class () -> ID () -> IO ()) +releaseCif = getCifForSelector (undefined :: ID () -> IO ()) getHaskellDataSelector = getSelectorForName "__getHaskellData__" -getHaskellDataCif = getCifForSelector (undefined :: Class () -> ID () -> IO (ID ())) +getHaskellDataCif = getCifForSelector (undefined :: ID () -> IO (ID ())) -- actually -> IO (Ptr ()) ... setHaskellRetainMethod methodList idx super = |
From: <cod...@go...> - 2009-08-12 18:21:25
|
Revision: 400 Author: wol...@gm... Date: Wed Aug 12 11:20:08 2009 Log: Let's be honest, this TODO file is dead. http://code.google.com/p/hoc/source/detail?r=400 Deleted: /trunk/hoc/TODO ======================================= --- /trunk/hoc/TODO Tue Jun 1 00:56:11 2004 +++ /dev/null @@ -1,7 +0,0 @@ -Mac OS X installer package - -Xcode integration - -Hmmm... but it doesn't even rebuild them now when it needs to - can we -make the build-stamp depend on something like *.hs? - |
From: <cod...@go...> - 2009-08-12 13:52:51
|
Revision: 399 Author: jam...@us... Date: Wed Aug 12 06:26:19 2009 Log: Cleaned up HOC.ID.importArgument', from r380. r380 is presently the only difference between the objc2 branch and the trunk, as far as I know. http://code.google.com/p/hoc/source/detail?r=399 Modified: / /branches/objc2/hoc/HOC/HOC/ID.hs ======================================= --- /branches/objc2/hoc/HOC/HOC/ID.hs Fri Jan 9 16:57:06 2009 +++ /branches/objc2/hoc/HOC/HOC/ID.hs Wed Aug 12 06:26:19 2009 @@ -171,37 +171,41 @@ -- this is where the magic happens. importArgument' immortal p | p == nullPtr = return Nil - -- do what needs to be done in the lock, return what - -- needs to be done outside the lock (specifically, - -- the retain needs to be done outside the lock). - | otherwise = join $ withObjectMapLock "importArgument'" $ do - sptr <- getHaskellPart p - mbHaskellObj <- - if castStablePtrToPtr sptr /= nullPtr - then do - wptr <- deRefStablePtr sptr - deRefWeak wptr - else - return Nothing - case mbHaskellObj of - -- if the HSO already exists, we're done! - Just haskellObj -> return $ return $ ID haskellObj - -- notice that the finalizer definition requires new_sptr - Nothing -> mdo {- it's much more pratical than fixM -} - haskellData <- makeNewHaskellData p - dPutWords ["got haskell data", show haskellData] - let haskellObj = HSO p (fromMaybe [] haskellData) - finalizer | immortal = Nothing - | otherwise = Just $ finalizeID p new_sptr - wptr <- mkWeakPtr haskellObj finalizer - new_sptr <- newStablePtr wptr - setHaskellPart p new_sptr (if immortal then 1 else 0) - - return $ do - -- retain the object, but do it outside the - -- lock because the retain IMP may need the lock. - retainObject p - return $ ID haskellObj + | otherwise = do + (haskellObj, retain) <- withObjectMapLock "importArgument'" $ do + mbHaskellObj <- lookupHSO p + case mbHaskellObj of + -- if the HSO already exists, we're done! + Just haskellObj -> return (haskellObj, False) + -- otherwise create one and (outside the lock) retain p + Nothing -> do + haskellObj <- makeNewHSO immortal p + return (haskellObj, True) + when retain (retainObject p) + return (ID haskellObj) + +lookupHSO p = do + sptr <- getHaskellPart p + if castStablePtrToPtr sptr /= nullPtr + then do + wptr <- deRefStablePtr sptr + deRefWeak wptr + else + return Nothing + +-- notice that wptr's finalizer definition requires new_sptr, which +-- cannot be created till after the wptr; +-- so we use 'mdo' (it's much more pratical than fixM) +makeNewHSO immortal p = mdo + haskellData <- makeNewHaskellData p + dPutWords ["got haskell data", show haskellData] + let haskellObj = HSO p (fromMaybe [] haskellData) + finalizer | immortal = Nothing + | otherwise = Just $ finalizeID p new_sptr + wptr <- mkWeakPtr haskellObj finalizer + new_sptr <- newStablePtr wptr + setHaskellPart p new_sptr (if immortal then 1 else 0) + return haskellObj finalizeID :: Ptr ObjCObject -> StablePtr (Weak HSO) -> IO () finalizeID cObj sptr = do |
From: <cod...@go...> - 2009-08-12 13:26:41
|
Revision: 398 Author: jam...@us... Date: Wed Aug 12 06:26:10 2009 Log: (objc2 branch) merging changes from trunk (r392-r397) http://code.google.com/p/hoc/source/detail?r=398 Added: /branches/objc2/hoc/Samples/Browser/Browser.cabal /branches/objc2/hoc/Samples/Browser/Contents/Resources/all-selectors.txt /branches/objc2/hoc/Samples/Browser/Setup.hs /branches/objc2/hoc/Samples/Editor/Editor.cabal /branches/objc2/hoc/Samples/Editor/Setup.hs /branches/objc2/hoc/Samples/ExpressionParser/ExpressionParser.cabal /branches/objc2/hoc/Samples/ExpressionParser/Setup.hs /branches/objc2/hoc/Samples/UniqSort/UniqSort.cabal Deleted: /branches/objc2/hoc/AppKit /branches/objc2/hoc/BUILDING.CVS /branches/objc2/hoc/Foundation /branches/objc2/hoc/HOC/HOC.conf.in /branches/objc2/hoc/HOC/Makefile.in /branches/objc2/hoc/InterfaceGenerator /branches/objc2/hoc/Makefile.in /branches/objc2/hoc/Samples/Browser/Makefile /branches/objc2/hoc/Samples/Editor/Makefile /branches/objc2/hoc/Samples/ExpressionParser/Makefile /branches/objc2/hoc/Samples/UniqSort/Makefile /branches/objc2/hoc/Tests/Makefile /branches/objc2/hoc/Tools/Makefile.in /branches/objc2/hoc/aclocal.m4 /branches/objc2/hoc/autogen.sh /branches/objc2/hoc/autotools /branches/objc2/hoc/config.mk.in /branches/objc2/hoc/configure.ac /branches/objc2/hoc/objc.m4 Modified: / /branches/objc2/hoc /branches/objc2/hoc/README.txt /branches/objc2/hoc/Samples/Browser/BrowserController.hs /branches/objc2/hoc/Samples/Browser/Main.hs /branches/objc2/hoc/Samples/Browser/TVUtilities.hs /branches/objc2/hoc/Samples/Editor/HaskellDocument.hs /branches/objc2/hoc/Samples/UniqSort/UniqSort.hs /branches/objc2/hoc/Tests/TestFoundation.hs /branches/objc2/hoc/Tools/HOCWrap.hs ======================================= --- /dev/null +++ /branches/objc2/hoc/Samples/Browser/Browser.cabal Wed Aug 12 06:26:10 2009 @@ -0,0 +1,12 @@ +name: Browser +Cabal-Version: >= 1.2 +version: 1.0 +build-type: Custom + +executable: Browser +main-is: Main.hs +build-depends: base, array, + HOC, HOC-Cocoa, HOC-Foundation, HOC-AppKit, parsec >= 3.0 + +-- reduce executable size by *a lot*: +ghc-options: -optl-Wl,-dead_strip ======================================= --- /dev/null +++ /branches/objc2/hoc/Samples/Browser/Contents/Resources/all-selectors.txt Wed Aug 12 06:26:10 2009 @@ -0,0 +1,6359 @@ +("usesAlternatingRowBackgroundColors","usesAlternatingRowBackgroundColors","IO Bool","AppKit.NSTableView") +("initAsTearOff","initAsTearOff","IO Inited","AppKit.NSMenuView") +("pasteboardChangedOwner","pasteboardChangedOwner:","forall t1 . NSPasteboard t1 -> IO ()","AppKit.NSPasteboard") +("fontWithNameSize","fontWithName:size:","forall t1 . NSString t1 -> Float -> IO (NSFont ())","AppKit.NSFont") +("makeNextSegmentKey","makeNextSegmentKey","IO ()","AppKit.NSSegmentedCell") +("sharedCredentialStorage","sharedCredentialStorage","IO (NSURLCredentialStorage ())","Foundation.NSURLCredentialStorage") +("drawSheetBorderWithSize","drawSheetBorderWithSize:","NSSize -> IO ()","AppKit.NSView") +("subscriptRange","subscriptRange:","NSRange -> IO ()","AppKit.NSAttributedString") +("replaceObjectsInRangeWithObjectsFromArray","replaceObjectsInRange:withObjectsFromArray:","forall t2 . NSRange -> NSArray t2 -> IO ()","Foundation.NSArray") +("setFileAttributes","setFileAttributes:","forall t1 . NSDictionary t1 -> IO ()","AppKit.NSFileWrapper") +("browserCreateRowsForColumnInMatrix","browser:createRowsForColumn:inMatrix:","forall t1 t3 . NSBrowser t1 -> Int -> NSMatrix t3 -> IO ()","AppKit.NSBrowser") +("initWithContent","initWithContent:","forall t1 . ID t1 -> IO Inited","AppKit.NSObjectController") +("arrangeInFront","arrangeInFront:","forall t1 . ID t1 -> IO ()","AppKit.NSApplication") +("helpRequested","helpRequested:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSResponder") +("helpRequested","helpRequested:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSMenu") +("movieUnfilteredPasteboardTypes","movieUnfilteredPasteboardTypes","IO (NSArray ())","AppKit.NSMovie") +("valueWithObjCType","value:withObjCType:","Ptr () -> Ptr CChar -> IO (NSValue ())","Foundation.NSValue") +("setStartSubelementIdentifier","setStartSubelementIdentifier:","NSWhoseSubelementIdentifier -> IO ()","Foundation.NSScriptObjectSpecifiers") +("initWithTimeIntervalSinceDate","initWithTimeInterval:sinceDate:","forall t2 . NSTimeInterval -> NSDate t2 -> IO Inited","Foundation.NSDate") +("setData","setData:","forall t1 . NSData t1 -> IO ()","Foundation.NSData") +("setHorizontalPagination","setHorizontalPagination:","NSPrintingPaginationMode -> IO ()","AppKit.NSPrintInfo") +("imageWillLoadRepresentation","image:willLoadRepresentation:","forall t1 t2 . NSImage t1 -> NSImageRep t2 -> IO ()","AppKit.NSImage") +("countWordsInStringLanguage","countWordsInString:language:","forall t1 t2 . NSString t1 -> NSString t2 -> IO Int","AppKit.NSSpellChecker") +("resizeLeftCursor","resizeLeftCursor","IO (NSCursor ())","AppKit.NSCursor") +("relativePath","relativePath","IO (NSString ())","Foundation.NSURL") +("valueWithPointer","valueWithPointer:","Ptr () -> IO (NSValue ())","Foundation.NSValue") +("serializeInt","serializeInt:","Int -> IO ()","Foundation.NSSerialization") +("writeToFileOfTypeOriginalFileSaveOperation","writeToFile:ofType:originalFile:saveOperation:","forall t1 t2 t3 . NSString t1 -> NSString t2 -> NSString t3 -> NSSaveOperationType -> IO Bool","AppKit.NSDocument") +("supportsMode","supportsMode:","Int -> IO Bool","AppKit.NSColorPicking") +("initWithURL","initWithURL:","forall t1 . NSURL t1 -> IO Inited","Foundation.NSURLRequest") +("setTimeInterval","setTimeInterval:","NSTimeInterval -> IO ()","AppKit.NSDatePicker") +("setTimeInterval","setTimeInterval:","NSTimeInterval -> IO ()","AppKit.NSDatePickerCell") +("autosaveExpandedItems","autosaveExpandedItems","IO Bool","AppKit.NSOutlineView") +("initWithContentSizePreferredEdge","initWithContentSize:preferredEdge:","NSSize -> NSRectEdge -> IO Inited","AppKit.NSDrawer") +("resetCancelButtonCell","resetCancelButtonCell","IO ()","AppKit.NSSearchFieldCell") +("setExtensionHidden","setExtensionHidden:","Bool -> IO ()","AppKit.NSSavePanel") +("setPathSeparator","setPathSeparator:","forall t1 . NSString t1 -> IO ()","AppKit.NSBrowser") +("pathSeparator","pathSeparator","IO (NSString ())","AppKit.NSBrowser") +("mouseInRect","mouse:inRect:","NSPoint -> NSRect -> IO Bool","AppKit.NSView") +("applicationDidUnhide","applicationDidUnhide:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSApplication") +("setWithSet","setWithSet:","forall t1 . NSSet t1 -> IO (ID ())","Foundation.NSSet") +("enableKeyEquivalentForDefaultButtonCell","enableKeyEquivalentForDefaultButtonCell","IO ()","AppKit.NSWindow") +("setMenuForSegment","setMenu:forSegment:","forall t1 . NSMenu t1 -> Int -> IO ()","AppKit.NSSegmentedControl") +("setMenuForSegment","setMenu:forSegment:","forall t1 . NSMenu t1 -> Int -> IO ()","AppKit.NSSegmentedCell") +("setAutorecalculatesKeyViewLoop","setAutorecalculatesKeyViewLoop:","Bool -> IO ()","AppKit.NSWindow") +("validateToolbarItem","validateToolbarItem:","forall t1 . NSToolbarItem t1 -> IO Bool","AppKit.NSToolbarItem") +("intersectsIndexesInRange","intersectsIndexesInRange:","NSRange -> IO Bool","Foundation.NSIndexSet") +("encodeRect","encodeRect:","NSRect -> IO ()","Foundation.NSGeometry") +("addColumnWithCells","addColumnWithCells:","forall t1 . NSArray t1 -> IO ()","AppKit.NSMatrix") +("setAlwaysUsesMultipleValuesMarker","setAlwaysUsesMultipleValuesMarker:","Bool -> IO ()","AppKit.NSTreeController") +("setAlwaysUsesMultipleValuesMarker","setAlwaysUsesMultipleValuesMarker:","Bool -> IO ()","AppKit.NSArrayController") +("colorUsingColorSpace","colorUsingColorSpace:","forall t1 . NSColorSpace t1 -> IO (NSColor ())","AppKit.NSColor") +("realm","realm","IO (NSString ())","Foundation.NSURLProtectionSpace") +("setCommands","setCommands:","forall t1 . NSArray t1 -> IO ()","AppKit.NSSpeechRecognizer") +("sortedArrayUsingDescriptors","sortedArrayUsingDescriptors:","forall t1 . NSArray t1 -> IO (NSArray ())","Foundation.NSSortDescriptor") +("cookiesForURL","cookiesForURL:","forall t1 . NSURL t1 -> IO (NSArray ())","Foundation.NSHTTPCookieStorage") +("setMinimumDaysInFirstWeek","setMinimumDaysInFirstWeek:","CUInt -> IO ()","Foundation.NSCalendar") +("setVolume","setVolume:","Float -> IO ()","AppKit.NSMovieView") +("postsBoundsChangedNotifications","postsBoundsChangedNotifications","IO Bool","AppKit.NSView") +("undoManager","undoManager","IO (NSUndoManager ())","AppKit.NSResponder") +("undoManager","undoManager","IO (NSUndoManager ())","AppKit.NSDocument") +("setRunLoopModes","setRunLoopModes:","forall t1 . NSArray t1 -> IO ()","Foundation.NSUndoManager") +("datePickerMode","datePickerMode","IO NSDatePickerMode","AppKit.NSDatePicker") +("datePickerMode","datePickerMode","IO NSDatePickerMode","AppKit.NSDatePickerCell") +("listOptions","listOptions","IO CUInt","AppKit.NSTextList") +("offsetInFile","offsetInFile","IO CULLong","Foundation.NSFileHandle") +("setAttributedAlternateTitle","setAttributedAlternateTitle:","forall t1 . NSAttributedString t1 -> IO ()","AppKit.NSButton") +("setAttributedAlternateTitle","setAttributedAlternateTitle:","forall t1 . NSAttributedString t1 -> IO ()","AppKit.NSButtonCell") +("usedRectForTextContainer","usedRectForTextContainer:","forall t1 . NSTextContainer t1 -> IO NSRect","AppKit.NSLayoutManager") +("unarchiveObjectWithData","unarchiveObjectWithData:","forall t1 . NSData t1 -> IO (ID ())","Foundation.NSKeyedArchiver") +("unarchiveObjectWithData","unarchiveObjectWithData:","forall t1 . NSData t1 -> IO (ID ())","Foundation.NSArchiver") +("punctuationCharacterSet","punctuationCharacterSet","IO (NSCharacterSet ())","Foundation.NSCharacterSet") +("filePosixPermissions","filePosixPermissions","IO CULong","Foundation.NSFileManager") +("initWithUTF8String","initWithUTF8String:","Ptr CChar -> IO Inited","Foundation.NSString") +("saveFrameUsingName","saveFrameUsingName:","forall t1 . NSString t1 -> IO ()","AppKit.NSWindow") +("initWithLongLong","initWithLongLong:","CLLong -> IO Inited","Foundation.NSValue") +("canonicalLocaleIdentifierFromString","canonicalLocaleIdentifierFromString:","forall t1 . NSString t1 -> IO (NSString ())","Foundation.NSLocale") +("levelForRow","levelForRow:","Int -> IO Int","AppKit.NSOutlineView") +("acceptableDragTypes","acceptableDragTypes","IO (NSArray ())","AppKit.NSTextView") +("minDate","minDate","IO (NSDate ())","AppKit.NSDatePicker") +("minDate","minDate","IO (NSDate ())","AppKit.NSDatePickerCell") +("formatter","formatter","IO (ID ())","AppKit.NSControl") +("formatter","formatter","IO (ID ())","AppKit.NSCell") +("drawers","drawers","IO (NSArray ())","AppKit.NSDrawer") +("soundDidFinishPlaying","sound:didFinishPlaying:","forall t1 . NSSound t1 -> Bool -> IO ()","AppKit.NSSound") +("setWeekday","setWeekday:","Int -> IO ()","Foundation.NSCalendar") +("setWeek","setWeek:","Int -> IO ()","Foundation.NSCalendar") +("performClickWithFrameInView","performClickWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSPopUpButtonCell") +("addTabViewItem","addTabViewItem:","forall t1 . NSTabViewItem t1 -> IO ()","AppKit.NSTabView") +("setHiddenUntilMouseMoves","setHiddenUntilMouseMoves:","Bool -> IO ()","AppKit.NSCursor") +("resourceData","resourceData","IO (NSData ())","Foundation.NSURLHandle") +("isTransparent","isTransparent","IO Bool","AppKit.NSButton") +("isTransparent","isTransparent","IO Bool","AppKit.NSButtonCell") +("elementWithNameChildrenAttributes","elementWithName:children:attributes:","forall t1 t2 t3 . NSString t1 -> NSArray t2 -> NSArray t3 -> IO (ID ())","Foundation.NSXMLNode") +("resetTotalAutoreleasedObjects","resetTotalAutoreleasedObjects","IO ()","Foundation.NSDebug") +("currentMode","currentMode","IO Int","AppKit.NSColorPicking") +("currentMode","currentMode","IO (NSString ())","Foundation.NSRunLoop") +("namespaceForPrefix","namespaceForPrefix:","forall t1 . NSString t1 -> IO (NSXMLNode ())","Foundation.NSXMLElement") +("selectedTextAttributes","selectedTextAttributes","IO (NSDictionary ())","AppKit.NSTextView") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSSound") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSMovie") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSImageRep") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSImage") +("representationUsingTypeProperties","representationUsingType:properties:","forall t2 . NSBitmapImageFileType -> NSDictionary t2 -> IO (NSData ())","AppKit.NSBitmapImageRep") +("isMovable","isMovable","IO Bool","AppKit.NSRulerMarker") +("menuFontOfSize","menuFontOfSize:","Float -> IO (NSFont ())","AppKit.NSFont") +("accessibilityAttributeValue","accessibilityAttributeValue:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSAccessibility") +("setDTD","setDTD:","forall t1 . NSXMLDTD t1 -> IO ()","Foundation.NSXMLDocument") +("attributedSubstringFromRange","attributedSubstringFromRange:","NSRange -> IO (NSAttributedString ())","AppKit.NSInputManager") +("attributedSubstringFromRange","attributedSubstringFromRange:","NSRange -> IO (NSAttributedString ())","Foundation.NSAttributedString") +("scaleBy","scaleBy:","Float -> IO ()","Foundation.NSAffineTransform") +("noteNewRecentDocument","noteNewRecentDocument:","forall t1 . NSDocument t1 -> IO ()","AppKit.NSDocumentController") +("dtdnodeWithXMLString","DTDNodeWithXMLString:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSXMLNode") +("menuBarHeight","menuBarHeight","IO Float","AppKit.NSMenuView") +("menuBarHeight","menuBarHeight","IO Float","AppKit.NSMenu") +("isAnyApplicationSpeaking","isAnyApplicationSpeaking","IO Bool","AppKit.NSSpeechSynthesizer") +("canUndo","canUndo","IO Bool","Foundation.NSUndoManager") +("rulerViewWillAddMarkerAtLocation","rulerView:willAddMarker:atLocation:","forall t1 t2 . NSRulerView t1 -> NSRulerMarker t2 -> Float -> IO Float","AppKit.NSRulerView") +("applicationDidHide","applicationDidHide:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSApplication") +("readToEndOfFileInBackgroundAndNotifyForModes","readToEndOfFileInBackgroundAndNotifyForModes:","forall t1 . NSArray t1 -> IO ()","Foundation.NSFileHandle") +("setCriticalValue","setCriticalValue:","Double -> IO ()","AppKit.NSLevelIndicator") +("setCriticalValue","setCriticalValue:","Double -> IO ()","AppKit.NSLevelIndicatorCell") +("criticalValue","criticalValue","IO Double","AppKit.NSLevelIndicator") +("criticalValue","criticalValue","IO Double","AppKit.NSLevelIndicatorCell") +("acceptsArrowKeys","acceptsArrowKeys","IO Bool","AppKit.NSBrowser") +("commitEditingWithDelegateDidCommitSelectorContextInfo","commitEditingWithDelegate:didCommitSelector:contextInfo:","forall t1 . ID t1 -> SEL -> Ptr () -> IO ()","AppKit.NSKeyValueBinding") +("setImageScaling","setImageScaling:","NSImageScaling -> IO ()","AppKit.NSImageView") +("setImageScaling","setImageScaling:","NSImageScaling -> IO ()","AppKit.NSImageCell") +("open","open","IO ()","AppKit.NSDrawer") +("open","open","IO ()","Foundation.NSStream") +("initWithBytesNoCopyLength","initWithBytesNoCopy:length:","Ptr () -> CUInt -> IO Inited","Foundation.NSData") +("underline","underline:","forall t1 . ID t1 -> IO ()","AppKit.NSText") +("resetCursorRects","resetCursorRects","IO ()","AppKit.NSWindow") +("resetCursorRects","resetCursorRects","IO ()","AppKit.NSView") +("secondsFromGMTForDate","secondsFromGMTForDate:","forall t1 . NSDate t1 -> IO Int","Foundation.NSTimeZone") +("postNotificationNameObject","postNotificationName:object:","forall t1 t2 . NSString t1 -> ID t2 -> IO ()","Foundation.NSNotification") +("setMiniwindowImage","setMiniwindowImage:","forall t1 . NSImage t1 -> IO ()","AppKit.NSWindow") +("selectorForCommand","selectorForCommand:","forall t1 . NSScriptCommandDescription t1 -> IO SEL","Foundation.NSScriptClassDescription") +("postNotificationNameObjectUserInfoOptions","postNotificationName:object:userInfo:options:","forall t1 t2 t3 . NSString t1 -> NSString t2 -> NSDictionary t3 -> CUInt -> IO ()","Foundation.NSDistributedNotificationCenter") +("selectItemWithTitle","selectItemWithTitle:","forall t1 . NSString t1 -> IO ()","AppKit.NSPopUpButtonCell") +("selectItemWithTitle","selectItemWithTitle:","forall t1 . NSString t1 -> IO ()","AppKit.NSPopUpButton") +("attachSubmenuForItemAtIndex","attachSubmenuForItemAtIndex:","Int -> IO ()","AppKit.NSMenuView") +("valueWraps","valueWraps","IO Bool","AppKit.NSStepper") +("valueWraps","valueWraps","IO Bool","AppKit.NSStepperCell") +("getFirstUnlaidCharacterIndexGlyphIndex","getFirstUnlaidCharacterIndex:glyphIndex:","Ptr CUInt -> Ptr CUInt -> IO ()","AppKit.NSLayoutManager") +("dictionaryFromTXTRecordData","dictionaryFromTXTRecordData:","forall t1 . NSData t1 -> IO (NSDictionary ())","Foundation.NSNetServices") +("setRequestTimeout","setRequestTimeout:","NSTimeInterval -> IO ()","Foundation.NSConnection") +("string","string","IO (NSString ())","AppKit.NSText") +("string","string","IO (ID ())","Foundation.NSString") +("string","string","IO (NSString ())","Foundation.NSScanner") +("string","string","IO (NSString ())","Foundation.NSAttributedString") +("drawerWillOpen","drawerWillOpen:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSDrawer") +("fontWithDescriptorSize","fontWithDescriptor:size:","forall t1 . NSFontDescriptor t1 -> Float -> IO (NSFont ())","AppKit.NSFont") +("archiverDidFinish","archiverDidFinish:","forall t1 . NSKeyedArchiver t1 -> IO ()","Foundation.NSKeyedArchiver") +("setPredicate","setPredicate:","forall t1 . NSPredicate t1 -> IO ()","Foundation.NSMetadata") +("setIconForFileOptions","setIcon:forFile:options:","forall t1 t2 . NSImage t1 -> NSString t2 -> CUInt -> IO Bool","AppKit.NSWorkspace") +("setFileModificationDate","setFileModificationDate:","forall t1 . NSDate t1 -> IO ()","AppKit.NSDocument") +("elementCount","elementCount","IO Int","AppKit.NSBezierPath") +("docFormatFromRangeDocumentAttributes","docFormatFromRange:documentAttributes:","forall t2 . NSRange -> NSDictionary t2 -> IO (NSData ())","AppKit.NSAttributedString") +("setNilValueForKey","setNilValueForKey:","forall t1 . NSString t1 -> IO ()","Foundation.NSKeyValueCoding") +("dictionaryWithContentsOfFile","dictionaryWithContentsOfFile:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSDictionary") +("initWithWindowRect","initWithWindow:rect:","forall t1 . NSWindow t1 -> NSRect -> IO Inited","AppKit.NSCachedImageRep") +("textStorageDidProcessEditing","textStorageDidProcessEditing:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSTextStorage") +("addNamespace","addNamespace:","forall t1 . NSXMLNode t1 -> IO ()","Foundation.NSXMLElement") +("urlhandleResourceDidBeginLoading","URLHandleResourceDidBeginLoading:","forall t1 . NSURLHandle t1 -> IO ()","Foundation.NSURLHandle") +("knownTimeZoneNames","knownTimeZoneNames","IO (NSArray ())","Foundation.NSTimeZone") +("encodeFloatForKey","encodeFloat:forKey:","forall t2 . Float -> NSString t2 -> IO ()","Foundation.NSCoder") +("contentSizeForFrameSizeHasHorizontalScrollerHasVerticalScrollerBorderType","contentSizeForFrameSize:hasHorizontalScroller:hasVerticalScroller:borderType:","NSSize -> Bool -> Bool -> NSBorderType -> IO NSSize","AppKit.NSScrollView") +("startSubelementIdentifier","startSubelementIdentifier","IO NSWhoseSubelementIdentifier","Foundation.NSScriptObjectSpecifiers") +("documents","documents","IO (NSArray ())","AppKit.NSDocumentController") +("setAlternateMnemonicLocation","setAlternateMnemonicLocation:","CUInt -> IO ()","AppKit.NSButtonCell") +("insertItemWithTitleActionKeyEquivalentAtIndex","insertItemWithTitle:action:keyEquivalent:atIndex:","forall t1 t3 . NSString t1 -> SEL -> NSString t3 -> Int -> IO (ID ())","AppKit.NSMenu") +("tokenFieldCellDisplayStringForRepresentedObject","tokenFieldCell:displayStringForRepresentedObject:","forall t1 t2 . NSTokenFieldCell t1 -> ID t2 -> IO (NSString ())","AppKit.NSTokenFieldCell") +("setReusesColumns","setReusesColumns:","Bool -> IO ()","AppKit.NSBrowser") +("checkSpaceForParts","checkSpaceForParts","IO ()","AppKit.NSScroller") +("preservesContentDuringLiveResize","preservesContentDuringLiveResize","IO Bool","AppKit.NSWindow") +("preservesContentDuringLiveResize","preservesContentDuringLiveResize","IO Bool","AppKit.NSView") +("scrollRectBy","scrollRect:by:","NSRect -> NSSize -> IO ()","AppKit.NSView") +("opaqueAncestor","opaqueAncestor","IO (NSView ())","AppKit.NSView") +("cellSize","cellSize","IO NSSize","AppKit.NSMatrix") +("cellSize","cellSize","IO NSSize","AppKit.NSTextAttachment") +("cellSize","cellSize","IO NSSize","AppKit.NSCell") +("adjustSubviews","adjustSubviews","IO ()","AppKit.NSSplitView") +("setVerticalRulerView","setVerticalRulerView:","forall t1 . NSRulerView t1 -> IO ()","AppKit.NSScrollView") +("readFileWrapper","readFileWrapper","IO (NSFileWrapper ())","AppKit.NSPasteboard") +("initWithUser","initWithUser:","forall t1 . NSString t1 -> IO Inited","Foundation.NSUserDefaults") +("outlineViewColumnDidResize","outlineViewColumnDidResize:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSOutlineView") +("animate","animate:","forall t1 . ID t1 -> IO ()","AppKit.NSProgressIndicator") +("setTextStorage","setTextStorage:","forall t1 . NSTextStorage t1 -> IO ()","AppKit.NSLayoutManager") +("validateMenuItem","validateMenuItem:","forall t1 . ID t1 -> IO Bool","AppKit.NSMenu") +("fileHandleForWriting","fileHandleForWriting","IO (NSFileHandle ())","Foundation.NSFileHandle") +("textViewDoubleClickedOnCellInRectAtIndex","textView:doubleClickedOnCell:inRect:atIndex:","forall t1 t2 . NSTextView t1 -> ID t2 -> NSRect -> CUInt -> IO ()","AppKit.NSTextView") +("textViewDoubleClickedOnCellInRect","textView:doubleClickedOnCell:inRect:","forall t1 t2 . NSTextView t1 -> ID t2 -> NSRect -> IO ()","AppKit.NSTextView") +("addTableColumn","addTableColumn:","forall t1 . NSTableColumn t1 -> IO ()","AppKit.NSTableView") +("sharedSystemTypesetter","sharedSystemTypesetter","IO (ID ())","AppKit.NSTypesetter") +("mouseDownFlags","mouseDownFlags","IO Int","AppKit.NSMatrix") +("mouseDownFlags","mouseDownFlags","IO Int","AppKit.NSCell") +("setFullScreen","setFullScreen","IO ()","AppKit.NSOpenGL") +("setStartSpecifier","setStartSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("stopMonitoring","stopMonitoring","IO ()","Foundation.NSNetServices") +("worksWhenModal","worksWhenModal","IO Bool","AppKit.NSWindow") +("windowDidUpdate","windowDidUpdate:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSWindow") +("setBlocksOtherRecognizers","setBlocksOtherRecognizers:","Bool -> IO ()","AppKit.NSSpeechRecognizer") +("parserFoundExternalEntityDeclarationWithNamePublicIDSystemID","parser:foundExternalEntityDeclarationWithName:publicID:systemID:","forall t1 t2 t3 t4 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> NSString t4 -> IO ()","Foundation.NSXMLParser") +("rotation","rotation","IO Float","AppKit.NSEvent") +("connection","connection","IO (NSConnection ())","Foundation.NSPortCoder") +("connection","connection","IO (NSConnection ())","Foundation.NSConnection") +("resumeExecutionWithResult","resumeExecutionWithResult:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptCommand") +("dictionaryWithObjectForKey","dictionaryWithObject:forKey:","forall t1 t2 . ID t1 -> ID t2 -> IO (ID ())","Foundation.NSDictionary") +("stringByResolvingSymlinksInPath","stringByResolvingSymlinksInPath","IO (NSString ())","Foundation.NSPathUtilities") +("initWithNameData","initWithName:data:","forall t1 t2 . NSString t1 -> NSData t2 -> IO Inited","Foundation.NSTimeZone") +("outlineViewShouldCollapseItem","outlineView:shouldCollapseItem:","forall t1 t2 . NSOutlineView t1 -> ID t2 -> IO Bool","AppKit.NSOutlineView") +("indexOfTabViewItemWithIdentifier","indexOfTabViewItemWithIdentifier:","forall t1 . ID t1 -> IO Int","AppKit.NSTabView") +("lineBreakBeforeIndexWithinRange","lineBreakBeforeIndex:withinRange:","CUInt -> NSRange -> IO CUInt","AppKit.NSAttributedString") +("encodeRectForKey","encodeRect:forKey:","forall t2 . NSRect -> NSString t2 -> IO ()","Foundation.NSKeyedArchiver") +("encodeConditionalObject","encodeConditionalObject:","forall t1 . ID t1 -> IO ()","Foundation.NSCoder") +("writeSelectionToPasteboardType","writeSelectionToPasteboard:type:","forall t1 t2 . NSPasteboard t1 -> NSString t2 -> IO Bool","AppKit.NSTextView") +("textUnfilteredPasteboardTypes","textUnfilteredPasteboardTypes","IO (NSArray ())","AppKit.NSAttributedString") +("downloadDidReceiveAuthenticationChallenge","download:didReceiveAuthenticationChallenge:","forall t1 t2 . NSURLDownload t1 -> NSURLAuthenticationChallenge t2 -> IO ()","Foundation.NSURLDownload") +("printPanel","printPanel","IO (NSPrintPanel ())","AppKit.NSPrintPanel") +("printPanel","printPanel","IO (NSPrintPanel ())","AppKit.NSPrintOperation") +("pointingDeviceSerialNumber","pointingDeviceSerialNumber","IO CUInt","AppKit.NSEvent") +("drawInRectFromRectOperationFraction","drawInRect:fromRect:operation:fraction:","NSRect -> NSRect -> NSCompositingOperation -> Float -> IO ()","AppKit.NSImage") +("setShowsHelp","setShowsHelp:","Bool -> IO ()","AppKit.NSAlert") +("credentialsForProtectionSpace","credentialsForProtectionSpace:","forall t1 . NSURLProtectionSpace t1 -> IO (NSDictionary ())","Foundation.NSURLCredentialStorage") +("orderFrontStandardAboutPanel","orderFrontStandardAboutPanel:","forall t1 . ID t1 -> IO ()","AppKit.NSApplication") +("insertTextClient","insertText:client:","forall t1 t2 . ID t1 -> ID t2 -> IO ()","AppKit.NSInputServer") +("isSymbolicLink","isSymbolicLink","IO Bool","AppKit.NSFileWrapper") +("documentForWindow","documentForWindow:","forall t1 . NSWindow t1 -> IO (ID ())","AppKit.NSDocumentController") +("openPanel","openPanel","IO (NSOpenPanel ())","AppKit.NSOpenPanel") +("setResolvesAliases","setResolvesAliases:","Bool -> IO ()","AppKit.NSOpenPanel") +("readableTypes","readableTypes","IO (NSArray ())","AppKit.NSDocument") +("defaultNameServerPortNumber","defaultNameServerPortNumber","IO CUShort","Foundation.NSPortNameServer") +("canCreateDirectories","canCreateDirectories","IO Bool","AppKit.NSSavePanel") +("titleWidth_","titleWidth:","NSSize -> IO Float","AppKit.NSFormCell") +("mouseDragged","mouseDragged:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSResponder") +("documentForURL","documentForURL:","forall t1 . NSURL t1 -> IO (ID ())","AppKit.NSDocumentController") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLDTDNode") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLDTD") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLParser") +("mainBundle","mainBundle","IO (NSBundle ())","Foundation.NSBundle") +("removeValueAtIndexFromPropertyWithKey","removeValueAtIndex:fromPropertyWithKey:","forall t2 . CUInt -> NSString t2 -> IO ()","Foundation.NSScriptKeyValueCoding") +("outlineViewWillDisplayOutlineCellForTableColumnItem","outlineView:willDisplayOutlineCell:forTableColumn:item:","forall t1 t2 t3 t4 . NSOutlineView t1 -> ID t2 -> NSTableColumn t3 -> ID t4 -> IO ()","AppKit.NSOutlineView") +("setContainerSize","setContainerSize:","NSSize -> IO ()","AppKit.NSTextContainer") +("usesFeedbackWindow","usesFeedbackWindow","IO Bool","AppKit.NSSpeechSynthesizer") +("layoutOptions","layoutOptions","IO CUInt","AppKit.NSGlyphGenerator") +("setLayoutAlgorithm","setLayoutAlgorithm:","NSTextTableLayoutAlgorithm -> IO ()","AppKit.NSTextTable") +("lockFocusOnRepresentation","lockFocusOnRepresentation:","forall t1 . NSImageRep t1 -> IO ()","AppKit.NSImage") +("tableView","tableView","IO (NSTableView ())","AppKit.NSTableHeaderView") +("tableView","tableView","IO (NSTableView ())","AppKit.NSTableColumn") +("openFileWithApplication","openFile:withApplication:","forall t1 t2 . NSString t1 -> NSString t2 -> IO Bool","AppKit.NSWorkspace") +("encodingScheme","encodingScheme","IO (NSString ())","AppKit.NSFont") +("doubleClickAtIndex","doubleClickAtIndex:","CUInt -> IO NSRange","AppKit.NSAttributedString") +("removeCharactersInRange","removeCharactersInRange:","NSRange -> IO ()","Foundation.NSCharacterSet") +("setFloatValue","setFloatValue:","Float -> IO ()","AppKit.NSControl") +("setFloatValue","setFloatValue:","Float -> IO ()","AppKit.NSCell") +("setInContext","setInContext:","forall t1 . NSGraphicsContext t1 -> IO ()","AppKit.NSFont") +("update","update","IO ()","AppKit.NSOpenGLView") +("update","update","IO ()","AppKit.NSMenuView") +("update","update","IO ()","AppKit.NSWindow") +("update","update","IO ()","AppKit.NSOpenGL") +("update","update","IO ()","AppKit.NSMenu") +("setPullsDown","setPullsDown:","Bool -> IO ()","AppKit.NSPopUpButtonCell") +("setPullsDown","setPullsDown:","Bool -> IO ()","AppKit.NSPopUpButton") +("setDefaultPlaceholderForMarkerWithBinding","setDefaultPlaceholder:forMarker:withBinding:","forall t1 t2 t3 . ID t1 -> ID t2 -> NSString t3 -> IO ()","AppKit.NSKeyValueBinding") +("fontDescriptorWithFace","fontDescriptorWithFace:","forall t1 . NSString t1 -> IO (NSFontDescriptor ())","AppKit.NSFontDescriptor") +("fontDescriptor","fontDescriptor","IO (NSFontDescriptor ())","AppKit.NSFont") +("setCanHide","setCanHide:","Bool -> IO ()","AppKit.NSWindow") +("removeAllToolTips","removeAllToolTips","IO ()","AppKit.NSView") +("setLineSpacing","setLineSpacing:","Float -> IO ()","AppKit.NSParagraphStyle") +("iccprofileData","ICCProfileData","IO (NSData ())","AppKit.NSColorSpace") +("useRunningCopyOfApplication","useRunningCopyOfApplication","IO ()","AppKit.NSApplication") +("defaultWritingDirectionForLanguage","defaultWritingDirectionForLanguage:","forall t1 . NSString t1 -> IO NSWritingDirection","AppKit.NSParagraphStyle") +("setIndentationMarkerFollowsCell","setIndentationMarkerFollowsCell:","Bool -> IO ()","AppKit.NSOutlineView") +("comboBoxCompletedString","comboBox:completedString:","forall t1 t2 . NSComboBox t1 -> NSString t2 -> IO (NSString ())","AppKit.NSComboBox") +("isSubviewCollapsed","isSubviewCollapsed:","forall t1 . NSView t1 -> IO Bool","AppKit.NSSplitView") +("availableFontFamilies","availableFontFamilies","IO (NSArray ())","AppKit.NSFontManager") +("accessibilityAttributeNames","accessibilityAttributeNames","IO (NSArray ())","AppKit.NSAccessibility") +("unscript","unscript:","forall t1 . ID t1 -> IO ()","AppKit.NSText") +("setAlertStyle","setAlertStyle:","NSAlertStyle -> IO ()","AppKit.NSAlert") +("verticalScroller","verticalScroller","IO (NSScroller ())","AppKit.NSScrollView") +("currentCursor","currentCursor","IO (NSCursor ())","AppKit.NSCursor") +("setVerticalPageScroll","setVerticalPageScroll:","Float -> IO ()","AppKit.NSScrollView") +("bitmapRepresentation","bitmapRepresentation","IO (NSData ())","Foundation.NSCharacterSet") +("markedRange","markedRange","IO NSRange","AppKit.NSInputManager") +("stringByPaddingToLengthWithStringStartingAtIndex","stringByPaddingToLength:withString:startingAtIndex:","forall t2 . CUInt -> NSString t2 -> CUInt -> IO (NSString ())","Foundation.NSString") +("localizedFailureReason","localizedFailureReason","IO (NSString ())","Foundation.NSError") +("keyForFileWrapper","keyForFileWrapper:","forall t1 . NSFileWrapper t1 -> IO (NSString ())","AppKit.NSFileWrapper") +("separatesColumns","separatesColumns","IO Bool","AppKit.NSBrowser") +("setSelectionIndexPath","setSelectionIndexPath:","forall t1 . NSIndexPath t1 -> IO Bool","AppKit.NSTreeController") +("decodeSizeForKey","decodeSizeForKey:","forall t1 . NSString t1 -> IO NSSize","Foundation.NSKeyedArchiver") +("windowShouldZoomToFrame","windowShouldZoom:toFrame:","forall t1 . NSWindow t1 -> NSRect -> IO Bool","AppKit.NSWindow") +("loadInForeground","loadInForeground","IO (NSData ())","Foundation.NSURLHandle") +("setObjectBeingTested","setObjectBeingTested:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptExecutionContext") +("drawWithFrameInView","drawWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSTextAttachment") +("drawWithFrameInView","drawWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSCell") +("ascender","ascender","IO Float","AppKit.NSFont") +("deserializeAlignedBytesLengthAtCursor","deserializeAlignedBytesLengthAtCursor:","Ptr CUInt -> IO CUInt","Foundation.NSSerialization") +("stateImageOffset","stateImageOffset","IO Float","AppKit.NSMenuView") +("enableMultipleThreads","enableMultipleThreads","IO ()","Foundation.NSConnection") +("sound","sound","IO (NSSound ())","AppKit.NSButton") +("sound","sound","IO (NSSound ())","AppKit.NSButtonCell") +("dateWithTimeIntervalSinceNow","dateWithTimeIntervalSinceNow:","NSTimeInterval -> IO (ID ())","Foundation.NSDate") +("isLoaded","isLoaded","IO Bool","AppKit.NSBrowser") +("isLoaded","isLoaded","IO Bool","AppKit.NSBrowserCell") +("isLoaded","isLoaded","IO Bool","Foundation.NSBundle") +("windowFrameTextColor","windowFrameTextColor","IO (NSColor ())","AppKit.NSColor") +("prefersAllColumnUserResizing","prefersAllColumnUserResizing","IO Bool","AppKit.NSBrowser") +("writeEPSInsideRectToPasteboard","writeEPSInsideRect:toPasteboard:","forall t2 . NSRect -> NSPasteboard t2 -> IO ()","AppKit.NSView") +("setLocationWithAdvancementsForStartOfGlyphRange","setLocation:withAdvancements:forStartOfGlyphRange:","NSPoint -> Ptr Float -> NSRange -> IO ()","AppKit.NSTypesetter") +("loadFileWrapperRepresentationOfType","loadFileWrapperRepresentation:ofType:","forall t1 t2 . NSFileWrapper t1 -> NSString t2 -> IO Bool","AppKit.NSDocument") +("encodePointForKey","encodePoint:forKey:","forall t2 . NSPoint -> NSString t2 -> IO ()","Foundation.NSKeyedArchiver") +("floatForKey","floatForKey:","forall t1 . NSString t1 -> IO Float","Foundation.NSUserDefaults") +("performSelectorWithObjectAfterDelayInModes","performSelector:withObject:afterDelay:inModes:","forall t2 t4 . SEL -> ID t2 -> NSTimeInterval -> NSArray t4 -> IO ()","Foundation.NSRunLoop") +("netServiceWillPublish","netServiceWillPublish:","forall t1 . NSNetService t1 -> IO ()","Foundation.NSNetServices") +("windowWillClose","windowWillClose:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSWindow") +("initWithLocaleIdentifier","initWithLocaleIdentifier:","forall t1 . NSString t1 -> IO Inited","Foundation.NSLocale") +("splitViewCanCollapseSubview","splitView:canCollapseSubview:","forall t1 t2 . NSSplitView t1 -> NSView t2 -> IO Bool","AppKit.NSSplitView") +("didChangeValueForKey","didChangeValueForKey:","forall t1 . NSString t1 -> IO ()","Foundation.NSKeyValueObserving") +("columnResizingType","columnResizingType","IO NSBrowserColumnResizingType","AppKit.NSBrowser") +("contentRect","contentRect","IO NSRect","AppKit.NSTabView") +("isFlushWindowDisabled","isFlushWindowDisabled","IO Bool","AppKit.NSWindow") +("convertFontToFace","convertFont:toFace:","forall t1 t2 . NSFont t1 -> NSString t2 -> IO (NSFont ())","AppKit.NSFontManager") +("getBytesLength","getBytes:length:","Ptr () -> CUInt -> IO ()","Foundation.NSData") +("selectionShouldChangeInTableView","selectionShouldChangeInTableView:","forall t1 . NSTableView t1 -> IO Bool","AppKit.NSTableView") +("collectionNames","collectionNames","IO (NSArray ())","AppKit.NSFontManager") +("laterDate","laterDate:","forall t1 . NSDate t1 -> IO (NSDate ())","Foundation.NSDate") +("parserFoundElementDeclarationWithNameModel","parser:foundElementDeclarationWithName:model:","forall t1 t2 t3 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> IO ()","Foundation.NSXMLParser") +("allHeaderFields","allHeaderFields","IO (NSDictionary ())","Foundation.NSURLResponse") +("fontDescriptorWithMatrix","fontDescriptorWithMatrix:","forall t1 . NSAffineTransform t1 -> IO (NSFontDescriptor ())","AppKit.NSFontDescriptor") +("indexOfItemAtPoint","indexOfItemAtPoint:","NSPoint -> IO Int","AppKit.NSMenuView") +("textView","textView","IO (NSTextView ())","AppKit.NSTextContainer") +("insertDescriptorAtIndex","insertDescriptor:atIndex:","forall t1 . NSAppleEventDescriptor t1 -> CLong -> IO ()","Foundation.NSAppleEventDescriptor") +("initWithWindowNibPathOwner","initWithWindowNibPath:owner:","forall t1 t2 . NSString t1 -> ID t2 -> IO Inited","AppKit.NSWindowController") +("addSubview","addSubview:","forall t1 . NSView t1 -> IO ()","AppKit.NSView") +("isEntryAcceptable","isEntryAcceptable:","forall t1 . NSString t1 -> IO Bool","AppKit.NSCell") +("rectValue","rectValue","IO NSRect","Foundation.NSGeometry") +("deltaX","deltaX","IO Float","AppKit.NSEvent") +("defaultManager","defaultManager","IO (NSFileManager ())","Foundation.NSFileManager") +("deltaY","deltaY","IO Float","AppKit.NSEvent") +("setLineWidth","setLineWidth:","Float -> IO ()","AppKit.NSBezierPath") +("performSelectorWithObjectAfterDelay","performSelector:withObject:afterDelay:","forall t2 . SEL -> ID t2 -> NSTimeInterval -> IO ()","Foundation.NSRunLoop") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTextField") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSMatrix") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSDatePicker") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTextFieldCell") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSText") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTabView") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSScrollView") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSDatePickerCell") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSClipView") +("needsDisplay","needsDisplay","IO Bool","AppKit.NSMenuItemCell") +("needsDisplay","needsDisplay","IO Bool","AppKit.NSView") +("applicationShouldHandleReopenHasVisibleWindows","applicationShouldHandleReopen:hasVisibleWindows:","forall t1 . NSApplication t1 -> Bool -> IO Bool","AppKit.NSApplication") +("deltaZ","deltaZ","IO Float","AppKit.NSEvent") +("initWithRequestDelegate","initWithRequest:delegate:","forall t1 t2 . NSURLRequest t1 -> ID t2 -> IO Inited","Foundation.NSURLDownload") +("initWithRequestDelegate","initWithRequest:delegate:","forall t1 t2 . NSURLRequest t1 -> ID t2 -> IO Inited","Foundation.NSURLConnection") +("increaseLengthBy","increaseLengthBy:","CUInt -> IO ()","Foundation.NSData") +("fileSystemChanged","fileSystemChanged","IO Bool","AppKit.NSWorkspace") +("imageDidNotDrawInRect","imageDidNotDraw:inRect:","forall t1 . ID t1 -> NSRect -> IO (NSImage ())","AppKit.NSImage") +("setCurrentDirectoryPath","setCurrentDirectoryPath:","forall t1 . NSString t1 -> IO ()","Foundation.NSTask") +("heightTracksTextView","heightTracksTextView","IO Bool","AppKit.NSTextContainer") +("rotateByDegrees","rotateByDegrees:","Float -> IO ()","Foundation.NSAffineTransform") +("selectionAffinity","selectionAffinity","IO NSSelectionAffinity","AppKit.NSTextView") +("initWithTitleActionKeyEquivalent","initWithTitle:action:keyEquivalent:","forall t1 t3 . NSString t1 -> SEL -> NSString t3 -> IO Inited","AppKit.NSMenuItem") +("createContext","createContext","IO (NSGraphicsContext ())","AppKit.NSPrintOperation") +("buttonNumber","buttonNumber","IO Int","AppKit.NSEvent") +("urls","URLs","IO (NSArray ())","AppKit.NSOpenPanel") +("columnWithIdentifier","columnWithIdentifier:","forall t1 . ID t1 -> IO Int","AppKit.NSTableView") +("markerLocation","markerLocation","IO Float","AppKit.NSRulerMarker") +("urlhandleResourceDidFailLoadingWithReason","URLHandle:resourceDidFailLoadingWithReason:","forall t1 t2 . NSURLHandle t1 -> NSString t2 -> IO ()","Foundation.NSURLHandle") +("initWithWindow","initWithWindow:","forall t1 . NSWindow t1 -> IO Inited","AppKit.NSWindowController") +("getValuesForParameter","getValues:forParameter:","Ptr CLong -> NSOpenGLContextParameter -> IO ()","AppKit.NSOpenGL") +("horizontalScroller","horizontalScroller","IO (NSScroller ())","AppKit.NSScrollView") +("defaultPrinter","defaultPrinter","IO (NSPrinter ())","AppKit.NSPrintInfo") +("numberOfComponents","numberOfComponents","IO Int","AppKit.NSColor") +("spellingPanel","spellingPanel","IO (NSPanel ())","AppKit.NSSpellChecker") +("setEnvironment","setEnvironment:","forall t1 . NSDictionary t1 -> IO ()","Foundation.NSTask") +("moveLeftAndModifySelection","moveLeftAndModifySelection:","forall t1 . ID t1 -> IO ()","AppKit.NSResponder") +("setMinute","setMinute:","Int -> IO ()","Foundation.NSCalendar") +("pickedOrientation","pickedOrientation:","forall t1 . ID t1 -> IO ()","AppKit.NSPageLayout") +("saveGraphicsState","saveGraphicsState","IO ()","AppKit.NSGraphicsContext") +("netServiceDidResolveAddress","netServiceDidResolveAddress:","forall t1 . NSNetService t1 -> IO ()","Foundation.NSNetServices") +("compareOptionsRangeLocale","compare:options:range:locale:","forall t1 t4 . NSString t1 -> CUInt -> NSRange -> NSDictionary t4 -> IO NSComparisonResult","Foundation.NSString") +("setArgumentAtIndex","setArgument:atIndex:","Ptr () -> Int -> IO ()","Foundation.NSInvocation") +("disableUpdates","disableUpdates","IO ()","Foundation.NSMetadata") +("preferredPasteboardTypeFromArrayRestrictedToTypesFromArray","preferredPasteboardTypeFromArray:restrictedToTypesFromArray:","forall t1 t2 . NSArray t1 -> NSArray t2 -> IO (NSString ())","AppKit.NSTextView") +("minValue","minValue","IO Double","AppKit.NSStepper") +("minValue","minValue","IO Double","AppKit.NSSlider") +("minValue","minValue","IO Double","AppKit.NSLevelIndicator") +("minValue","minValue","IO Double","AppKit.NSStepperCell") +("minValue","minValue","IO Double","AppKit.NSSliderCell") +("minValue","minValue","IO Double","AppKit.NSProgressIndicator") +("minValue","minValue","IO Double","AppKit.NSLevelIndicatorCell") +("extendPowerOffBy","extendPowerOffBy:","Int -> IO Int","AppKit.NSWorkspace") +("thickness","thickness","IO Float","AppKit.NSStatusBar") +("canSelectPrevious","canSelectPrevious","IO Bool","AppKit.NSArrayController") +("numberOfGlyphs","numberOfGlyphs","IO CUInt","AppKit.NSLayoutManager") +("numberOfGlyphs","numberOfGlyphs","IO CUInt","AppKit.NSFont") +("abbreviationDictionary","abbreviationDictionary","IO (NSDictionary ())","Foundation.NSTimeZone") +("netServiceDidNotResolve","netService:didNotResolve:","forall t1 t2 . NSNetService t1 -> NSDictionary t2 -> IO ()","Foundation.NSNetServices") +("performKeyEquivalent","performKeyEquivalent:","forall t1 . NSEvent t1 -> IO Bool","AppKit.NSResponder") +("performKeyEquivalent","performKeyEquivalent:","forall t1 . NSEvent t1 -> IO Bool","AppKit.NSMenu") +("setNameFieldLabel","setNameFieldLabel:","forall t1 . NSString t1 -> IO ()","AppKit.NSSavePanel") +("tabStopType","tabStopType","IO NSTextTabType","AppKit.NSParagraphStyle") +("deserializeIntsCountAtCursor","deserializeInts:count:atCursor:","Ptr Int -> CUInt -> Ptr CUInt -> IO ()","Foundation.NSSerialization") +("scanLocation","scanLocation","IO CUInt","Foundation.NSScanner") +("removeObjectsForKeys","removeObjectsForKeys:","forall t1 . NSArray t1 -> IO ()","Foundation.NSDictionary") +("canBeDisabled","canBeDisabled","IO Bool","AppKit.NSInputServer") +("weekday","weekday","IO Int","Foundation.NSCalendar") +("setAutorepeat","setAutorepeat:","Bool -> IO ()","AppKit.NSStepper") +("setAutorepeat","setAutorepeat:","Bool -> IO ()","AppKit.NSStepperCell") +("tabViewType","tabViewType","IO NSTabViewType","AppKit.NSTabView") +("backingType","backingType","IO NSBackingStoreType","AppKit.NSWindow") +("nextEventMatchingMaskUntilDateInModeDequeue","nextEventMatchingMask:untilDate:inMode:dequeue:","forall t2 t3 . CUInt -> NSDate t2 -> NSString t3 -> Bool -> IO (NSEvent ())","AppKit.NSWindow") +("nextEventMatchingMaskUntilDateInModeDequeue","nextEventMatchingMask:untilDate:inMode:dequeue:","forall t2 t3 . CUInt -> NSDate t2 -> NSString t3 -> Bool -> IO (NSEvent ())","AppKit.NSApplication") +("defaultFocusRingType","defaultFocusRingType","IO NSFocusRingType","AppKit.NSView") +("defaultFocusRingType","defaultFocusRingType","IO NSFocusRingType","AppKit.NSCell") +("tokenFieldCellStyleForRepresentedObject","tokenFieldCell:styleForRepresentedObject:","forall t1 t2 . NSTokenFieldCell t1 -> ID t2 -> IO NSTokenStyle","AppKit.NSTokenFieldCell") +("setParagraphSpacingBefore","setParagraphSpacingBefore:","Float -> IO ()","AppKit.NSParagraphStyle") +("indexOfItemWithSubmenu","indexOfItemWithSubmenu:","forall t1 . NSMenu t1 -> IO Int","AppKit.NSMenu") +("setBaseWritingDirectionRange","setBaseWritingDirection:range:","NSWritingDirection -> NSRange -> IO ()","AppKit.NSTextView") +("setBaseWritingDirectionRange","setBaseWritingDirection:range:","NSWritingDirection -> NSRange -> IO ()","AppKit.NSAttributedString") +("initWithPickerMaskColorPanel","initWithPickerMask:colorPanel:","forall t2 . Int -> NSColorPanel t2 -> IO Inited","AppKit.NSColorPicking") +("locationForGlyphAtIndex","locationForGlyphAtIndex:","CUInt -> IO NSPoint","AppKit.NSLayoutManager") +("indexLessThanIndex","indexLessThanIndex:","CUInt -> IO CUInt","Foundation.NSIndexSet") +("shadowBlurRadius","shadowBlurRadius","IO Float","AppKit.NSShadow") +("interpretKeyEvents","interpretKeyEvents:","forall t1 . NSArray t1 -> IO ()","AppKit.NSResponder") +("lockFocus","lockFocus","IO ()","AppKit.NSView") +("lockFocus","lockFocus","IO ()","AppKit.NSImage") +("setDefaultNameServerPortNumber","setDefaultNameServerPortNumber:","CUShort -> IO ()","Foundation.NSPortNameServer") +("descriptionWithLocaleIndent","descriptionWithLocale:indent:","forall t1 . NSDictionary t1 -> CUInt -> IO (NSString ())","Foundation.NSDictionary") +("descriptionWithLocaleIndent","descriptionWithLocale:indent:","forall t1 . NSDictionary t1 -> CUInt -> IO (NSString ())","Foundation.NSArray") +("sortIndicatorRectForBounds","sortIndicatorRectForBounds:","NSRect -> IO NSRect","AppKit.NSTableHeaderCell") +("initialFirstResponder","initialFirstResponder","IO (NSView ())","AppKit.NSWindow") +("initialFirstResponder","initialFirstResponder","IO (NSView ())","AppKit.NSTabViewItem") +("decimalNumberByMultiplyingByWithBehavior","decimalNumberByMultiplyingBy:withBehavior:","forall t1 t2 . NSDecimalNumber t1 -> ID t2 -> IO (NSDecimalNumber ())","Foundation.NSDecimalNumber") +("xmlstring","XMLString","IO (NSString ())","Foundation.NSXMLNode") +("availableVoices","availableVoices","IO (NSArray ())","AppKit.NSSpeechSynthesizer") +("setPaperName","setPaperName:","forall t1 . NSString t1 -> IO ()","AppKit.NSPrintInfo") +("rootObject","rootObject","IO (ID ())","Foundation.NSConnection") +("browserNumberOfRowsInColumn","browser:numberOfRowsInColumn:","forall t1 . NSBrowser t1 -> Int -> IO Int","AppKit.NSBrowser") +("isAutodisplay","isAutodisplay","IO Bool","AppKit.NSWindow") +("parserValidationErrorOccurred","parser:validationErrorOccurred:","forall t1 t2 . NSXMLParser t1 -> NSError t2 -> IO ()","Foundation.NSXMLParser") +("stringForKey","stringForKey:","forall t1 . NSString t1 -> IO (NSString ())","Foundation.NSUserDefaults") +("contentViewMargins","contentViewMargins","IO NSSize","AppKit.NSBox") +("autosavedContentsFileURL","autosavedContentsFileURL","IO (NSURL ())","AppKit.NSDocument") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSCalendarDate") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSValue") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSSet") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSDictionary") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSArray") +("commandName","commandName","IO (NSString ())","Foundation.NSScriptCommandDescription") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSComboBox") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSTableView") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSMatrix") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSComboBoxCell") +("documentView","documentView","IO (ID ())","AppKit.NSScrollView") +("documentView","documentView","IO (ID ())","AppKit.NSClipView") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSWindow") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSScreen") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSPrinter") +("serializePropertyListIntoData","serializePropertyList:intoData:","forall t1 t2 . ID t1 -> NSMutableData t2 -> IO ()","Foundation.NSSerialization") +("firstResponder","firstResponder","IO (NSResponder ())","AppKit.NSWindow") +("tableViewAcceptDropRowDropOperation","tableView:acceptDrop:row:dropOperation:","forall t1 t2 . NSTableView t1 -> ID t2 -> Int -> NSTableViewDropOperation -> IO Bool","AppKit.NSTableView") +("setCalendar","setCalendar:","forall t1 . NSCalendar t1 -> IO ()","AppKit.NSDatePicker") +("setCalendar","setCalendar:","forall t1 . NSCalendar t1 -> IO ()","AppKit.NSDatePickerCell") +("knobProportion","knobProportion","IO Float","AppKit.NSScroller") +("setSegmentCount","setSegmentCount:","Int -> IO ()","AppKit.NSSegmentedControl") +("setSegmentCount","setSegmentCount:","Int -> IO ()","AppKit.NSSegmentedCell") +("setVerticalScroller","setVerticalScroller:","forall t1 . NSScroller t1 -> IO ()","AppKit.NSScrollView") +("setStandalone","setStandalone:","Bool -> IO ()","Foundation.NSXMLDocument") +("parserResolveExternalEntityNameSystemID","parser:resolveExternalEntityName:systemID:","forall t1 t2 t3 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> IO (NSData ())","Foundation.NSXMLParser") +("insertItemWithTitleAtIndex","insertItemWithTitle:atIndex:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSPopUpButtonCell") +("insertItemWithTitleAtIndex","insertItemWithTitle:atIndex:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSPopUpButton") +("setDuration","setDuration:","NSTimeInterval -> IO ()","AppKit.NSAnimation") +("completionsForPartialWordRangeIndexOfSelectedItem","completionsForPartialWordRange:indexOfSelectedItem:","NSRange -> Ptr Int -> IO (NSArray ())","AppKit.NSTextView") +("setAllowsTickMarkValuesOnly","setAllowsTickMarkValuesOnly:","Bool -> IO ()","AppKit.NSSlider") +("setAllowsTickMarkValuesOnly","setAllowsTickMarkValuesOnly:","Bool -> IO ()","AppKit.NSSliderCell") +("defaultVoice","defaultVoice","IO (NSString ())","AppKit.NSSpeechSynthesizer") +("archiverWillEncodeObject","archiver:willEncodeObject:","forall t1 t2 . NSKeyedArchiver t1 -> ID t2 -> IO (ID ())","Foundation.NSKeyedArchiver") +("setMenuBarVisible","setMenuBarVisible:","Bool -> IO ()","AppKit.NSMenu") +("moveToPoint","moveToPoint:","NSPoint -> IO ()","AppKit.NSBezierPath") +("txtrecordData","TXTRecordData","IO (NSData ())","Foundation.NSNetServices") +("setSeparatesColumns","setSeparatesColumns:","Bool -> IO ()","AppKit.NSBrowser") +("deleteForward","deleteForward:","forall t1 . ID t1 -> IO ()","AppKit.NSResponder") +("inputStreamWithFileAtPath","inputStreamWithFileAtPath:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSStream") +("valueWithRect","valueWithRect:","NSRect -> IO (NSValue ())","Foundation.NSGeometry") +("selectRowInColumn","selectRow:inColumn:","Int -> Int -> IO ()","AppKit.NSBrowser") +("gotoEnd","gotoEnd:","forall t1 . ID t1 -> IO ()","AppKit.NSMovieView") +("compare","compare:","forall t1 . ID t1 -> IO NSComparisonResult","AppKit.NSCell") +("compare","compare:","forall t1 . NSNumber t1 -> IO NSComparisonResult","Foundation.NSValue") +("compare","compare:","forall t1 . NSString t1 -> IO NSComparisonResult","Foundation.NSString") +("compare","compare:","forall t1 . NSIndexPath t1 -> IO NSComparisonResult","Foundation.NSIndexPath") +("compare","compare:","forall t1 . NSDate t1 -> IO NSComparisonResult","Foundation.NSDate") +("scrollColumnToVisible","scrollColumnToVisible:","Int -> IO ()","AppKit.NSTableView") +("scrollColumnToVisible","scrollColumnToVisible:","Int -> IO ()","AppKit.NSBrowser") +("invalidateCursorRectsForView","invalidateCursorRectsForView:","forall t1 . NSView t1 -> IO ()","AppKit.NSWindow") +("tabStops","tabStops","IO (NSArray ())","AppKit.NSParagraphStyle") +("setSharedURLCache","setSharedURLCache:","forall t1 . NSURLCache t1 -> IO ()","Foundation.NSURLCache") +("dataWithBytesNoCopyLengthFreeWhenDone","dataWithBytesNoCopy:length:freeWhenDone:","Ptr () -> CUInt -> Bool -> IO (ID ())","Foundation.NSData") +("removeWindowsItem","removeWindowsItem:","forall t1 . NSWindow t1 -> IO ()","AppKit.NSApplication") +("printerFont","printerFont","IO (NSFont ())","AppKit.NSFont") +("addItemsWithObjectValues","addItemsWithObjectValues:","forall t1 . NSArray t1 -> IO ()","AppKit.NSComboBox") +("addItemsWithObjectValues","addItemsWithObjectValues:","forall t1 . NSArray t1 -> IO ()","AppKit.NSComboBoxCell") +("defaultLineHeightForFont","defaultLineHeightForFont","IO Float","AppKit.NSFont") +("setBaseSpecifier","setBaseSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("baseSpecifier","baseSpecifier","IO (NSScriptObjectSpecifier ())","Foundation.NSScriptObjectSpecifiers") +("insertObjectAtIndex","insertObject:atIndex:","forall t1 . ID t1 -> CUInt -> IO ()","Foundation.NSArray") +("numberWithLong","numberWithLong:","CLong -> IO (NSNumber ())","Foundation.NSValue") +("addItemWithObjectValue","addItemWithObjectValue:","forall t1 . ID t1 -> IO ()","AppKit.NSComboBox") +("addItemWithObjectValue","addItemWithObjectValue:","forall t1 . ID t1 -> IO ()","AppKit.NSComboBoxCell") +("secondsFromGMT","secondsFromGMT","IO Int","Foundation.NSTimeZone") +("dragImageForRowsEventDragImageOffset","dragImageForRows:event:dragImageOffset:","forall t1 t2 . NSArray t1 -> NSEvent t2 -> NSPointPointer -> IO (NSImage ())","AppKit.NSTableView") +("titleOfColumn","titleOfColumn:","Int -> IO (NSString ())","AppKit.NSBrowser") +("setTitleOfColumn","setTitle:ofColumn:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSBrowser") +("lineScroll","lineScroll","IO Float","AppKit.NSScrollView") +("scriptingIsLessThanOrEqualTo","scriptingIsLessThanOrEqualTo:","forall t1 . ID t1 -> IO Bool","Foundation.NSScriptWhoseTests") +("setChildSpecifier","setChildSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("initWithScrollViewOrientation","initWithScrollView:orientation:","forall t1 . NSScrollView t1 -> NSRulerOrientation -> IO Inited","AppKit.NSRulerView") +("drawWithFrameInViewCharacterIndexLayoutManager","drawWithFrame:inView:characterIndex:layoutManager:","forall t2 t4 . NSRect -> NSView t2 -> CUInt -> NSLayoutManager t4 -> IO ()","AppKit.NSTextAttachment") +("popUpContextMenuWithEventForViewWithFont","popUpContextMenu:withEvent:forView:withFont:","forall t1 t2 t3 t4 . NSMenu t1 -> NSEvent t2 -> NSView t3 -> NSFont t4 -> IO ()","AppKit.NSMenu") +("sharedDocumentController","sharedDocumentController","IO (ID ())","AppKit.NSDocumentController") +("lastIndex","lastIndex","IO CUInt","Foundation.NSIndexSet") +("timeIntervalSince1970","timeIntervalSince1970","IO NSTimeInterval","Foundation.NSDate") +("focusStack","focusStack","IO (Ptr ())","AppKit.NSGraphicsContext") +("modifyFontViaPanel","modifyFontViaPanel:","forall t1 . ID t1 -> IO ()","AppKit.NSFontManager") +("removePortForName","removePortForName:","forall t1 . NSString t1 -> IO Bool","Foundation.NSPortNameServer") +("cancelButtonCell","cancelButtonCell","IO (NSButtonCell ())","AppKit.NSSearchFieldCell") +("takeFloatValueFrom","takeFloatValueFrom:","forall t1 . ID t1 -> IO ()","AppKit.NSControl") +("takeFloatValueFrom","takeFloatValueFrom:","forall t1 . ID t1 -> IO ()","AppKit.NSCell") +("drawAtPointWithAttributes","drawAtPoint:withAttributes:","forall t2 . NSPoint -> NSDictionary t2 -> IO ()","AppKit.NSStringDrawing") +("ignoreWordInSpellDocumentWithTag","ignoreWord:inSpellDocumentWithTag:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSSpellChecker") +("setCalendarFormat","setCalendarFormat:","forall t1 . NSString t1 -> IO ()","Foundation.NSCalendarDate") +("setSmartInsertDeleteEnabled","setSmartInsertDeleteEnabled:","Bool -> IO ()","AppKit.NSTextView") +("defaultTypesetterBehavior","defaultTypesetterBehavior","IO NSTypesetterBehavior","AppKit.NSTypesetter") +("printerTypes","printerTypes","IO (NSArray ())","AppKit.NSPrinter") +("initFileURLWithPath","initFileURLWithPath:","forall t1 . NSString t1 -> IO Inited","Foundation.NSURL") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSPopUpButtonCell") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSPopUpButton") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSMenu") +("isDataRetained","isDataRetained","IO Bool","AppKit.NSImage") +("parserParseErrorOccurred","parser:parseErrorOccurred:","forall t1 t2 . NSXMLParser t1 -> NSError t2 -> IO ()","Foundation.NSXMLParser") +("headerCell","headerCell","IO (ID ())","AppKit.NSTableColumn") +("setDrawsCellBackground","setDrawsCellBackground:","Bool -> IO ()","AppKit.NSMatrix") +("setOrientation","setOrientation:","NSRulerOrientation -> IO ()","AppKit.NSRulerView") +("setOrientation","setOrientation:","NSPrintingOrientation -> IO ()","AppKit.NSPrintInfo") +("allowsUserCustomization","allowsUserCustomization","IO Bool","AppKit.NSToolbar") +("createTextureFromViewInternalFormat","createTexture:fromView:internalFormat:","forall t2 . CULong -> NSView t2 -> CULong -> IO ()","AppKit.NSOpenGL") +("locationOfPrintRect","locationOfPrintRect:","NSRect -> IO NSPoint","AppKit.NSView") +("flatness","flatness","IO Float","AppKit.NSBezierPath") +("titleColor","titleColor","IO (NSColor ())","AppKit.NSSlider") +("titleColor","titleColor","IO (NSColor ())","AppKit.NSSliderCell") +("urlsFromRunningOpenPanel","URLsFromRunningOpenPanel","IO (NSArray ())","AppKit.NSDocumentController") +("setDirectParameter","setDirectParameter:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptCommand") +("setAutohidesScrollers","setAutohidesScrollers:","Bool -> IO ()","AppKit.NSScrollView") +("lockFocusIfCanDraw","lockFocusIfCanDraw","IO Bool","AppKit.NSView") +("writeToFileAtomicallyUpdateFilenames","writeToFile:atomically:updateFilenames:","forall t1 . NSString t1 -> Bool -> Bool -> IO Bool","AppKit.NSFileWrapper") +("reloadColumn","reloadColumn:","Int -> IO ()","AppKit.NSBrowser") +("initWithTableStartingRowRowSpanStartingColumnColumnSpan","initWithTable:startingRow:rowSpan:startingColumn:columnSpan:","forall t1 . NSTextTable t1 -> Int -> Int -> Int -> Int -> IO Inited","AppKit.NSTextTable") +("shouldCreateUI","shouldCreateUI","IO Bool","AppKit.NSDocumentController") +("rightExpression","rightExpression","IO (NSExpression ())","Foundation.NSComparisonPredicate") +("dayOfCommonEra","dayOfCommonEra","IO Int","Foundation.NSCalendarDate") +("terminationStatus","terminationStatus","IO Int","Foundation.NSTask") +("refusesFirstResponder","refusesFirstResponder","IO Bool","AppKit.NSControl") +("refusesFirstResponder","refusesFirstResponder","IO Bool","AppKit.NSCell") +("sizeWithAttributes","sizeWithAttributes:","forall t1 . NSDictionary t1 -> IO NSSize","AppKit.NSStringDrawing") +("fileURLWithPath","fileURLWithPath:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSURL") +("caseInsensitiveCompare","caseInsensitiveCompare:","forall t1 . NSString t1 -> IO NSComparisonResult","Foundation.NSString") +("firstVisibleColumn","firstVisibleColumn","IO Int","AppKit.NSBrowser") +("setNeedsDisplayInRect","setNeedsDisplayInRect:","NSRect -> IO ()","AppKit.NSView") +("toggleBaseWritingDirection","toggleBaseWritingDirection:","forall t1 . ID t1 -> IO ()","AppKit.NSTextView") +("setMenuFormRepresentation","setMenuFormRepresentation:","forall t1 . NSMenuItem t1 ->... [truncated message content] |
From: <cod...@go...> - 2009-08-11 21:10:14
|
Revision: 397 Author: wol...@gm... Date: Tue Aug 11 14:09:42 2009 Log: zap autoconf/make build system, old interface generator (issue #3) http://code.google.com/p/hoc/source/detail?r=397 Deleted: /trunk/hoc/AppKit /trunk/hoc/Foundation /trunk/hoc/HOC/HOC.conf.in /trunk/hoc/HOC/Makefile.in /trunk/hoc/InterfaceGenerator /trunk/hoc/Makefile.in /trunk/hoc/Samples/Browser/Makefile /trunk/hoc/Samples/Editor/Makefile /trunk/hoc/Samples/ExpressionParser/Makefile /trunk/hoc/Samples/UniqSort/Makefile /trunk/hoc/Tests/Makefile /trunk/hoc/Tools/Makefile.in /trunk/hoc/aclocal.m4 /trunk/hoc/autogen.sh /trunk/hoc/autotools /trunk/hoc/config.mk.in /trunk/hoc/configure.ac /trunk/hoc/objc.m4 ======================================= --- /trunk/hoc/HOC/HOC.conf.in Sun Aug 24 21:31:51 2008 +++ /dev/null @@ -1,57 +0,0 @@ -name: HOC -maintainer: wol...@gm... -exposed: True - -exposed-modules: - HOC, - HOC.SelectorNameMangling, - HOC.Arguments, - HOC.FFICallInterface, - HOC.StdArgumentTypes, - HOC.TH, - HOC.DeclareClass, - HOC.ID, - HOC.Class, - HOC.DeclareSelector, - HOC.SelectorMarshaller, - HOC.Base, - HOC.NewlyAllocated, - HOC.Invocation, - HOC.MsgSend, - HOC.Utilities, - HOC.ExportClass, - HOC.NewClass, - HOC.Super, - HOC.CEnum, - HOC.NameCaseChange, - HOC.Dyld, - HOC.ExternConstants, - HOC.Exception, - HOC.ExternFunctions, - HOC.Unicode, - HOC.Selectors, - HOC.THDebug, - HOC.CannedCIFs - -hs-libraries: "HOC", "HOC_cbits" -depends: base, template-haskell, unix - -#if GNUSTEP -extra-libraries: "gnustep-base", "objc" PKG_EXTRA_LIBS -#else -extra-libraries: "objc" PKG_EXTRA_LIBS -frameworks: Foundation -#endif - -#if INPLACE -import-dirs: "../HOC/build/imports" -library-dirs: "../HOC" - "../HOC_cbits" - FOUNDATION_LIB_DIRS - FFI_LIB_DIRS -#else -import-dirs: GHC_LIB_PATH/HOC/imports -library-dirs: GHC_LIB_PATH/HOC - FOUNDATION_LIB_DIRS - FFI_LIB_DIRS -#endif ======================================= --- /trunk/hoc/HOC/Makefile.in Sun Aug 17 21:58:22 2008 +++ /dev/null @@ -1,105 +0,0 @@ -include ../config.mk - -dist_srcdir = HOC -dist_FILES = \ - HOC \ - HOC-gnustep.conf \ - HOC-gnustep.conf-inplace \ - HOC-macos.conf \ - HOC-macos.conf-inplace \ - HOC.hs \ - Makefile.in \ - $(NULL) - -ifeq "$(HocBuildDylibs)" "YES" -LIBRARIES=libHOC.a libHOC.dylib -else -LIBRARIES=libHOC.a HOC.o -endif - -FOUND_SOURCES := $(shell find . -name '*.hs') - -HOCLIBDIR="$(destdir)"/$(GHC_LIB_PATH)/HOC - -all: $(LIBRARIES) ../inplace.conf - -../inplace.conf: HOC.conf-inplace - [ -f "$@" ] || echo '[]' > $@ - $(GHC_PKG) update HOC.conf-inplace \ - --package-conf=../inplace.conf - -%.conf: %.conf.in - gcc -E -x c -DGHC_LIB_PATH=@GHC_LIB_PATH@ \ - -DFOUNDATION_LIB_DIRS=@HOC_FOUNDATION_LIB_DIRS@ \ - -DFFI_LIB_DIRS=@FFI_LIB_DIRS@ \ - -DPKG_EXTRA_LIBS=@PKG_EXTRA_LIBS@ \ - @HOC_DEFINES@ $< | grep -v '^#' > $@ -%.conf-inplace: %.conf.in - gcc -E -x c -DINPLACE=1 \ - -DGHC_LIB_PATH=@GHC_LIB_PATH@ \ - -DFOUNDATION_LIB_DIRS=@HOC_FOUNDATION_LIB_DIRS@ \ - -DFFI_LIB_DIRS=@FFI_LIB_DIRS@ \ - -DPKG_EXTRA_LIBS=@PKG_EXTRA_LIBS@ \ - @HOC_DEFINES@ $< | grep -v '^#' > $@ - -libHOC.a: ghcmake.build-stamp - find build/objects/ -name \*.o | xargs $(MAKE_STATIC_LIB) libHOC.a - -libHOC.dylib: ghcmake.build-stamp - find build/objects/ -name \*.o \ - | xargs libtool \ - -dynamic \ - $(FFI_LIBS) \ - -undefined dynamic_lookup \ - -single_module \ - -o $@ - install_name_tool -id "`pwd`/$@" $@ - -HOC.o: libHOC.a - ld -r -x -o HOC.o $(FFI_LIBS) $(ALL_LOAD) libHOC.a - -ghcmake: ghcmake.build-stamp - -ifeq "$(HocBuildDylibs)" "YES" -CBITS=-L../HOC_cbits -lHOC_cbits -else -CBITS=../HOC_cbits/HOC_cbits.o -endif - -ghcmake.build-stamp: $(FOUND_SOURCES) - mkdir -p build/objects - mkdir -p build/imports - $(GHC) --make HOC.hs \ - -O -fasm \ - -fPIC \ - -odir build/objects -hidir build/imports \ - -fglasgow-exts -fth \ - -lobjc \ - $(CBITS) \ - -I../HOC_cbits \ - $(FFI_CFLAGS) \ - $(FFI_LIBS) \ - -package-name HOC \ - -package unix \ - $(FOUNDATION_INCLUDES) \ - $(FOUNDATION_LIBS) \ - $(DEFINES) \ - $(EXTRA_GHCFLAGS) - touch $@ - -clean: - rm -rf libHOC.a HOC.o build \ - HOC/NewClass_stub.c HOC/NewClass_stub.h \ - ghcmake.build-stamp - -install: install-files - ranlib $(HOCLIBDIR)/libHOC.a -ifeq "$(HocBuildDylibs)" "YES" - install_name_tool -id $(HOCLIBDIR)/libHOC.dylib $(HOCLIBDIR)/libHOC.dylib -endif - $(GHC_PKG) update HOC.conf - -install-files: all HOC.conf - mkdir -p $(HOCLIBDIR) - cp -R $(LIBRARIES) build/imports \ - $(HOCLIBDIR) ======================================= --- /trunk/hoc/Makefile.in Sun Aug 17 21:58:22 2008 +++ /dev/null @@ -1,84 +0,0 @@ -include config.mk - -SUBDIRS = \ - HOC_cbits \ - HOC \ - InterfaceGenerator \ - InterfaceGenerator2 \ - Bindings \ - Foundation \ - AppKit \ - Tools \ - docs \ - $(NULL) - -Samples_SUBDIRS = \ - Samples/Browser \ - Samples/Editor \ - Samples/ExpressionParser \ - Samples/UniqSort \ - $(NULL) - -all_SUBDIRS = $(SUBDIRS) $(Samples_SUBDIRS) - -dist_srcdir = . -dist_FILES = \ - AUTHORS.txt \ - LICENSE \ - Makefile.in \ - README.txt \ - aclocal.m4 \ - autogen.sh \ - autotools \ - config.mk.in \ - configure \ - configure.ac \ - objc.m4 \ - $(NULL) - -installer_package_root = $(shell pwd)/installer-package/root - -all: hoc-all - -dist: - -test -d "$(dist_dir)" && rm -rf "$(dist_dir)" - $(MAKE) dist-recursive - for dir in $(all_SUBDIRS); do (cd $$dir; $(MAKE) dist-recursive); done - find "$(dist_dir)" -type d -name 'CVS' -exec rm -rf '{}' ';' -prune - find "$(dist_dir)" -type d -name '*~' -exec rm -rf '{}' ';' -prune - tar jcvf @abs_top_builddir@/hoc-@PACKAGE_VERSION@.tar.bz2 \ - ./hoc-@PACKAGE_VERSION@ - -distcheck: dist - ( cd "$(dist_dir)" && ./configure && make ) - -check: - ( cd Tests && $(MAKE) check ) - -$(FFI_SOURCE_DIR)/build/src/raw_api.o: - ( cd $(FFI_SOURCE_DIR)/build && $(MAKE) ) - -hoc-all: - for dir in $(SUBDIRS); do (cd $$dir; echo "In directory $$dir"; $(MAKE) all) done - -clean: - for dir in $(all_SUBDIRS); do (cd $$dir; echo "In directory $$dir"; $(MAKE) clean) done - -install: - for dir in $(SUBDIRS); do (cd $$dir; echo "In directory $$dir"; $(MAKE) install) done - -install-files: - for dir in $(SUBDIRS); do (cd $$dir; echo "In directory $$dir"; $(MAKE) install-files) done - -package: - mkdir -p "$(installer_package_root)" - $(MAKE) install-files destdir="$(installer_package_root)" - cp HOC/HOC.conf "$(installer_package_root)"/$(GHC_LIB_PATH)/HOC - cp Foundation/Foundation.conf "$(installer_package_root)"/$(GHC_LIB_PATH)/Foundation - cp AppKit/AppKit.conf "$(installer_package_root)"/$(GHC_LIB_PATH)/AppKit - chown -R root:admin "$(installer_package_root)" - -.PHONY: samples -samples: - for dir in $(Samples_SUBDIRS); do (echo "In directory $$dir"; cd $$dir; $(MAKE)) done - ======================================= --- /trunk/hoc/Samples/Browser/Makefile Tue Jul 26 19:55:40 2005 +++ /dev/null @@ -1,34 +0,0 @@ -include ../../config.mk - -dist_srcdir = Samples/Browser -dist_FILES = \ - Contents \ - $(wildcard *.hs) \ - Makefile.in \ - $(NULL) - -all: Browser.app - -Browser.app: Browser Contents/Resources/all-selectors.txt - hocwrap Browser - -Browser: *.hs - mkdir -p build - $(GHC) --make -fglasgow-exts Main.hs -odir build -hidir build -O -o Browser - -interpret: - mkdir -p build - hocwrap -i -- -fglasgow-exts Main.hs -odir build -hidir build - -zerolink: nolink interpret - -nolink: - mkdir -p build - $(GHC) --make -fglasgow-exts Main.hs -odir build -hidir build -O -pgml true - -Contents/Resources/all-selectors.txt: ../../Bindings/all-selectors.txt - cp $< $@ - -clean: - rm -rf build/ Browser Browser.app/ 'Interpreted Haskell Application.app/' Contents/Resources/all-selectors.txt - ======================================= --- /trunk/hoc/Samples/Editor/Makefile Wed Nov 1 07:45:05 2006 +++ /dev/null @@ -1,29 +0,0 @@ -include ../../config.mk - -dist_srcdir = Samples/Editor -dist_FILES = \ - Contents \ - $(wildcard *.hs) \ - Makefile.in \ - $(NULL) - -all: Editor.app - -Editor.app: Editor - hocwrap Editor - -Editor: *.hs - mkdir -p build - $(GHC) --make -fglasgow-exts -fth Main.hs -odir build -hidir build -O -o Editor - -interpret: - mkdir -p build - hocwrap -i -- -fglasgow-exts Main.hs -odir build -hidir build - -zerolink: nolink interpret - -nolink: - mkdir -p build - $(GHC) --make -fglasgow-exts -fth Main.hs -odir build -hidir build -O -pgml true -clean: - rm -rf build Editor Editor.app 'Interpreted Haskell Application.app/' ======================================= --- /trunk/hoc/Samples/ExpressionParser/Makefile Tue Jul 26 19:55:40 2005 +++ /dev/null @@ -1,31 +0,0 @@ -include ../../config.mk - -dist_srcdir = Samples/ExpressionParser -dist_FILES = \ - Contents \ - $(wildcard *.hs) \ - Makefile.in \ - $(NULL) - -all: ExpressionParser.app - -ExpressionParser.app: ExpressionParser - hocwrap ExpressionParser - -ExpressionParser: *.hs - mkdir -p build - $(GHC) --make Main.hs -odir build -hidir build -O -o $@ - -interpret: - mkdir -p build - hocwrap -i -- Main.hs -odir build -hidir build - -zerolink: nolink interpret - -nolink: - mkdir -p build - $(GHC) --make Main.hs -odir build -hidir build -O -pgml true - -clean: - rm -rf build/ ExpressionParser ExpressionParser.app/ 'Interactive Haskell Application.app/' - ======================================= --- /trunk/hoc/Samples/UniqSort/Makefile Sat Aug 6 09:45:38 2005 +++ /dev/null @@ -1,19 +0,0 @@ -include ../../config.mk - -dist_srcdir = Samples/UniqSort -dist_FILES = \ - $(wildcard *.hs) \ - Makefile.in \ - $(NULL) - -all: uniqsort - -uniqsort: UniqSort.hs - $(GHC) -o $@ --make $< - -uniqsort.stripped: UniqSort.hs - $(GHC) -o $@ --make -optl-Wl,-dead_strip $< - -clean: - rm -f uniqsort *.o *.hi - ======================================= --- /trunk/hoc/Tests/Makefile Sun Aug 24 21:31:51 2008 +++ /dev/null @@ -1,47 +0,0 @@ -.PHONY: thtests cleanthbuild - -check: static - -static: TestFoundation.static - ./TestFoundation.static - -dynamic: TestFoundation.dynamic - ./TestFoundation.dynamic - - -build: - mkdir -p build/dynamic/imports - mkdir -p build/dynamic/objects - mkdir -p build/static/imports - mkdir -p build/static/objects - -TestFoundation.dynamic: build TestFoundation.hs - ghc -dynamic -odir build/dynamic/objects -hidir build/dynamic/imports \ - -o $@ -package-conf ../inplace.conf \ - -package Foundation --make TestFoundation.hs - -TestFoundation.static: build TestFoundation.hs - ghc -odir build/static/objects -hidir build/static/imports \ - -o $@ -package-conf ../inplace.conf \ - -package Foundation --make TestFoundation.hs - -thbuild: - mkdir -p thbuild/static/imports - mkdir -p thbuild/static/objects - -cleanthbuild: - rm -rf thbuild - -TestHOCDeclareSelector: thbuild TestHOCDeclareSelector.hs TestHOCDeclareSelectorForward.hs - ghc -odir thbuild/static/objects -hidir thbuild/static/imports \ - -pgml true -fth -o $@ -package-conf ../inplace.conf \ - -package HOC --make TestHOCDeclareSelector.hs \ - -main-is TestHOCDeclareSelector - -thtests: cleanthbuild TestHOCDeclareSelector - -clean: cleanthbuild - rm -rf build - rm -f TestFoundation.static - rm -f TestFoundation.dynamic - ======================================= --- /trunk/hoc/Tools/Makefile.in Sat Jul 30 01:24:45 2005 +++ /dev/null @@ -1,27 +0,0 @@ -include ../config.mk - -dist_srcdir = Tools -dist_FILES = \ - HOCWrap.hs \ - Makefile.in \ - $(NULL) - -all: hocwrap - -hocwrap: *.hs - mkdir -p build/hocwrap - $(GHC) --make HOCWrap.hs \ - -fglasgow-exts \ - -o hocwrap \ - -odir build/hocwrap -hidir build/hocwrap \ - -package-conf ../inplace.conf - -clean: - rm -rf hocwrap build - -install: install-files - -install-files: all - mkdir -p "$(destdir)"/$(bindir) - install -s hocwrap "$(destdir)"/$(bindir) - ======================================= --- /trunk/hoc/aclocal.m4 Tue May 11 22:44:14 2004 +++ /dev/null @@ -1,373 +0,0 @@ -builtin(include,objc.m4) - -AC_SUBST(MAKE) -AC_SUBST(OBJC_RUNTIME) -AC_SUBST(OBJC_RUNTIME_FLAG) -AC_SUBST(BROKEN_COMPILER) -AC_SUBST(BROKEN_BUILTIN_APPLY) -AC_SUBST(NO_NESTED_FUNCTIONS) -AC_SUBST(PCCTS_CFLAGS) -AC_SUBST(HOST)dnl -AC_SUBST(HOST_CPU)dnl -AC_SUBST(HOST_VENDOR)dnl -AC_SUBST(HOST_OS)dnl -AC_SUBST(TARGET)dnl -AC_SUBST(TARGET_CPU)dnl -AC_SUBST(TARGET_VENDOR)dnl -AC_SUBST(TARGET_OS)dnl -AC_SUBST(STRUCT_ALIGNMENT)dnl - -#------------------------------------------------------------------------ -# OD_OBJC_RUNTIME -- -# -# Determine the default, working Objective C runtime -# -# Arguments: -# None. -# -# Requires: -# none -# -# Depends: -# AC_PROG_OBJC from objc.m4 -# -# Results: -# -# Adds a --with-objc-runtime switch to configure. -# Result is cached. -# -# Defines one of the following preprocessor macros: -# NeXT_RUNTIME GNU_RUNTIME -#------------------------------------------------------------------------ -AC_DEFUN([OD_OBJC_RUNTIME],[ - AC_REQUIRE([AC_PROG_OBJC]) - AC_ARG_WITH(objc-runtime, [ --with-objc-runtime Specify either "GNU" or "NeXT"], [with_objc_runtime=${withval}]) - - if test x"${with_objc_runtime}" != x; then - case "${with_objc_runtime}" in - GNU) - ;; - NeXT) - ;; - *) - AC_MSG_ERROR([${with_objc_runtime} is not a valid argument to --with-objc-runtime. Please specify either "GNU" or "NeXT"]) - ;; - esac - fi - - AC_LANG_PUSH([Objective C]) - - # Check for common header, objc/objc.h - AC_CHECK_HEADERS([objc/objc.h], ,[AC_MSG_ERROR([Can't locate Objective C runtime headers])]) - - # Add -lobjc. The following tests will ensure that the library exists and functions with the detected Objective C compiler - # If the tests fail, AC_MSG_FAILURE is called, and $LIBS does not need to be restored - LIBS="${LIBS} -lobjc" - - if test x"${with_objc_runtime}" == x || test x"${with_objc_runtime}" == x"NeXT"; then - AC_MSG_CHECKING([for NeXT Objective C runtime]) - AC_CACHE_VAL(ac_cv_objc_runtime_next, [ - # The following uses quadrigraphs - # '@<:@' = '[' - # '@:>@' = ']' - AC_LINK_IFELSE([ - AC_LANG_PROGRAM([ - #include <objc/objc.h> - #include <objc/objc-api.h> - ], [ - id class = objc_lookUpClass("Object"); - id obj = @<:@class alloc@:>@; - puts(@<:@obj name@:>@); - ]) - ], [ - ac_cv_objc_runtime_next="yes" - ], [ - ac_cv_objc_runtime_next="no" - ] - ) - ]) - AC_MSG_RESULT(${ac_cv_objc_runtime_next}) - else - ac_cv_objc_runtime_next="no" - fi - - if test x"${with_objc_runtime}" == x || test x"${with_objc_runtime}" == x"GNU"; then - AC_MSG_CHECKING([for GNU Objective C runtime]) - AC_CACHE_VAL(ac_cv_objc_runtime_gnu, [ - # The following uses quadrigraphs - # '@<:@' = '[' - # '@:>@' = ']' - AC_LINK_IFELSE([ - AC_LANG_PROGRAM([ - #include <objc/objc.h> - #include <objc/objc-api.h> - ], [ - id class = objc_lookup_class("Object"); - id obj = @<:@class alloc@:>@; - puts(@<:@obj name@:>@); - ]) - ], [ - ac_cv_objc_runtime_gnu="yes" - ], [ - ac_cv_objc_runtime_gnu="no" - ] - ) - ]) - AC_MSG_RESULT(${ac_cv_objc_runtime_gnu}) - else - ac_cv_objc_runtime_gnu="no" - fi - - # NeXT runtime is prefered - if test x"${ac_cv_objc_runtime_next}" == x"yes"; then - OBJC_RUNTIME="NeXT" - OBJC_RUNTIME_FLAGS="-fnext-runtime" - AC_MSG_NOTICE([Using NeXT Objective C runtime]) - AC_DEFINE([NeXT_RUNTIME], 1, [Define if using the NeXT Objective C runtime and compiler.]) - elif test x"${ac_cv_objc_runtime_gnu}" == x"yes"; then - OBJC_RUNTIME="GNU" - OBJC_RUNTIME_FLAGS="-fgnu-runtime" - AC_MSG_NOTICE([Using GNU Objective C runtime]) - AC_DEFINE([GNU_RUNTIME], 1, [Define if using the GNU Objective C runtime and compiler.]) - else - AC_MSG_FAILURE([Could not locate a working Objective C runtime.]) - fi - - - AC_LANG_POP([Objective C]) -]) - -AC_DEFUN(AC_CHECK_NESTED_FUNCTIONS, [ -AC_REQUIRE([AC_PROG_OBJC]) -AC_REQUIRE([OD_OBJC_RUNTIME]) -AC_MSG_CHECKING(whether nested functions work) -AC_CACHE_VAL(ac_cv_nested_functions, [ -AC_LANG_PUSH([Objective C]) -AC_TRY_RUN([ -f(void (*nested)()) -{ - (*nested)(); -} - -main() -{ - int a = 0; - void nested() - { - a = 1; - } - f(nested); - if(a != 1) - exit(1); - exit(0); -} -], ac_cv_nested_functions=yes, ac_cv_nested_functions=no, -ac_cv_nested_functions=yes) -AC_LANG_POP([Objective C]) -])dnl -AC_MSG_RESULT(${ac_cv_nested_functions}) -NO_NESTED_FUNCTIONS=no -if test $ac_cv_nested_functions = no; then - AC_DEFINE(NO_NESTED_FUNCTIONS, 1, [Define if the compiler does not support nested functions.]) - NO_NESTED_FUNCTIONS=yes -fi -])dnl -dnl -dnl -AC_DEFUN(AC_BROKEN_COMPILER, [ -AC_REQUIRE([AC_PROG_OBJC]) -AC_REQUIRE([OD_OBJC_RUNTIME]) -AC_MSG_CHECKING(if the Objective-C compiler crashes with nested functions) -AC_CACHE_VAL(ac_cv_broken_compiler, [ -AC_LANG_PUSH([Objective C]) -AC_TRY_RUN([ -#include <objc/objc.h> -#include <objc/Object.h> - -void f() -{ - auto void h(id); - - void h(id exception) - { - [Object alloc]; - { - void clean(void) - { - } - } - } -} - -void g() -{ - auto void h(id); - - void h(id exception) - { - [Object alloc]; - } -} - -main() -{ - exit(0); -} -], ac_cv_broken_compiler=no, -ac_cv_broken_compiler=yes, -ac_cv_broken_compiler=no) -AC_LANG_POP([Objective C]) -])dnl -BROKEN_COMPILER=${ac_cv_broken_compiler} -if test ${ac_cv_nested_functions} = no -o ${ac_cv_broken_compiler} = yes; then - ac_cv_broken_compiler=yes; - BROKEN_COMPILER=yes; - AC_DEFINE(BROKEN_COMPILER, 1, [Define if the compiler is broken when nested fu nctions are used with Objective-C messages.]) -fi -AC_MSG_RESULT(${ac_cv_broken_compiler}) -])dnl -dnl -dnl -AC_DEFUN(AC_BROKEN_BUILTIN_APPLY, [ -AC_REQUIRE([AC_PROG_OBJC]) -AC_REQUIRE([OD_OBJC_RUNTIME]) -AC_MSG_CHECKING(whether __builtin_apply and __builtin_return are broken) -AC_CACHE_VAL(ac_cv_broken_builtin_apply, [ -AC_LANG_PUSH([Objective C]) -AC_TRY_RUN([ -#include <objc/Object.h> - -float value = 123.456; - -@interface MyObject : Object -@end - -@implementation MyObject -- (float)floatValue -{ - return value; -} -@end - -@interface Forwarder : Object -{ - id object; -} -@end - -@implementation Forwarder -- setObject:anObject -{ - object = anObject; - return self; -} - -- (void*)forward:(SEL)selector:(void*)argframe -{ - IMP imp = [object methodFor:@selector(floatValue)]; - void* retframe; - void* frame = malloc(116); - *(void**)frame = NULL; - retframe = __builtin_apply((void(*)(void))imp, frame, 0); - if(*(long double*)(((char*)retframe) + 8) == (long double)value) - exit(0); - exit(1); -} -@end - -int main() -{ - id fwd = [[[Forwarder alloc] init] setObject:[MyObject alloc]]; - [fwd floatValue]; - exit(0); - return 0; // keep compiler happy -} -], ac_cv_broken_builtin_apply=no, -ac_cv_broken_builtin_apply=yes, -ac_cv_broken_builtin_apply=no) -AC_LANG_POP([Objective C]) -])dnl -AC_MSG_RESULT(${ac_cv_broken_builtin_apply}) -BROKEN_BUILTIN_APPLY=${ac_cv_broken_builtin_apply} -if test $BROKEN_BUILTIN_APPLY = yes; then - AC_DEFINE(BROKEN_BUILTIN_APPLY, 1, [Define if the __builtin_apply pseudo-function doesn't set the floating point return value at retframe + 8 on Intel machines.]) -fi -])dnl -dnl -dnl -AC_DEFUN(AC_CHECK_MATH_LIB, [ -AC_REQUIRE([AC_PROG_OBJC]) -AC_REQUIRE([OD_OBJC_RUNTIME]) -dnl temporary rename AC_MSG_RESULT to do nothing -define(old_AC_MSG_RESULT, defn([AC_MSG_RESULT]))dnl -define([AC_MSG_RESULT],)dnl -AC_CHECK_FUNC(sqrt, , -[dnl On linux, to link a program that use math functions we must link with libm.a -LIBS="$LIBS -lm -lc" -ac_cv_func_sqrt=no -AC_TRY_LINK(, [ -double sqrt(double); -sqrt(2.0); -], ac_cv_func_sqrt="-lm -lc") -]) -define([AC_MSG_RESULT], defn([old_AC_MSG_RESULT]))dnl -undefine([old_AC_MSG_RESULT])dnl -AC_MSG_RESULT($ac_cv_func_sqrt) -])dnl -dnl -dnl -AC_DEFUN(AC_STRUCT_ALIGNMENT, [ -AC_REQUIRE([AC_PROG_OBJC]) -AC_REQUIRE([OD_OBJC_RUNTIME]) -AC_MSG_CHECKING(for the C structures alignment) -AC_CACHE_VAL(ac_cv_struct_alignment, -[AC_TRY_RUN([#include <stdio.h> - -struct simple { - double x; - char y; -} simple1; - -int struct_alignment = __alignof__ (simple1); - -main() -{ - FILE *f=fopen("conftestval", "w"); - if (!f) exit(1); - fprintf(f, "%u\n", struct_alignment); - exit(0); -} -], ac_cv_struct_alignment=`cat conftestval`, -ac_cv_struct_alignment=0, -ifelse([$2], , , ac_cv_struct_alignment=$2))])dnl -AC_MSG_RESULT($ac_cv_struct_alignment) -STRUCT_ALIGNMENT=$ac_cv_struct_alignment -])dnl -dnl -dnl -AC_DEFUN(AC_COMPILE_CHECK_SIZEOF, -[changequote(<<, >>)dnl -dnl The name to #define. -define(<<AC_TYPE_NAME>>, translit(sizeof_$1, [a-z *], [A-Z_P]))dnl -dnl The cache variable name. -define(<<AC_CV_NAME>>, translit(ac_cv_sizeof_$1, [ *], [_p]))dnl -changequote([, ])dnl -AC_MSG_CHECKING(size of $1) -AC_CACHE_VAL(AC_CV_NAME, -[for ac_size in 4 8 1 2 16 $2 ; do # List sizes in rough order of prevalence. - AC_TRY_COMPILE([#include "confdefs.h" -#include <sys/types.h> -$2 -], [switch (0) case 0: case (sizeof ($1) == $ac_size):;], AC_CV_NAME=$ac_size) - if test x$AC_CV_NAME != x ; then break; fi -done -]) -if test x$AC_CV_NAME = x ; then - echo "cannot determine a size for $1"; - AC_CV_NAME=0; -fi -AC_MSG_RESULT($AC_CV_NAME) -AC_DEFINE_UNQUOTED(AC_TYPE_NAME, $AC_CV_NAME, [The number of bytes in type $1]) -undefine([AC_TYPE_NAME])dnl -undefine([AC_CV_NAME])dnl -]) ======================================= --- /trunk/hoc/autogen.sh Tue May 11 22:44:14 2004 +++ /dev/null @@ -1,6 +0,0 @@ -#!/bin/sh -x - -# this is the world's most complicated autogen.sh script :) - -exec autoconf - ======================================= --- /trunk/hoc/config.mk.in Sun Aug 17 21:58:22 2008 +++ /dev/null @@ -1,45 +0,0 @@ -NULL = - -PLATFORM=@HOC_PLATFORM@ -ALL_LOAD=@HOC_LD_ALL_LOAD@ -MAKE_STATIC_LIB=@HOC_MAKE_STATIC_LIB@ -FOUNDATION_INCLUDES=@HOC_FOUNDATION_INCLUDES@ -FOUNDATION_LIBS=@HOC_FOUNDATION_LIBS@ -DEFINES=@HOC_DEFINES@ -CFLAGS=@HOC_CFLAGS@ - -GHC=@GHC@ -GHC_PKG=@GHC_PKG@ -GHC_LIB_PATH=@GHC_LIB_PATH@ - -FFI_CFLAGS=@FFI_CFLAGS@ -FFI_SOURCES=@FFI_SOURCES@ -FFI_LIBS=@FFI_LIBS@ -FFI_SOURCE_DIR=@FFI_SOURCE_DIR@ - -HocBuildDylibs=@HocBuildDylibs@ - -DOT=@DOT@ -POD2HTML=@POD2HTML@ - -# installation parameters - -prefix = @prefix@ -DESTDIR = $(prefix) -bindir = $(DESTDIR)/bin - -# distribution tarball information - -dist_dir = @abs_top_builddir@/hoc-@PACKAGE_VERSION@ - -default: all - -dist-recursive: - mkdir -p "$(dist_dir)/$(dist_srcdir)" - cp -R $(dist_FILES) "$(dist_dir)/$(dist_srcdir)" - -CFLAGS+= -I$(GHC_LIB_PATH)/include - -ifeq "$(HocBuildDylibs)" "YES" -EXTRA_GHCFLAGS += -fPIC -dynamic -endif ======================================= --- /trunk/hoc/configure.ac Sun Aug 17 21:58:22 2008 +++ /dev/null @@ -1,292 +0,0 @@ -# -*- Autoconf -*- -# Process this file with autoconf to produce a configure script. - - -# -# Basic autoconf setup -# - -AC_PREREQ(2.57) -AC_INIT(HOC, 0.8, oz...@al...) -AC_CONFIG_AUX_DIR(autotools) - -# Check we're in the right directory -AC_CONFIG_SRCDIR([HOC/HOC/NewClass.hs]) - -# Check system we're running on -AC_CANONICAL_SYSTEM - -# Checks for Objective-C support -AC_LANG_OBJC - -# Checks for programs. -AC_PROG_OBJC -AC_PROG_MAKE_SET -AC_PROG_RANLIB -# other programs to check for: ar cp ghc-pkg ld rm xargs gnumake - -# Programs required for building docs -build_docs_ok=no -AC_CHECK_PROG(POD2HTML, pod2html, pod2html) -APP_GRAPHVIZ_PATH='/Applications/Graphviz.app/Contents/MacOS' -AC_PATH_PROG(DOT, "dot", no, "$APP_GRAPHVIZ_PATH:$PATH") -if test "x$POD2HTML" = "xpod2html"; then - if test "x$DOT" != "xno"; then - build_docs_ok=yes - fi -fi - - -# -# Test for GHC: this handy autoconf macro blatantly stolen from HDoc: -# http://www.fmi.uni-passau.de/~groessli/hdoc/ -# - -AC_ARG_WITH(ghc, - [ --with-ghc=... command to run ghc (e.g. $HOME/bin/ghc-6.4)], - [GHC=$withval]) - -if test -z "$GHC"; then - AC_CHECK_TOOL(GHC, ghc, ghc) -fi - -GHC_FLAGS="" - -if test "$GHC"; then - AC_MSG_CHECKING([for ghc version]) - changequote(<<, >>) - ghc_version=`$GHC --version 2>&1 | sed -n -e 's/.* version \([0-9.][0-9.]*\).*/\1/p'` - ghc_major=`echo "$ghc_version" | sed -n -e 's/\([0-9][0-9]*\).*/\1/p'` - ghc_minor=`echo "$ghc_version" | sed -n -e 's/[0-9][0-9]*\.\([0-9][0-9]*\).*/\1/p'` - changequote([, ]) - AC_MSG_RESULT([$ghc_version]) - if test '(' "$ghc_major" -ge 6 -a "$ghc_minor" -ge 4 ')' -o \ - '(' "$ghc_major" -gt 6 ')'; then - AC_MSG_CHECKING([for ghc library directory]) - GHC_LIB_PATH=`$GHC --print-libdir` - AC_MSG_RESULT([$GHC_LIB_PATH]) - else - AC_MSG_ERROR([** Sorry, your GHC is too old. GHC >= 6.4 required.]) - GHC="" - fi -else - AC_MSG_ERROR([** Could not find GHC.]) -fi - -AC_SUBST(GHC) -AC_SUBST(GHC_LIB_PATH) - -# Check for ghc-pkg -AC_ARG_WITH(ghc-pkg, - [ --with-ghc-pkg=... command to run ghc-pkg (e.g. $HOME/bin/ghc-pkg-6.4)], - [GHC_PKG="$withval"]) - -if test -n "$GHC_PKG"; then - AC_SUBST(GHC_PKG) - true -else - AC_CHECK_TOOL(GHC_PKG, ghc-pkg, ghc-pkg) -fi - - -# -# Check for various C requirements -# - -AC_CHECK_HEADERS([assert.h objc/objc-api.h objc/objc-class.h objc/objc-runtime.h stdlib.h]) -AC_C_CONST -AC_FUNC_MALLOC -AC_CHECK_FUNCS([memset strdup]) - -#check to see if we're building a dynanic haskell lib -AC_ARG_WITH([dynamic-haskell], - [AS_HELP_STRING([--with-dynamic-haskell], - [whether or not to build dynamic libraries for the haskell modules. Default is static])], - [HocBuildDylibs=YES], - [HocBuildDylibs=NO]) -AC_SUBST(HocBuildDylibs) - -# -# Determine which ffi to use -# -AC_ARG_WITH([ffi], - [AS_HELP_STRING([--with-ffi], - [where to find ffi. Use either this or --with-ffi-sources @<:@default=check@:>@])], - [], - [with_ffi=check]) -AC_ARG_WITH([ffi-sources], - [AS_HELP_STRING([--with-ffi-sources], - [where to find ffi sources. Use either this or --with-ffi @<:@default=check@:>@])], - [], - [with_ffi_sources=check]) - - -if test "x$with_ffi" = "xyes"; then - with_ffi=check -fi -if test "x$with_ffi_sources" = "xyes";then - with_ffi_sources=check -fi - -if test "x$with_ffi" != "xcheck" -a "x$with_ffi_sources" != "xcheck"; then - AC_MSG_ERROR([*** Cannot specify both --with-ffi and --with-ffi-sources.]) -fi - -if test "x$with_ffi_sources" = "xcheck" -a "x$with_ffi" != "xcheck"; then - with_ffi_sources=no -fi - -# -# Check for libffi in the libffi-src/ directory -# -case "$with_ffi_sources" in - 'no') - ;; - 'check') - AC_CHECK_FILE([libffi-src/configure], [with_ffi_sources=$(pwd)/libffi-src; $with_ffi_sources/configure], [with_ffi_sources=no]) - ;; - /*) - AC_CHECK_FILE([$with_ffi_sources/configure],[$with_ffi_sources/configure],[with_ffi_sources=fail]) - ;; - *) - with_ffi_sources=$(pwd)/$(dirname $with_ffi_sources)/$(basename $with_ffi_sources) - AC_CHECK_FILE([$with_ffi_sources/configure],[$with_ffi_sources/configure],[with_ffi_sources=fail]) - ;; -esac - -if test "x$with_ffi_sources" = "xfail"; then - AC_MSG_ERROR([*** Unable to locate ffi-sources. Please specify a valid ffi path with --with-ffi-sources]) -elif test "x$with_ffi_sources" != "xno"; then - with_ffi=no -fi - -if test "x$with_ffi_sources" = "xno"; then - case "$with_ffi" in - 'no') - AC_MSG_ERROR([*** Must specify either a valid --with-ffi or a valid --with-ffi-sources]) - ;; - 'check') - AC_CHECK_FILE([/usr/include/ffi/ffi.h], [with_ffi=/usr], [with_ffi=no]) - ;; - /*) - AC_CHECK_FILE([$with_ffi/include/ffi/ffi.h], [], [with_ffi=fail]) - ;; - *) - with_ffi=$(pwd)/$(dirname $with_ffi)/$(basename $with_ffi) - AC_CHECK_FILE([$with_ffi/include/ffi/ffi.h], [], [with_ffi=fail]) - ;; - esac - - if test "x$with_ffi" = "xfail"; then - AC_MSG_ERROR([*** Unable to locate ffi. Please specify a valid ffi path with --with-ffi]) - fi - -fi - -if test "x$with_ffi" = "xno" -a "x$with_ffi_sources" = "xno"; then - AC_MSG_ERROR([*** Must specify one of --with-ffi or --with-ffi-sources]) -fi - -if test "x$with_ffi" != "xno"; then - FFI_CFLAGS="-I$with_ffi/include/ffi" - FFI_SOURCES= - if test "x$with_ffi" == "x/usr"; then - FFI_LIBS="-lffi" - FFI_LIB_DIRS= - else - FFI_LIBS="-L$with_ffi/lib -lffi" - FFI_LIB_DIRS="\"\\\"$with_ffi/lib\\\"\"" - fi - PKG_EXTRA_LIBS="\", \\\"ffi\\\"\"" -elif test "x$with_ffi_sources" != "xno" ; then - FFI_CFLAGS="-I$with_ffi_sources/include" - FFI_SOURCES=" \\ - $with_ffi_sources/src/types.c \\ - $with_ffi_sources/src/prep_cif.c \\ - $with_ffi_sources/src/x86/ffi_darwin.c \\ - $with_ffi_sources/src/x86/darwin.S \\ - $with_ffi_sources/src/powerpc/ffi_darwin.c \\ - $with_ffi_sources/src/powerpc/darwin.S \\ - $with_ffi_sources/src/powerpc/darwin_closure.S" - FFI_SOURCE_DIR=$with_ffi_sources - FFI_LIBS= -fi - -AC_SUBST(FFI_CFLAGS) -AC_SUBST(FFI_SOURCES) -AC_SUBST(FFI_LIBS) -AC_SUBST(FFI_SOURCE_DIR) -AC_SUBST(FFI_LIB_DIRS) -AC_SUBST(PKG_EXTRA_LIBS) - -# -# Check for Cocoa (Mac OS X) or GNUstep platform -# - -AC_MSG_CHECKING([for Objective-C platform]) -case "$target_os" in - darwin*) - AC_MSG_RESULT([Cocoa]) - platform=macos;; - *) - AC_MSG_RESULT([GNUstep]) - platform=gnustep;; -esac - -# Platform-specific definitions go here -if test "x$platform" = "xgnustep"; then - HOC_LD_ALL_LOAD='--whole-archive' - HOC_MAKE_STATIC_LIB='ar cqs' - HOC_FOUNDATION_INCLUDES='-I/usr/lib/GNUstep/System/Library/Headers/' - HOC_FOUNDATION_LIBS='-L/usr/lib/GNUstep/System/Library/Libraries \\\ - -L/usr/lib/gcc-lib/i486-linux/3.3.5 \\\ - -lobjc -lgnustep-base' - HOC_DEFINES='-DGNUSTEP' - HOC_CFLAGS='$(FOUNDATION_INCLUDES) $(DEFINES) \\\ - -fconstant-string-class=NSConstantString \\\ - -Wno-import' - - HOC_FOUNDATION_LIB_DIRS="\"\\\"/usr/lib/GNUstep/System/Library/Libraries\\\" \\\"/usr/lib/gcc-lib/i486-linux/3.3.5\\\"\"" - -else - HOC_LD_ALL_LOAD='-all_load' - HOC_MAKE_STATIC_LIB='libtool -static -o' - HOC_FOUNDATION_INCLUDES='' - HOC_FOUNDATION_LIBS='-framework Foundation' - HOC_DEFINES='' - HOC_CFLAGS='$(FOUNDATION_INCLUDES) $(DEFINES)' - HOC_FOUNDATION_LIB_DIRS='' -fi -HOC_PLATFORM="$platform" -AC_SUBST(HOC_PLATFORM) -AC_SUBST(HOC_LD_ALL_LOAD) -AC_SUBST(HOC_MAKE_STATIC_LIB) -AC_SUBST(HOC_FOUNDATION_INCLUDES) -AC_SUBST(HOC_FOUNDATION_LIBS) -AC_SUBST(HOC_DEFINES) -AC_SUBST(HOC_CFLAGS) -AC_SUBST(HOC_FOUNDATION_LIB_DIRS) - -# -# Output configuration files and Makefiles -# - -AC_SUBST(PACKAGE_VERSION) - -AC_CONFIG_FILES([config.mk - Makefile - AppKit/Makefile - Bindings/Makefile - docs/Makefile - Foundation/Makefile - HOC/Makefile - HOC_cbits/Makefile - InterfaceGenerator/Makefile - InterfaceGenerator2/Makefile - Tools/Makefile - ]) - -AC_OUTPUT - -# Modeline for vi(m) - vi:expandtab - ======================================= --- /trunk/hoc/objc.m4 Tue May 11 22:44:14 2004 +++ /dev/null @@ -1,623 +0,0 @@ -# objc.m4 -# Based on c.m4 from GNU Autoconf -# The Objective C support, added by Landon Fuller <la...@op...> -# on March 10th, 2004, is heavily based on Autoconf's existing C++ support. -# -########### Copyright and Licensing terms ########## -# -# This file is part of Autoconf. -*- Autoconf -*- -# Programming languages support. -# Copyright (C) 2001, 2002, 2003 Free Software Foundation, Inc. -# -# This program is free software; you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation; either version 2, or (at your option) -# any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program; if not, write to the Free Software -# Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA -# 02111-1307, USA. -# -# As a special exception, the Free Software Foundation gives unlimited -# permission to copy, distribute and modify the configure scripts that -# are the output of Autoconf. You need not follow the terms of the GNU -# General Public License when using or distributing such scripts, even -# though portions of the text of Autoconf appear in them. The GNU -# General Public License (GPL) does govern all other use of the material -# that constitutes the Autoconf program. -# -# Certain portions of the Autoconf source text are designed to be copied -# (in certain cases, depending on the input) into the output of -# Autoconf. We call these the "data" portions. The rest of the Autoconf -# source text consists of comments plus executable code that decides which -# of the data portions to output in any given case. We call these -# comments and executable code the "non-data" portions. Autoconf never -# copies any of the non-data portions into its output. -# -# This special exception to the GPL applies to versions of Autoconf -# released by the Free Software Foundation. When you make and -# distribute a modified version of Autoconf, you may extend this special -# exception to the GPL to apply to your modified version as well, *unless* -# your modified version has the potential to copy into its output some -# of the text that was the non-data portion of the version that you started -# with. (In other words, unless your change moves or copies text from -# the non-data portions to the data portions.) If your modification has -# such potential, you must delete any notice of this special exception -# to the GPL from your modified version. -# -# Written by David MacKenzie, with help from -# Franc,ois Pinard, Karl Berry, Richard Pixley, Ian Lance Taylor, -# Roland McGrath, Noah Friedman, david d zuhn, and many others. -# -########## GNU General Public License (GPL), version 2 ########## -# -# GNU GENERAL PUBLIC LICENSE -# Version 2, June 1991 -# -# Copyright (C) 1989, 1991 Free Software Foundation, Inc. -# 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -# Everyone is permitted to copy and distribute verbatim copies -# of this license document, but changing it is not allowed. -# -# Preamble -# -# The licenses for most software are designed to take away your -# freedom to share and change it. By contrast, the GNU General Public -# License is intended to guarantee your freedom to share and change free -# software--to make sure the software is free for all its users. This -# General Public License applies to most of the Free Software -# Foundation's software and to any other program whose authors commit to -# using it. (Some other Free Software Foundation software is covered by -# the GNU Library General Public License instead.) You can apply it to -# your programs, too. -# -# When we speak of free software, we are referring to freedom, not -# price. Our General Public Licenses are designed to make sure that you -# have the freedom to distribute copies of free software (and charge for -# this service if you wish), that you receive source code or can get it -# if you want it, that you can change the software or use pieces of it -# in new free programs; and that you know you can do these things. -# -# To protect your rights, we need to make restrictions that forbid -# anyone to deny you these rights or to ask you to surrender the rights. -# These restrictions translate to certain responsibilities for you if you -# distribute copies of the software, or if you modify it. -# -# For example, if you distribute copies of such a program, whether -# gratis or for a fee, you must give the recipients all the rights that -# you have. You must make sure that they, too, receive or can get the -# source code. And you must show them these terms so they know their -# rights. -# -# We protect your rights with two steps: (1) copyright the software, and -# (2) offer you this license which gives you legal permission to copy, -# distribute and/or modify the software. -# -# Also, for each author's protection and ours, we want to make certain -# that everyone understands that there is no warranty for this free -# software. If the software is modified by someone else and passed on, we -# want its recipients to know that what they have is not the original, so -# that any problems introduced by others will not reflect on the original -# authors' reputations. -# -# Finally, any free program is threatened constantly by software -# patents. We wish to avoid the danger that redistributors of a free -# program will individually obtain patent licenses, in effect making the -# program proprietary. To prevent this, we have made it clear that any -# patent must be licensed for everyone's free use or not licensed at all. -# -# The precise terms and conditions for copying, distribution and -# modification follow. -# -# GNU GENERAL PUBLIC LICENSE -# TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION -# -# 0. This License applies to any program or other work which contains -# a notice placed by the copyright holder saying it may be distributed -# under the terms of this General Public License. The "Program", below, -# refers to any such program or work, and a "work based on the Program" -# means either the Program or any derivative work under copyright law: -# that is to say, a work containing the Program or a portion of it, -# either verbatim or with modifications and/or translated into another -# language. (Hereinafter, translation is included without limitation in -# the term "modification".) Each licensee is addressed as "you". -# -# Activities other than copying, distribution and modification are not -# covered by this License; they are outside its scope. The act of -# running the Program is not restricted, and the output from the Program -# is covered only if its contents constitute a work based on the -# Program (independent of having been made by running the Program). -# Whether that is true depends on what the Program does. -# -# 1. You may copy and distribute verbatim copies of the Program's -# source code as you receive it, in any medium, provided that you -# conspicuously and appropriately publish on each copy an appropriate -# copyright notice and disclaimer of warranty; keep intact all the -# notices that refer to this License and to the absence of any warranty; -# and give any other recipients of the Program a copy of this License -# along with the Program. -# -# You may charge a fee for the physical act of transferring a copy, and -# you may at your option offer warranty protection in exchange for a fee. -# -# 2. You may modify your copy or copies of the Program or any portion -# of it, thus forming a work based on the Program, and copy and -# distribute such modifications or work under the terms of Section 1 -# above, provided that you also meet all of these conditions: -# -# a) You must cause the modified files to carry prominent notices -# stating that you changed the files and the date of any change. -# -# b) You must cause any work that you distribute or publish, that in -# whole or in part contains or is derived from the Program or any -# part thereof, to be licensed as a whole at no charge to all third -# parties under the terms of this License. -# -# c) If the modified program normally reads commands interactively -# when run, you must cause it, when started running for such -# interactive use in the most ordinary way, to print or display an -# announcement including an appropriate copyright notice and a -# notice that there is no warranty (or else, saying that you provide -# a warranty) and that users may redistribute the program under -# these conditions, and telling the user how to view a copy of this -# License. (Exception: if the Program itself is interactive but -# does not normally print such an announcement, your work based on -# the Program is not required to print an announcement.) -# -# These requirements apply to the modified work as a whole. If -# identifiable sections of that work are not derived from the Program, -# and can be reasonably considered independent and separate works in -# themselves, then this License, and its terms, do not apply to those -# sections when you distribute them as separate works. But when you -# distribute the same sections as part of a whole which is a work based -# on the Program, the distribution of the whole must be on the terms of -# this License, whose permissions for other licensees extend to the -# entire whole, and thus to each and every part regardless of who wrote it. -# -# Thus, it is not the intent of this section to claim rights or contest -# your rights to work written entirely by you; rather, the intent is to -# exercise the right to control the distribution of derivative or -# collective works based on the Program. -# -# In addition, mere aggregation of another work not based on the Program -# with the Program (or with a work based on the Program) on a volume of -# a storage or distribution medium does not bring the other work under -# the scope of this License. -# -# 3. You may copy and distribute the Program (or a work based on it, -# under Section 2) in object code or executable form under the terms of -# Sections 1 and 2 above provided that you also do one of the following: -# -# a) Accompany it with the complete corresponding machine-readable -# source code, which must be distributed under the terms of Sections -# 1 and 2 above on a medium customarily used for software interchange; or, -# -# b) Accompany it with a written offer, valid for at least three -# years, to give any third party, for a charge no more than your -# cost of physically performing source distribution, a complete -# machine-readable copy of the corresponding source code, to be -# distributed under the terms of Sections 1 and 2 above on a medium -# customarily used for software interchange; or, -# -# c) Accompany it with the information you received as to the offer -# to distribute corresponding source code. (This alternative is -# allowed only for noncommercial distribution and only if you -# received the program in object code or executable form with such -# an offer, in accord with Subsection b above.) -# -# The source code for a work means the preferred form of the work for -# making modifications to it. For an executable work, complete source -# code means all the source code for all modules it contains, plus any -# associated interface definition files, plus the scripts used to -# control compilation and installation of the executable. However, as a -# special exception, the source code distributed need not include -# anything that is normally distributed (in either source or binary -# form) with the major components (compiler, kernel, and so on) of the -# operating system on which the executable runs, unless that component -# itself accompanies the executable. -# -# If distribution of executable or object code is made by offering -# access to copy from a designated place, then offering equivalent -# access to copy the source code from the same place counts as -# distribution of the source code, even though third parties are not -# compelled to copy the source along with the object code. -# -# 4. You may not copy, modify, sublicense, or distribute the Program -# except as expressly provided under this License. Any attempt -# otherwise to copy, modify, sublicense or distribute the Program is -# void, and will automatically terminate your rights under this License. -# However, parties who have received copies, or rights, from you under -# this License will not have their licenses terminated so long as such -# parties remain in full compliance. -# -# 5. You are not required to accept this License, since you have not -# signed it. However, nothing else grants you permission to modify or -# distribute the Program or its derivative works. These actions are -# prohibited by law if you do not accept this License. Therefore, by -# modifying or distributing the Program (or any work based on the -# Program), you indicate your acceptance of this License to do so, and -# all its terms and conditions for copying, distributing or modifying -# the Program or works based on it. - -# 6. Each time you redistribute the Program (or any work based on the -# Program), the recipient automatically receives a license from the -# original licensor to copy, distribute or modify the Program subject to -# these terms and conditions. You may not impose any further -# restrictions on the recipients' exercise of the rights granted herein. -# You are not responsible for enforcing compliance by third parties to -# this License. -# -# 7. If, as a consequence of a court judgment or allegation of patent -# infringement or for any other reason (not limited to patent issues), -# conditions are imposed on you (whether by court order, agreement or -# otherwise) that contradict the conditions of this License, they do not -# excuse you from the conditions of this License. If you cannot -# distribute so as to satisfy simultaneously your obligations under this -# License and any other pertinent obligations, then as a consequence you -# may not distribute the Program at all. For example, if a patent -# license would not permit royalty-free redistribution of the Program by -# all those who receive copies directly or indirectly through you, then -# the only way you could satisfy both it and this License would be to -# refrain entirely from distribution of the Program. -# -# If any portion of this section is held invalid or unenforceable under -# any particular circumstance, the balance of the section is intended to -# apply and the section as a whole is intended to apply in other -# circumstances. -# -# It is not the purpose of this section to induce you to infringe any -# patents or other property right claims or to contest validity of any -# such claims; this section has the sole purpose of protecting the -# integrity of the free software distribution system, which is -# implemented by public license practices. Many people have made -# generous contributions to the wide range of software distributed -# through that system in reliance on consistent application of that -# system; it is up to the author/donor to decide if he or she is willing -# to distribute software through any other system and a licensee cannot -# impose that choice. -# -# This section is intended to make thoroughly clear what is believed to -# be a consequence of the rest of this License. -# -# 8. If the distribution and/or use of the Program is restricted in -# certain countries either by patents or by copyrighted interfaces, the -# original copyright holder who places the Program under this License -# may add an explicit geographical distribution limitation excluding -# those countries, so that distribution is permitted only in or among -# countries not thus excluded. In such case, this License incorporates -# the limitation as if written in the body of this License. -# -# 9. The Free Software Foundation may publish revised and/or new versions -# of the General Public License from time to time. Such new versions will -# be similar in spirit to the present version, but may differ in detail to -# address new problems or concerns. -# -# Each version is given a distinguishing version number. If the Program -# specifies a version number of this License which applies to it and "any -# later version", you have the option of following the terms and conditions -# either of that version or of any later version published by the Free -# Software Foundation. If the Program does not specify a version number of -# this License, you may choose any version ever published by the Free Software -# Foundation. -# -# 10. If you wish to incorporate parts of the Program into other free -# programs whose distribution conditions are different, write to the author -# to ask for permission. For software which is copyrighted by the Free -# Software Foundation, write to the Free Software Foundation; we sometimes -# make exceptions for this. Our decision will be guided by the two goals -# of preserving the free status of all derivatives of our free software and -# of promoting the sharing and reuse of software generally. -# -# NO WARRANTY -# -# 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY -# FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN -# OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES -# PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED -# OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF -# MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS -# TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE -# PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, -# REPAIR OR CORRECTION. -# -# 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING -# WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR -# REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, -# INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING -# OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED -# TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY -# YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER -# PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE -# POSSIBILITY OF SUCH DAMAGES. -# -# END OF TERMS AND CONDITIONS -# -# How to Apply These Terms to Your New Programs -# -# If you develop a new program, and you want it to be of the greatest -# possible use to the public, the best way to achieve this is to make it -# free software which everyone can redistribute and change under these terms. -# -# To do so, attach the following notices to the program. It is safest -# to attach them to the start of each source file to most effectively -# convey the exclusion of warranty; and each file should have at least -# the "copyright" line and a pointer to where the full notice is found. -# -# <one line to give the program's name and a brief idea of what it does.> -# Copyright (C) <year> <name of author> -# -# This program is free software; you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation; either version 2 of the License, or -# (at your option) any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program; if not, write to the Free Software -# Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA -# -# -# Also add information on how to contact you by electronic and paper mail. -# -# If the program is interactive, make it output a short notice like this -# when it starts in an interactive mode: -# -# Gnomovision version 69, Copyright (C) year name of author -# Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. -# This is free software, and you are welcome to redistribute it -# under certain conditions; type `show c' for details. -# -# The hypothetical commands `show w' and `show c' should show the appropriate -# parts of the General Public License. Of course, the commands you use may -# be called something other than `show w' and `show c'; they could even be -# mouse-clicks or menu items--whatever suits your program. -# -# You should also get your employer (if you work as a programmer) or your -# school, if any, to sign a "copyright disclaimer" for the program, if -# necessary. Here is a sample; alter the names: -# -# Yoyodyne, Inc., hereby disclaims all copyright interest in the program -# `Gnomovision' (which makes passes at compilers) written by James Hacker. -# -# <signature of Ty Coon>, 1 April 1989 -# Ty Coon, President of Vice -# -# This General Public License does not permit incorporating your program into -# proprietary programs. If your program is a subroutine library, you may -# consider it more useful to permit linking proprietary applications with the -# library. If this is what you want to do, use the GNU Library General -# Public License instead of this License. -# -########## End of GNU General Public License (GPL), version 2 ########## - -## ----------------------- ## -## 1. Language selection. ## -## ----------------------- ## - - -# ------------------------------ # -# 1d. The Objective C language. # -# ------------------------------ # - -# AC_LANG(Objective C) -# -------------------- -# OBJCFLAGS is not in ac_cpp because -g, -O, etc. are not valid cpp options. -m4_define([AC_LANG(Objective C)], -[ac_ext=m -ac_cpp='$OBJCPP $CPPFLAGS' -ac_compile='$OBJC -c $OBJCFLAGS $CPPFLAGS conftest.$ac_ext >&AS_MESSAGE_LOG_FD' -ac_link='$OBJC -o conftest$ac_exeext $OBJCFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&AS_MESSAGE_LOG_FD' -ac_compiler_gnu=$ac_cv_objc_compiler_gnu -]) - - -# AC_LANG_OBJC -# ------------------------- -AU_DEFUN([AC_LANG_OBJC], [AC_LANG(Objective C)]) - - -# _AC_LANG_ABBREV(Objective C) -# ---------------------------- -m4_define([_AC_LANG_ABBREV(Objective C)], [objc]) - - -# _AC_LANG_PREFIX(Objective C) -# ---------------------------- -m4_define([_AC_LANG_PREFIX(Objective C)], [OBJC]) - - - -## ---------------------- ## -## 2.Producing programs. ## -## ---------------------- ## - - -# ------------------------- # -# 2d. Objective C sources. # -# ------------------------- # - -# AC_LANG_SOURCE(Objective C)(BODY) -# --------------------------------- -m4_copy([AC_LANG_SOURCE(C)], [AC_LANG_SOURCE(Objective C)]) - - -# AC_LANG_PROGRAM(Objective C)([PROLOGUE], [BODY]) -# ------------------------------------------------ -m4_copy([AC_LANG_PROGRAM(C)], [AC_LANG_PROGRAM(Objective C)]) - - -# AC_LANG_CALL(Objective C)(PROLOGUE, FUNCTION) -# --------------------------------------------- -m4_copy([AC_LANG_CALL(C)], [AC_LANG_CALL(Objective C)]) - - -# AC_LANG_FUNC_LINK_TRY(Objective C)(FUNCTION) -# -------------------------------------------- -m4_copy([AC_LANG_FUNC_LINK_TRY(C)], [AC_LANG_FUNC_LINK_TRY(Objective C)]) - - -# AC_LANG_BOOL_COMPILE_TRY(Objective C)(PROLOGUE, EXPRESSION) -# ----------------------------------------------------------- -m4_copy([AC_LANG_BOOL_COMPILE_TRY(C)], [AC_LANG_BOOL_COMPILE_TRY(Objective C)]) - - -# AC_LANG_INT_SAVE(Objective C)(PROLOGUE, EXPRESSION) -# --------------------------------------------------- -m4_copy([AC_LANG_INT_SAVE(C)], [AC_LANG_INT_SAVE(Objective C)]) - - - -## -------------------------------------------- ## -## 3. Looking for Compilers and Preprocessors. ## -## -------------------------------------------- ## - - -# ------------------------------ # -# 3d. The Objective C compiler. # -# ------------------------------ # - - -# AC_LANG_PREPROC(Objecitve C) -# ---------------------------- -# Find the Objective C preprocessor. Must be AC_DEFUN'd to be AC_REQUIRE'able. -AC_DEFUN([AC_LANG_PREPROC(Objective C)], -[AC_REQUIRE([AC_PROG_OBJCPP])]) - - -# AC_PROG_OBJCPP -# -------------- -# Find a working Objective C preprocessor. -# We shouldn't have to require AC_PROG_CC, but this is due to the concurrency -# between the AC_LANG_COMPILER_REQUIRE family and that of AC_PROG_OBJC. -AC_DEFUN([AC_PROG_OBJCPP], -[AC_REQUIRE([AC_PROG_OBJC])dnl -AC_ARG_VAR([OBJCPP], [Objective C preprocessor])dnl -_AC_ARG_VAR_CPPFLAGS()dnl -AC_LANG_PUSH(Objective C)dnl -AC_MSG_CHECKING([how to run the Objective C preprocessor]) -if test -z "$OBJCPP"; then - AC_CACHE_VAL(ac_cv_prog_OBJCPP, - [dnl - # Double quotes because OBJCPP needs to be expanded - for OBJCPP in "$OBJC -E" "/lib/cpp" - do - _AC_PROG_PREPROC_WORKS_IFELSE([break]) - done - ac_cv_prog_OBJCPP=$OBJCPP - ])dnl - OBJCPP=$ac_cv_prog_OBJCPP -else - ac_cv_prog_OBJCPP=$OBJCPP -fi -AC_MSG_RESULT([$OBJCPP]) -_AC_PROG_PREPROC_WORKS_IFELSE([], - [AC_MSG_FAILURE([Objective C preprocessor "$OBJCPP" fails sanity check])]) -AC_SUBST(OBJCPP)dnl -AC_LANG_POP(Objective C)dnl -])# AC_PROG_OBJCPP - - -# AC_LANG_COMPILER(Objective C) -# ----------------------------- -# Find the Objective C compiler. Must be AC_DEFUN'd to be AC_REQUIRE'able. -AC_DEFUN([AC_LANG_COMPILER(Objective C)], -[AC_REQUIRE([AC_PROG_OBJC])]) - - -# ac_cv_prog_objc -# --------------- -# We used to name the cache variable this way. -AU_DEFUN([ac_cv_prog_objc], -[ac_cv_objc_compiler_gnu]) - - -# AC_PROG_OBJC([LIST-OF-COMPILERS]) -# --------------------------------- -# LIST-OF-COMPILERS is a space separated list of Objective C compilers -# to search for (if not specified, a default list is used). This just gives -# the user an opportunity to specify an alternative search list for the -# Objective C compiler. -# cc Native compiler -# objc David Stes' Portable Object Compiler -AN_MAKEVAR([OBJC], [AC_PROG_OBJC]) -AN_PROGRAM([gcc], [AC_PROG_OBJC]) -AN_PROGRAM([cc], [AC_PROG_OBJC]) -AC_DEFUN([AC_PROG_OBJC], -[AC_LANG_PUSH(Objective C)dnl -AC_ARG_VAR([OBJC], [Objective C compiler command])dnl -AC_ARG_VAR([OBJCFLAGS], [Objective C compiler flags])dnl -_AC_ARG_VAR_LDFLAGS()dnl -_AC_ARG_VAR_CPPFLAGS()dnl -AC_CHECK_TOOLS(OBJC, - [$CCC m4_default([$1], - [gcc cc objc])], - gcc) - -# Provide some information about the compiler. -echo "$as_me:$LINENO:" \ - "checking for _AC_LANG compiler version" >&AS_MESSAGE_LOG_FD -ac_compiler=`set X $ac_compile; echo $[2]` -_AC_EVAL([$ac_compiler --version </dev/null >&AS_MESSAGE_LOG_FD]) -_AC_EVAL([$ac_compiler -v </dev/null >&AS_MESSAGE_LOG_FD]) -_AC_EVAL([$ac_compiler -V </dev/null >&AS_MESSAGE_LOG_FD]) - -m4_expand_once([_AC_COMPILER_EXEEXT])[]dnl -m4_expand_once([_AC_COMPILER_OBJEXT])[]dnl -_AC_LANG_COMPILER_GNU -GOBJC=`test $ac_compiler_gnu = yes && echo yes` -_AC_PROG_OBJC_G -AC_LANG_POP(Objective C)dnl -])# AC_PROG_OBJC - - -# _AC_PROG_OBJC_G -# --------------- -# Check whether -g works, even if OBJCFLAGS is set, in case the package -# plays around with OBJCFLAGS (such as to build both debugging and -# normal versions of a library), tasteless as that idea is. -m4_define([_AC_PROG_OBJC_G], -[ac_test_OBJCFLAGS=${OBJCFLAGS+set} -ac_save_OBJCFLAGS=$OBJCFLAGS -OBJCFLAGS="-g" -AC_CACHE_CHECK(whether $OBJC accepts -g, ac_cv_prog_objc_g, - [_AC_COMPILE_IFELSE([AC_LANG_PROGRAM()], - [ac_cv_prog_objc_g=yes], - [ac_cv_prog_objc_g=no])]) -if test "$ac_test_OBJCFLAGS" = set; then - OBJCFLAGS=$ac_save_OBJCFLAGS -elif test $ac_cv_prog_objc_g = yes; then - if test "$GOBJC" = yes; then - OBJCFLAGS="-g -O2" - else - OBJCFLAGS="-g" - fi -else - if test "$GOBJC" = yes; then - OBJCFLAGS="-O2" - else - OBJCFLAGS= - fi -fi[]dnl -])# _AC_PROG_OBJC_G - - -## ------------------------------- ## -## 4. Compilers' characteristics. ## -## ------------------------------- ## - - -# -------------------------------- # -# 4b. C compiler characteristics. # -# -------------------------------- # - -# libobjc and objc header tests shere? |
From: <cod...@go...> - 2009-08-11 20:42:59
|
Revision: 396 Author: wol...@gm... Date: Tue Aug 11 13:37:27 2009 Log: update documentation on the subject of building HOC http://code.google.com/p/hoc/source/detail?r=396 Deleted: /trunk/hoc/BUILDING.CVS Modified: /trunk/hoc/README.txt ======================================= --- /trunk/hoc/BUILDING.CVS Wed May 19 19:17:05 2004 +++ /dev/null @@ -1,34 +0,0 @@ -CVS BUILDING INSTRUCTIONS -========================= - -These are build instructions if you've checked out HOC from CVS -(instead of downloading a source distribution tarball). - -1. Check out the libffi module from HOC's CVS repository into - a directory named libffi-src/ in the HOC source tree: - - cvs -d :pserver:ano...@cv...:/cvsroot/hoc co -d libffi-src libffi - - You can also check out libffi into another directory: if you - do this, just make sure that - -2. Execute autogen.sh to generate the GNU ./configure script: - - ./autogen.sh - -3. Build HOC as usual with ./configure && make && make install. - - -cvsps -===== - -While we'd love to use a more modern revision control system such as -darcs, Subversion or GNU arch, Sourceforge "only" provides a CVS server, -so we're using that. For people who are used to more modern revision -control systems and miss working with 'patchsets' instead of the disjoint -per-file patches that CVS uses, take a look at cvsps -<http://www.cobite.com/cvsps/>, a patchset manager for CVS. While it -doesn't, by any means, give you the many advantages that more modern -source control systems offer you, it certainly makes using CVS and -managing patches far easier! - ======================================= --- /trunk/hoc/README.txt Thu Mar 31 07:35:23 2005 +++ /trunk/hoc/README.txt Tue Aug 11 13:37:27 2009 @@ -22,9 +22,9 @@ You can use HOC to write full-blown GUI applications using Mac OS X's advanced Cocoa framework. -For more information on HOC, see its homepage, at: - - http://hoc.sourceforge.net/ +For more information on HOC, see its google code project page, at: + + http://code.google.com/p/hoc Building HOC @@ -35,35 +35,38 @@ target platforms (Mac OS X 10.2, 10.3, or various Linux & GNUstep platforms). You'll thus have to build HOC from source code. -(Note: If you have checked out HOC from CVS, see the BUILDING.CVS file for -build instructions instead of this.) - -HOC uses GNU autoconf for its build system, so building HOC should be -a simple matter of the standard autoconf build mantra: - - ./configure - make - make install - -If you have a problem building HOC, please check the "Requirements" -section in the docs/HOC.html file to make sure that you have all the Good -Stuff required for HOC to build properly. If you've got everything you -need and HOC still doesn't work, this is a _bug_ -- please see the support -page at http://hoc.sourceforge.net/support.html, and contact one of the -HOC developers to help you out. Chances are that a few other people have -run into the same problems as you! - -HOC should automatically locate where GHC is on your system, but if you -want to specify what command it should use to run GHC, HOC's ./configure -script takes a few extra flags you'll be interested in: - - --with-ghc=... command to run ghc (e.g. $HOME/bin/ghc-6.4) - --with-ghc-pkg=... command to run ghc-pkg (e.g. $HOME/bin/ghc-pkg-6.4) - -Note that HOC will install itself to GHC's library directory (which you -can find out yourself with `ghc --print-libdir`), so you'll need the -appropriate permissions to write to there during the 'make install'. - +1. Build the HOC library and the interface generator: + + cabal configure + cabal build + cabal install + +To run the unit tests, use: + + cabal configure -fTests + cabal build + ./dist/build/hoc-test/hoc-test + cabal install + +2. Create the bindings: + + cd Bindings + sh make-bindings-macos.sh + cd .. + +3. Build the hoc-wrap tool: + + cd Tools + cabal configure + cabal build + cabal install + cd .. + + +Depending on your setup, you will need to add "sudo" in front of the +"cabal install" commands and in front of the make-bindings command. +You can also add additional Cabal configure options after "cabal configure" +and after "sh make-bindings-macos.sh". Authors ======= |
From: <cod...@go...> - 2009-08-11 20:39:00
|
Revision: 395 Author: wol...@gm... Date: Tue Aug 11 13:36:24 2009 Log: add a magic incantation to reduce executable sizes and link times by a huge factor (i.e. 1MB instead of 31MB for an unstripped binary): ghc-options: -optl-Wl,-dead_strip http://code.google.com/p/hoc/source/detail?r=395 Modified: /trunk/hoc/Samples/Browser/Browser.cabal /trunk/hoc/Samples/Editor/Editor.cabal /trunk/hoc/Samples/ExpressionParser/ExpressionParser.cabal /trunk/hoc/Samples/UniqSort/UniqSort.cabal ======================================= --- /trunk/hoc/Samples/Browser/Browser.cabal Tue Aug 11 13:08:42 2009 +++ /trunk/hoc/Samples/Browser/Browser.cabal Tue Aug 11 13:36:24 2009 @@ -7,3 +7,6 @@ main-is: Main.hs build-depends: base, array, HOC, HOC-Cocoa, HOC-Foundation, HOC-AppKit, parsec >= 3.0 + +-- reduce executable size by *a lot*: +ghc-options: -optl-Wl,-dead_strip ======================================= --- /trunk/hoc/Samples/Editor/Editor.cabal Tue Aug 11 13:08:42 2009 +++ /trunk/hoc/Samples/Editor/Editor.cabal Tue Aug 11 13:36:24 2009 @@ -6,3 +6,6 @@ executable: Editor main-is: Main.hs build-depends: base, HOC, HOC-Cocoa, HOC-Foundation, HOC-AppKit, parsec >= 3.0 + +-- reduce executable size by *a lot*: +ghc-options: -optl-Wl,-dead_strip ======================================= --- /trunk/hoc/Samples/ExpressionParser/ExpressionParser.cabal Tue Aug 11 13:08:42 2009 +++ /trunk/hoc/Samples/ExpressionParser/ExpressionParser.cabal Tue Aug 11 13:36:24 2009 @@ -6,3 +6,6 @@ executable: ExpressionParser main-is: Main.hs build-depends: base, HOC, HOC-Cocoa, HOC-Foundation, HOC-AppKit, parsec >= 3.0 + +-- reduce executable size by *a lot*: +ghc-options: -optl-Wl,-dead_strip ======================================= --- /trunk/hoc/Samples/UniqSort/UniqSort.cabal Tue Aug 11 13:08:42 2009 +++ /trunk/hoc/Samples/UniqSort/UniqSort.cabal Tue Aug 11 13:36:24 2009 @@ -6,3 +6,6 @@ executable: UniqSort main-is: UniqSort.hs build-depends: base, HOC, HOC-Foundation + +-- reduce executable size by *a lot*: +ghc-options: -optl-Wl,-dead_strip |
From: <cod...@go...> - 2009-08-11 20:34:52
|
Revision: 394 Author: wol...@gm... Date: Tue Aug 11 13:34:07 2009 Log: change a path name so that tests can now be run from the main HOC directory, where the cabal file that builds the tests is located http://code.google.com/p/hoc/source/detail?r=394 Modified: /trunk/hoc/Tests/TestFoundation.hs ======================================= --- /trunk/hoc/Tests/TestFoundation.hs Sat Feb 14 12:53:11 2009 +++ /trunk/hoc/Tests/TestFoundation.hs Tue Aug 11 13:34:07 2009 @@ -20,6 +20,9 @@ import MiniFoundation + -- (relative) path name of a text file that can be assumed to exist +testTextFile = "HOC.cabal" + -- garbage collect and make really sure that finalizers have time to run performGCAndWait targetCount time maxRepeat = do performGC @@ -176,9 +179,9 @@ fromNSString (toNSString "Hello, world.") @?= "Hello, world." ), "initWithContentsOfFile" ~: (assertNoLeaks $ do - expected <- readFile "TestFoundation.hs" + expected <- readFile testTextFile actual_ns <- _NSString # alloc >>= initWithContentsOfFile - (toNSString "TestFoundation.hs") + (toNSString testTextFile) fromNSString actual_ns @?= expected ), "Unicode" ~: |
From: <cod...@go...> - 2009-08-11 20:11:36
|
Revision: 393 Author: wol...@gm... Date: Tue Aug 11 13:08:42 2009 Log: add cabal build files for the samples, and fix some compile errors http://code.google.com/p/hoc/source/detail?r=393 Added: /trunk/hoc/Samples/Browser/Browser.cabal /trunk/hoc/Samples/Browser/Contents/Resources/all-selectors.txt /trunk/hoc/Samples/Browser/Setup.hs /trunk/hoc/Samples/Editor/Editor.cabal /trunk/hoc/Samples/Editor/Setup.hs /trunk/hoc/Samples/ExpressionParser/ExpressionParser.cabal /trunk/hoc/Samples/ExpressionParser/Setup.hs /trunk/hoc/Samples/UniqSort/UniqSort.cabal Modified: /trunk/hoc/Samples/Browser/BrowserController.hs /trunk/hoc/Samples/Browser/Main.hs /trunk/hoc/Samples/Browser/TVUtilities.hs /trunk/hoc/Samples/Editor/HaskellDocument.hs /trunk/hoc/Samples/UniqSort/UniqSort.hs ======================================= --- /dev/null +++ /trunk/hoc/Samples/Browser/Browser.cabal Tue Aug 11 13:08:42 2009 @@ -0,0 +1,9 @@ +name: Browser +Cabal-Version: >= 1.2 +version: 1.0 +build-type: Custom + +executable: Browser +main-is: Main.hs +build-depends: base, array, + HOC, HOC-Cocoa, HOC-Foundation, HOC-AppKit, parsec >= 3.0 ======================================= --- /dev/null +++ /trunk/hoc/Samples/Browser/Contents/Resources/all-selectors.txt Tue Aug 11 13:08:42 2009 @@ -0,0 +1,6359 @@ +("usesAlternatingRowBackgroundColors","usesAlternatingRowBackgroundColors","IO Bool","AppKit.NSTableView") +("initAsTearOff","initAsTearOff","IO Inited","AppKit.NSMenuView") +("pasteboardChangedOwner","pasteboardChangedOwner:","forall t1 . NSPasteboard t1 -> IO ()","AppKit.NSPasteboard") +("fontWithNameSize","fontWithName:size:","forall t1 . NSString t1 -> Float -> IO (NSFont ())","AppKit.NSFont") +("makeNextSegmentKey","makeNextSegmentKey","IO ()","AppKit.NSSegmentedCell") +("sharedCredentialStorage","sharedCredentialStorage","IO (NSURLCredentialStorage ())","Foundation.NSURLCredentialStorage") +("drawSheetBorderWithSize","drawSheetBorderWithSize:","NSSize -> IO ()","AppKit.NSView") +("subscriptRange","subscriptRange:","NSRange -> IO ()","AppKit.NSAttributedString") +("replaceObjectsInRangeWithObjectsFromArray","replaceObjectsInRange:withObjectsFromArray:","forall t2 . NSRange -> NSArray t2 -> IO ()","Foundation.NSArray") +("setFileAttributes","setFileAttributes:","forall t1 . NSDictionary t1 -> IO ()","AppKit.NSFileWrapper") +("browserCreateRowsForColumnInMatrix","browser:createRowsForColumn:inMatrix:","forall t1 t3 . NSBrowser t1 -> Int -> NSMatrix t3 -> IO ()","AppKit.NSBrowser") +("initWithContent","initWithContent:","forall t1 . ID t1 -> IO Inited","AppKit.NSObjectController") +("arrangeInFront","arrangeInFront:","forall t1 . ID t1 -> IO ()","AppKit.NSApplication") +("helpRequested","helpRequested:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSResponder") +("helpRequested","helpRequested:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSMenu") +("movieUnfilteredPasteboardTypes","movieUnfilteredPasteboardTypes","IO (NSArray ())","AppKit.NSMovie") +("valueWithObjCType","value:withObjCType:","Ptr () -> Ptr CChar -> IO (NSValue ())","Foundation.NSValue") +("setStartSubelementIdentifier","setStartSubelementIdentifier:","NSWhoseSubelementIdentifier -> IO ()","Foundation.NSScriptObjectSpecifiers") +("initWithTimeIntervalSinceDate","initWithTimeInterval:sinceDate:","forall t2 . NSTimeInterval -> NSDate t2 -> IO Inited","Foundation.NSDate") +("setData","setData:","forall t1 . NSData t1 -> IO ()","Foundation.NSData") +("setHorizontalPagination","setHorizontalPagination:","NSPrintingPaginationMode -> IO ()","AppKit.NSPrintInfo") +("imageWillLoadRepresentation","image:willLoadRepresentation:","forall t1 t2 . NSImage t1 -> NSImageRep t2 -> IO ()","AppKit.NSImage") +("countWordsInStringLanguage","countWordsInString:language:","forall t1 t2 . NSString t1 -> NSString t2 -> IO Int","AppKit.NSSpellChecker") +("resizeLeftCursor","resizeLeftCursor","IO (NSCursor ())","AppKit.NSCursor") +("relativePath","relativePath","IO (NSString ())","Foundation.NSURL") +("valueWithPointer","valueWithPointer:","Ptr () -> IO (NSValue ())","Foundation.NSValue") +("serializeInt","serializeInt:","Int -> IO ()","Foundation.NSSerialization") +("writeToFileOfTypeOriginalFileSaveOperation","writeToFile:ofType:originalFile:saveOperation:","forall t1 t2 t3 . NSString t1 -> NSString t2 -> NSString t3 -> NSSaveOperationType -> IO Bool","AppKit.NSDocument") +("supportsMode","supportsMode:","Int -> IO Bool","AppKit.NSColorPicking") +("initWithURL","initWithURL:","forall t1 . NSURL t1 -> IO Inited","Foundation.NSURLRequest") +("setTimeInterval","setTimeInterval:","NSTimeInterval -> IO ()","AppKit.NSDatePicker") +("setTimeInterval","setTimeInterval:","NSTimeInterval -> IO ()","AppKit.NSDatePickerCell") +("autosaveExpandedItems","autosaveExpandedItems","IO Bool","AppKit.NSOutlineView") +("initWithContentSizePreferredEdge","initWithContentSize:preferredEdge:","NSSize -> NSRectEdge -> IO Inited","AppKit.NSDrawer") +("resetCancelButtonCell","resetCancelButtonCell","IO ()","AppKit.NSSearchFieldCell") +("setExtensionHidden","setExtensionHidden:","Bool -> IO ()","AppKit.NSSavePanel") +("setPathSeparator","setPathSeparator:","forall t1 . NSString t1 -> IO ()","AppKit.NSBrowser") +("pathSeparator","pathSeparator","IO (NSString ())","AppKit.NSBrowser") +("mouseInRect","mouse:inRect:","NSPoint -> NSRect -> IO Bool","AppKit.NSView") +("applicationDidUnhide","applicationDidUnhide:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSApplication") +("setWithSet","setWithSet:","forall t1 . NSSet t1 -> IO (ID ())","Foundation.NSSet") +("enableKeyEquivalentForDefaultButtonCell","enableKeyEquivalentForDefaultButtonCell","IO ()","AppKit.NSWindow") +("setMenuForSegment","setMenu:forSegment:","forall t1 . NSMenu t1 -> Int -> IO ()","AppKit.NSSegmentedControl") +("setMenuForSegment","setMenu:forSegment:","forall t1 . NSMenu t1 -> Int -> IO ()","AppKit.NSSegmentedCell") +("setAutorecalculatesKeyViewLoop","setAutorecalculatesKeyViewLoop:","Bool -> IO ()","AppKit.NSWindow") +("validateToolbarItem","validateToolbarItem:","forall t1 . NSToolbarItem t1 -> IO Bool","AppKit.NSToolbarItem") +("intersectsIndexesInRange","intersectsIndexesInRange:","NSRange -> IO Bool","Foundation.NSIndexSet") +("encodeRect","encodeRect:","NSRect -> IO ()","Foundation.NSGeometry") +("addColumnWithCells","addColumnWithCells:","forall t1 . NSArray t1 -> IO ()","AppKit.NSMatrix") +("setAlwaysUsesMultipleValuesMarker","setAlwaysUsesMultipleValuesMarker:","Bool -> IO ()","AppKit.NSTreeController") +("setAlwaysUsesMultipleValuesMarker","setAlwaysUsesMultipleValuesMarker:","Bool -> IO ()","AppKit.NSArrayController") +("colorUsingColorSpace","colorUsingColorSpace:","forall t1 . NSColorSpace t1 -> IO (NSColor ())","AppKit.NSColor") +("realm","realm","IO (NSString ())","Foundation.NSURLProtectionSpace") +("setCommands","setCommands:","forall t1 . NSArray t1 -> IO ()","AppKit.NSSpeechRecognizer") +("sortedArrayUsingDescriptors","sortedArrayUsingDescriptors:","forall t1 . NSArray t1 -> IO (NSArray ())","Foundation.NSSortDescriptor") +("cookiesForURL","cookiesForURL:","forall t1 . NSURL t1 -> IO (NSArray ())","Foundation.NSHTTPCookieStorage") +("setMinimumDaysInFirstWeek","setMinimumDaysInFirstWeek:","CUInt -> IO ()","Foundation.NSCalendar") +("setVolume","setVolume:","Float -> IO ()","AppKit.NSMovieView") +("postsBoundsChangedNotifications","postsBoundsChangedNotifications","IO Bool","AppKit.NSView") +("undoManager","undoManager","IO (NSUndoManager ())","AppKit.NSResponder") +("undoManager","undoManager","IO (NSUndoManager ())","AppKit.NSDocument") +("setRunLoopModes","setRunLoopModes:","forall t1 . NSArray t1 -> IO ()","Foundation.NSUndoManager") +("datePickerMode","datePickerMode","IO NSDatePickerMode","AppKit.NSDatePicker") +("datePickerMode","datePickerMode","IO NSDatePickerMode","AppKit.NSDatePickerCell") +("listOptions","listOptions","IO CUInt","AppKit.NSTextList") +("offsetInFile","offsetInFile","IO CULLong","Foundation.NSFileHandle") +("setAttributedAlternateTitle","setAttributedAlternateTitle:","forall t1 . NSAttributedString t1 -> IO ()","AppKit.NSButton") +("setAttributedAlternateTitle","setAttributedAlternateTitle:","forall t1 . NSAttributedString t1 -> IO ()","AppKit.NSButtonCell") +("usedRectForTextContainer","usedRectForTextContainer:","forall t1 . NSTextContainer t1 -> IO NSRect","AppKit.NSLayoutManager") +("unarchiveObjectWithData","unarchiveObjectWithData:","forall t1 . NSData t1 -> IO (ID ())","Foundation.NSKeyedArchiver") +("unarchiveObjectWithData","unarchiveObjectWithData:","forall t1 . NSData t1 -> IO (ID ())","Foundation.NSArchiver") +("punctuationCharacterSet","punctuationCharacterSet","IO (NSCharacterSet ())","Foundation.NSCharacterSet") +("filePosixPermissions","filePosixPermissions","IO CULong","Foundation.NSFileManager") +("initWithUTF8String","initWithUTF8String:","Ptr CChar -> IO Inited","Foundation.NSString") +("saveFrameUsingName","saveFrameUsingName:","forall t1 . NSString t1 -> IO ()","AppKit.NSWindow") +("initWithLongLong","initWithLongLong:","CLLong -> IO Inited","Foundation.NSValue") +("canonicalLocaleIdentifierFromString","canonicalLocaleIdentifierFromString:","forall t1 . NSString t1 -> IO (NSString ())","Foundation.NSLocale") +("levelForRow","levelForRow:","Int -> IO Int","AppKit.NSOutlineView") +("acceptableDragTypes","acceptableDragTypes","IO (NSArray ())","AppKit.NSTextView") +("minDate","minDate","IO (NSDate ())","AppKit.NSDatePicker") +("minDate","minDate","IO (NSDate ())","AppKit.NSDatePickerCell") +("formatter","formatter","IO (ID ())","AppKit.NSControl") +("formatter","formatter","IO (ID ())","AppKit.NSCell") +("drawers","drawers","IO (NSArray ())","AppKit.NSDrawer") +("soundDidFinishPlaying","sound:didFinishPlaying:","forall t1 . NSSound t1 -> Bool -> IO ()","AppKit.NSSound") +("setWeekday","setWeekday:","Int -> IO ()","Foundation.NSCalendar") +("setWeek","setWeek:","Int -> IO ()","Foundation.NSCalendar") +("performClickWithFrameInView","performClickWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSPopUpButtonCell") +("addTabViewItem","addTabViewItem:","forall t1 . NSTabViewItem t1 -> IO ()","AppKit.NSTabView") +("setHiddenUntilMouseMoves","setHiddenUntilMouseMoves:","Bool -> IO ()","AppKit.NSCursor") +("resourceData","resourceData","IO (NSData ())","Foundation.NSURLHandle") +("isTransparent","isTransparent","IO Bool","AppKit.NSButton") +("isTransparent","isTransparent","IO Bool","AppKit.NSButtonCell") +("elementWithNameChildrenAttributes","elementWithName:children:attributes:","forall t1 t2 t3 . NSString t1 -> NSArray t2 -> NSArray t3 -> IO (ID ())","Foundation.NSXMLNode") +("resetTotalAutoreleasedObjects","resetTotalAutoreleasedObjects","IO ()","Foundation.NSDebug") +("currentMode","currentMode","IO Int","AppKit.NSColorPicking") +("currentMode","currentMode","IO (NSString ())","Foundation.NSRunLoop") +("namespaceForPrefix","namespaceForPrefix:","forall t1 . NSString t1 -> IO (NSXMLNode ())","Foundation.NSXMLElement") +("selectedTextAttributes","selectedTextAttributes","IO (NSDictionary ())","AppKit.NSTextView") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSSound") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSMovie") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSImageRep") +("canInitWithPasteboard","canInitWithPasteboard:","forall t1 . NSPasteboard t1 -> IO Bool","AppKit.NSImage") +("representationUsingTypeProperties","representationUsingType:properties:","forall t2 . NSBitmapImageFileType -> NSDictionary t2 -> IO (NSData ())","AppKit.NSBitmapImageRep") +("isMovable","isMovable","IO Bool","AppKit.NSRulerMarker") +("menuFontOfSize","menuFontOfSize:","Float -> IO (NSFont ())","AppKit.NSFont") +("accessibilityAttributeValue","accessibilityAttributeValue:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSAccessibility") +("setDTD","setDTD:","forall t1 . NSXMLDTD t1 -> IO ()","Foundation.NSXMLDocument") +("attributedSubstringFromRange","attributedSubstringFromRange:","NSRange -> IO (NSAttributedString ())","AppKit.NSInputManager") +("attributedSubstringFromRange","attributedSubstringFromRange:","NSRange -> IO (NSAttributedString ())","Foundation.NSAttributedString") +("scaleBy","scaleBy:","Float -> IO ()","Foundation.NSAffineTransform") +("noteNewRecentDocument","noteNewRecentDocument:","forall t1 . NSDocument t1 -> IO ()","AppKit.NSDocumentController") +("dtdnodeWithXMLString","DTDNodeWithXMLString:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSXMLNode") +("menuBarHeight","menuBarHeight","IO Float","AppKit.NSMenuView") +("menuBarHeight","menuBarHeight","IO Float","AppKit.NSMenu") +("isAnyApplicationSpeaking","isAnyApplicationSpeaking","IO Bool","AppKit.NSSpeechSynthesizer") +("canUndo","canUndo","IO Bool","Foundation.NSUndoManager") +("rulerViewWillAddMarkerAtLocation","rulerView:willAddMarker:atLocation:","forall t1 t2 . NSRulerView t1 -> NSRulerMarker t2 -> Float -> IO Float","AppKit.NSRulerView") +("applicationDidHide","applicationDidHide:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSApplication") +("readToEndOfFileInBackgroundAndNotifyForModes","readToEndOfFileInBackgroundAndNotifyForModes:","forall t1 . NSArray t1 -> IO ()","Foundation.NSFileHandle") +("setCriticalValue","setCriticalValue:","Double -> IO ()","AppKit.NSLevelIndicator") +("setCriticalValue","setCriticalValue:","Double -> IO ()","AppKit.NSLevelIndicatorCell") +("criticalValue","criticalValue","IO Double","AppKit.NSLevelIndicator") +("criticalValue","criticalValue","IO Double","AppKit.NSLevelIndicatorCell") +("acceptsArrowKeys","acceptsArrowKeys","IO Bool","AppKit.NSBrowser") +("commitEditingWithDelegateDidCommitSelectorContextInfo","commitEditingWithDelegate:didCommitSelector:contextInfo:","forall t1 . ID t1 -> SEL -> Ptr () -> IO ()","AppKit.NSKeyValueBinding") +("setImageScaling","setImageScaling:","NSImageScaling -> IO ()","AppKit.NSImageView") +("setImageScaling","setImageScaling:","NSImageScaling -> IO ()","AppKit.NSImageCell") +("open","open","IO ()","AppKit.NSDrawer") +("open","open","IO ()","Foundation.NSStream") +("initWithBytesNoCopyLength","initWithBytesNoCopy:length:","Ptr () -> CUInt -> IO Inited","Foundation.NSData") +("underline","underline:","forall t1 . ID t1 -> IO ()","AppKit.NSText") +("resetCursorRects","resetCursorRects","IO ()","AppKit.NSWindow") +("resetCursorRects","resetCursorRects","IO ()","AppKit.NSView") +("secondsFromGMTForDate","secondsFromGMTForDate:","forall t1 . NSDate t1 -> IO Int","Foundation.NSTimeZone") +("postNotificationNameObject","postNotificationName:object:","forall t1 t2 . NSString t1 -> ID t2 -> IO ()","Foundation.NSNotification") +("setMiniwindowImage","setMiniwindowImage:","forall t1 . NSImage t1 -> IO ()","AppKit.NSWindow") +("selectorForCommand","selectorForCommand:","forall t1 . NSScriptCommandDescription t1 -> IO SEL","Foundation.NSScriptClassDescription") +("postNotificationNameObjectUserInfoOptions","postNotificationName:object:userInfo:options:","forall t1 t2 t3 . NSString t1 -> NSString t2 -> NSDictionary t3 -> CUInt -> IO ()","Foundation.NSDistributedNotificationCenter") +("selectItemWithTitle","selectItemWithTitle:","forall t1 . NSString t1 -> IO ()","AppKit.NSPopUpButtonCell") +("selectItemWithTitle","selectItemWithTitle:","forall t1 . NSString t1 -> IO ()","AppKit.NSPopUpButton") +("attachSubmenuForItemAtIndex","attachSubmenuForItemAtIndex:","Int -> IO ()","AppKit.NSMenuView") +("valueWraps","valueWraps","IO Bool","AppKit.NSStepper") +("valueWraps","valueWraps","IO Bool","AppKit.NSStepperCell") +("getFirstUnlaidCharacterIndexGlyphIndex","getFirstUnlaidCharacterIndex:glyphIndex:","Ptr CUInt -> Ptr CUInt -> IO ()","AppKit.NSLayoutManager") +("dictionaryFromTXTRecordData","dictionaryFromTXTRecordData:","forall t1 . NSData t1 -> IO (NSDictionary ())","Foundation.NSNetServices") +("setRequestTimeout","setRequestTimeout:","NSTimeInterval -> IO ()","Foundation.NSConnection") +("string","string","IO (NSString ())","AppKit.NSText") +("string","string","IO (ID ())","Foundation.NSString") +("string","string","IO (NSString ())","Foundation.NSScanner") +("string","string","IO (NSString ())","Foundation.NSAttributedString") +("drawerWillOpen","drawerWillOpen:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSDrawer") +("fontWithDescriptorSize","fontWithDescriptor:size:","forall t1 . NSFontDescriptor t1 -> Float -> IO (NSFont ())","AppKit.NSFont") +("archiverDidFinish","archiverDidFinish:","forall t1 . NSKeyedArchiver t1 -> IO ()","Foundation.NSKeyedArchiver") +("setPredicate","setPredicate:","forall t1 . NSPredicate t1 -> IO ()","Foundation.NSMetadata") +("setIconForFileOptions","setIcon:forFile:options:","forall t1 t2 . NSImage t1 -> NSString t2 -> CUInt -> IO Bool","AppKit.NSWorkspace") +("setFileModificationDate","setFileModificationDate:","forall t1 . NSDate t1 -> IO ()","AppKit.NSDocument") +("elementCount","elementCount","IO Int","AppKit.NSBezierPath") +("docFormatFromRangeDocumentAttributes","docFormatFromRange:documentAttributes:","forall t2 . NSRange -> NSDictionary t2 -> IO (NSData ())","AppKit.NSAttributedString") +("setNilValueForKey","setNilValueForKey:","forall t1 . NSString t1 -> IO ()","Foundation.NSKeyValueCoding") +("dictionaryWithContentsOfFile","dictionaryWithContentsOfFile:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSDictionary") +("initWithWindowRect","initWithWindow:rect:","forall t1 . NSWindow t1 -> NSRect -> IO Inited","AppKit.NSCachedImageRep") +("textStorageDidProcessEditing","textStorageDidProcessEditing:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSTextStorage") +("addNamespace","addNamespace:","forall t1 . NSXMLNode t1 -> IO ()","Foundation.NSXMLElement") +("urlhandleResourceDidBeginLoading","URLHandleResourceDidBeginLoading:","forall t1 . NSURLHandle t1 -> IO ()","Foundation.NSURLHandle") +("knownTimeZoneNames","knownTimeZoneNames","IO (NSArray ())","Foundation.NSTimeZone") +("encodeFloatForKey","encodeFloat:forKey:","forall t2 . Float -> NSString t2 -> IO ()","Foundation.NSCoder") +("contentSizeForFrameSizeHasHorizontalScrollerHasVerticalScrollerBorderType","contentSizeForFrameSize:hasHorizontalScroller:hasVerticalScroller:borderType:","NSSize -> Bool -> Bool -> NSBorderType -> IO NSSize","AppKit.NSScrollView") +("startSubelementIdentifier","startSubelementIdentifier","IO NSWhoseSubelementIdentifier","Foundation.NSScriptObjectSpecifiers") +("documents","documents","IO (NSArray ())","AppKit.NSDocumentController") +("setAlternateMnemonicLocation","setAlternateMnemonicLocation:","CUInt -> IO ()","AppKit.NSButtonCell") +("insertItemWithTitleActionKeyEquivalentAtIndex","insertItemWithTitle:action:keyEquivalent:atIndex:","forall t1 t3 . NSString t1 -> SEL -> NSString t3 -> Int -> IO (ID ())","AppKit.NSMenu") +("tokenFieldCellDisplayStringForRepresentedObject","tokenFieldCell:displayStringForRepresentedObject:","forall t1 t2 . NSTokenFieldCell t1 -> ID t2 -> IO (NSString ())","AppKit.NSTokenFieldCell") +("setReusesColumns","setReusesColumns:","Bool -> IO ()","AppKit.NSBrowser") +("checkSpaceForParts","checkSpaceForParts","IO ()","AppKit.NSScroller") +("preservesContentDuringLiveResize","preservesContentDuringLiveResize","IO Bool","AppKit.NSWindow") +("preservesContentDuringLiveResize","preservesContentDuringLiveResize","IO Bool","AppKit.NSView") +("scrollRectBy","scrollRect:by:","NSRect -> NSSize -> IO ()","AppKit.NSView") +("opaqueAncestor","opaqueAncestor","IO (NSView ())","AppKit.NSView") +("cellSize","cellSize","IO NSSize","AppKit.NSMatrix") +("cellSize","cellSize","IO NSSize","AppKit.NSTextAttachment") +("cellSize","cellSize","IO NSSize","AppKit.NSCell") +("adjustSubviews","adjustSubviews","IO ()","AppKit.NSSplitView") +("setVerticalRulerView","setVerticalRulerView:","forall t1 . NSRulerView t1 -> IO ()","AppKit.NSScrollView") +("readFileWrapper","readFileWrapper","IO (NSFileWrapper ())","AppKit.NSPasteboard") +("initWithUser","initWithUser:","forall t1 . NSString t1 -> IO Inited","Foundation.NSUserDefaults") +("outlineViewColumnDidResize","outlineViewColumnDidResize:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSOutlineView") +("animate","animate:","forall t1 . ID t1 -> IO ()","AppKit.NSProgressIndicator") +("setTextStorage","setTextStorage:","forall t1 . NSTextStorage t1 -> IO ()","AppKit.NSLayoutManager") +("validateMenuItem","validateMenuItem:","forall t1 . ID t1 -> IO Bool","AppKit.NSMenu") +("fileHandleForWriting","fileHandleForWriting","IO (NSFileHandle ())","Foundation.NSFileHandle") +("textViewDoubleClickedOnCellInRectAtIndex","textView:doubleClickedOnCell:inRect:atIndex:","forall t1 t2 . NSTextView t1 -> ID t2 -> NSRect -> CUInt -> IO ()","AppKit.NSTextView") +("textViewDoubleClickedOnCellInRect","textView:doubleClickedOnCell:inRect:","forall t1 t2 . NSTextView t1 -> ID t2 -> NSRect -> IO ()","AppKit.NSTextView") +("addTableColumn","addTableColumn:","forall t1 . NSTableColumn t1 -> IO ()","AppKit.NSTableView") +("sharedSystemTypesetter","sharedSystemTypesetter","IO (ID ())","AppKit.NSTypesetter") +("mouseDownFlags","mouseDownFlags","IO Int","AppKit.NSMatrix") +("mouseDownFlags","mouseDownFlags","IO Int","AppKit.NSCell") +("setFullScreen","setFullScreen","IO ()","AppKit.NSOpenGL") +("setStartSpecifier","setStartSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("stopMonitoring","stopMonitoring","IO ()","Foundation.NSNetServices") +("worksWhenModal","worksWhenModal","IO Bool","AppKit.NSWindow") +("windowDidUpdate","windowDidUpdate:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSWindow") +("setBlocksOtherRecognizers","setBlocksOtherRecognizers:","Bool -> IO ()","AppKit.NSSpeechRecognizer") +("parserFoundExternalEntityDeclarationWithNamePublicIDSystemID","parser:foundExternalEntityDeclarationWithName:publicID:systemID:","forall t1 t2 t3 t4 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> NSString t4 -> IO ()","Foundation.NSXMLParser") +("rotation","rotation","IO Float","AppKit.NSEvent") +("connection","connection","IO (NSConnection ())","Foundation.NSPortCoder") +("connection","connection","IO (NSConnection ())","Foundation.NSConnection") +("resumeExecutionWithResult","resumeExecutionWithResult:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptCommand") +("dictionaryWithObjectForKey","dictionaryWithObject:forKey:","forall t1 t2 . ID t1 -> ID t2 -> IO (ID ())","Foundation.NSDictionary") +("stringByResolvingSymlinksInPath","stringByResolvingSymlinksInPath","IO (NSString ())","Foundation.NSPathUtilities") +("initWithNameData","initWithName:data:","forall t1 t2 . NSString t1 -> NSData t2 -> IO Inited","Foundation.NSTimeZone") +("outlineViewShouldCollapseItem","outlineView:shouldCollapseItem:","forall t1 t2 . NSOutlineView t1 -> ID t2 -> IO Bool","AppKit.NSOutlineView") +("indexOfTabViewItemWithIdentifier","indexOfTabViewItemWithIdentifier:","forall t1 . ID t1 -> IO Int","AppKit.NSTabView") +("lineBreakBeforeIndexWithinRange","lineBreakBeforeIndex:withinRange:","CUInt -> NSRange -> IO CUInt","AppKit.NSAttributedString") +("encodeRectForKey","encodeRect:forKey:","forall t2 . NSRect -> NSString t2 -> IO ()","Foundation.NSKeyedArchiver") +("encodeConditionalObject","encodeConditionalObject:","forall t1 . ID t1 -> IO ()","Foundation.NSCoder") +("writeSelectionToPasteboardType","writeSelectionToPasteboard:type:","forall t1 t2 . NSPasteboard t1 -> NSString t2 -> IO Bool","AppKit.NSTextView") +("textUnfilteredPasteboardTypes","textUnfilteredPasteboardTypes","IO (NSArray ())","AppKit.NSAttributedString") +("downloadDidReceiveAuthenticationChallenge","download:didReceiveAuthenticationChallenge:","forall t1 t2 . NSURLDownload t1 -> NSURLAuthenticationChallenge t2 -> IO ()","Foundation.NSURLDownload") +("printPanel","printPanel","IO (NSPrintPanel ())","AppKit.NSPrintPanel") +("printPanel","printPanel","IO (NSPrintPanel ())","AppKit.NSPrintOperation") +("pointingDeviceSerialNumber","pointingDeviceSerialNumber","IO CUInt","AppKit.NSEvent") +("drawInRectFromRectOperationFraction","drawInRect:fromRect:operation:fraction:","NSRect -> NSRect -> NSCompositingOperation -> Float -> IO ()","AppKit.NSImage") +("setShowsHelp","setShowsHelp:","Bool -> IO ()","AppKit.NSAlert") +("credentialsForProtectionSpace","credentialsForProtectionSpace:","forall t1 . NSURLProtectionSpace t1 -> IO (NSDictionary ())","Foundation.NSURLCredentialStorage") +("orderFrontStandardAboutPanel","orderFrontStandardAboutPanel:","forall t1 . ID t1 -> IO ()","AppKit.NSApplication") +("insertTextClient","insertText:client:","forall t1 t2 . ID t1 -> ID t2 -> IO ()","AppKit.NSInputServer") +("isSymbolicLink","isSymbolicLink","IO Bool","AppKit.NSFileWrapper") +("documentForWindow","documentForWindow:","forall t1 . NSWindow t1 -> IO (ID ())","AppKit.NSDocumentController") +("openPanel","openPanel","IO (NSOpenPanel ())","AppKit.NSOpenPanel") +("setResolvesAliases","setResolvesAliases:","Bool -> IO ()","AppKit.NSOpenPanel") +("readableTypes","readableTypes","IO (NSArray ())","AppKit.NSDocument") +("defaultNameServerPortNumber","defaultNameServerPortNumber","IO CUShort","Foundation.NSPortNameServer") +("canCreateDirectories","canCreateDirectories","IO Bool","AppKit.NSSavePanel") +("titleWidth_","titleWidth:","NSSize -> IO Float","AppKit.NSFormCell") +("mouseDragged","mouseDragged:","forall t1 . NSEvent t1 -> IO ()","AppKit.NSResponder") +("documentForURL","documentForURL:","forall t1 . NSURL t1 -> IO (ID ())","AppKit.NSDocumentController") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLDTDNode") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLDTD") +("systemID","systemID","IO (NSString ())","Foundation.NSXMLParser") +("mainBundle","mainBundle","IO (NSBundle ())","Foundation.NSBundle") +("removeValueAtIndexFromPropertyWithKey","removeValueAtIndex:fromPropertyWithKey:","forall t2 . CUInt -> NSString t2 -> IO ()","Foundation.NSScriptKeyValueCoding") +("outlineViewWillDisplayOutlineCellForTableColumnItem","outlineView:willDisplayOutlineCell:forTableColumn:item:","forall t1 t2 t3 t4 . NSOutlineView t1 -> ID t2 -> NSTableColumn t3 -> ID t4 -> IO ()","AppKit.NSOutlineView") +("setContainerSize","setContainerSize:","NSSize -> IO ()","AppKit.NSTextContainer") +("usesFeedbackWindow","usesFeedbackWindow","IO Bool","AppKit.NSSpeechSynthesizer") +("layoutOptions","layoutOptions","IO CUInt","AppKit.NSGlyphGenerator") +("setLayoutAlgorithm","setLayoutAlgorithm:","NSTextTableLayoutAlgorithm -> IO ()","AppKit.NSTextTable") +("lockFocusOnRepresentation","lockFocusOnRepresentation:","forall t1 . NSImageRep t1 -> IO ()","AppKit.NSImage") +("tableView","tableView","IO (NSTableView ())","AppKit.NSTableHeaderView") +("tableView","tableView","IO (NSTableView ())","AppKit.NSTableColumn") +("openFileWithApplication","openFile:withApplication:","forall t1 t2 . NSString t1 -> NSString t2 -> IO Bool","AppKit.NSWorkspace") +("encodingScheme","encodingScheme","IO (NSString ())","AppKit.NSFont") +("doubleClickAtIndex","doubleClickAtIndex:","CUInt -> IO NSRange","AppKit.NSAttributedString") +("removeCharactersInRange","removeCharactersInRange:","NSRange -> IO ()","Foundation.NSCharacterSet") +("setFloatValue","setFloatValue:","Float -> IO ()","AppKit.NSControl") +("setFloatValue","setFloatValue:","Float -> IO ()","AppKit.NSCell") +("setInContext","setInContext:","forall t1 . NSGraphicsContext t1 -> IO ()","AppKit.NSFont") +("update","update","IO ()","AppKit.NSOpenGLView") +("update","update","IO ()","AppKit.NSMenuView") +("update","update","IO ()","AppKit.NSWindow") +("update","update","IO ()","AppKit.NSOpenGL") +("update","update","IO ()","AppKit.NSMenu") +("setPullsDown","setPullsDown:","Bool -> IO ()","AppKit.NSPopUpButtonCell") +("setPullsDown","setPullsDown:","Bool -> IO ()","AppKit.NSPopUpButton") +("setDefaultPlaceholderForMarkerWithBinding","setDefaultPlaceholder:forMarker:withBinding:","forall t1 t2 t3 . ID t1 -> ID t2 -> NSString t3 -> IO ()","AppKit.NSKeyValueBinding") +("fontDescriptorWithFace","fontDescriptorWithFace:","forall t1 . NSString t1 -> IO (NSFontDescriptor ())","AppKit.NSFontDescriptor") +("fontDescriptor","fontDescriptor","IO (NSFontDescriptor ())","AppKit.NSFont") +("setCanHide","setCanHide:","Bool -> IO ()","AppKit.NSWindow") +("removeAllToolTips","removeAllToolTips","IO ()","AppKit.NSView") +("setLineSpacing","setLineSpacing:","Float -> IO ()","AppKit.NSParagraphStyle") +("iccprofileData","ICCProfileData","IO (NSData ())","AppKit.NSColorSpace") +("useRunningCopyOfApplication","useRunningCopyOfApplication","IO ()","AppKit.NSApplication") +("defaultWritingDirectionForLanguage","defaultWritingDirectionForLanguage:","forall t1 . NSString t1 -> IO NSWritingDirection","AppKit.NSParagraphStyle") +("setIndentationMarkerFollowsCell","setIndentationMarkerFollowsCell:","Bool -> IO ()","AppKit.NSOutlineView") +("comboBoxCompletedString","comboBox:completedString:","forall t1 t2 . NSComboBox t1 -> NSString t2 -> IO (NSString ())","AppKit.NSComboBox") +("isSubviewCollapsed","isSubviewCollapsed:","forall t1 . NSView t1 -> IO Bool","AppKit.NSSplitView") +("availableFontFamilies","availableFontFamilies","IO (NSArray ())","AppKit.NSFontManager") +("accessibilityAttributeNames","accessibilityAttributeNames","IO (NSArray ())","AppKit.NSAccessibility") +("unscript","unscript:","forall t1 . ID t1 -> IO ()","AppKit.NSText") +("setAlertStyle","setAlertStyle:","NSAlertStyle -> IO ()","AppKit.NSAlert") +("verticalScroller","verticalScroller","IO (NSScroller ())","AppKit.NSScrollView") +("currentCursor","currentCursor","IO (NSCursor ())","AppKit.NSCursor") +("setVerticalPageScroll","setVerticalPageScroll:","Float -> IO ()","AppKit.NSScrollView") +("bitmapRepresentation","bitmapRepresentation","IO (NSData ())","Foundation.NSCharacterSet") +("markedRange","markedRange","IO NSRange","AppKit.NSInputManager") +("stringByPaddingToLengthWithStringStartingAtIndex","stringByPaddingToLength:withString:startingAtIndex:","forall t2 . CUInt -> NSString t2 -> CUInt -> IO (NSString ())","Foundation.NSString") +("localizedFailureReason","localizedFailureReason","IO (NSString ())","Foundation.NSError") +("keyForFileWrapper","keyForFileWrapper:","forall t1 . NSFileWrapper t1 -> IO (NSString ())","AppKit.NSFileWrapper") +("separatesColumns","separatesColumns","IO Bool","AppKit.NSBrowser") +("setSelectionIndexPath","setSelectionIndexPath:","forall t1 . NSIndexPath t1 -> IO Bool","AppKit.NSTreeController") +("decodeSizeForKey","decodeSizeForKey:","forall t1 . NSString t1 -> IO NSSize","Foundation.NSKeyedArchiver") +("windowShouldZoomToFrame","windowShouldZoom:toFrame:","forall t1 . NSWindow t1 -> NSRect -> IO Bool","AppKit.NSWindow") +("loadInForeground","loadInForeground","IO (NSData ())","Foundation.NSURLHandle") +("setObjectBeingTested","setObjectBeingTested:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptExecutionContext") +("drawWithFrameInView","drawWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSTextAttachment") +("drawWithFrameInView","drawWithFrame:inView:","forall t2 . NSRect -> NSView t2 -> IO ()","AppKit.NSCell") +("ascender","ascender","IO Float","AppKit.NSFont") +("deserializeAlignedBytesLengthAtCursor","deserializeAlignedBytesLengthAtCursor:","Ptr CUInt -> IO CUInt","Foundation.NSSerialization") +("stateImageOffset","stateImageOffset","IO Float","AppKit.NSMenuView") +("enableMultipleThreads","enableMultipleThreads","IO ()","Foundation.NSConnection") +("sound","sound","IO (NSSound ())","AppKit.NSButton") +("sound","sound","IO (NSSound ())","AppKit.NSButtonCell") +("dateWithTimeIntervalSinceNow","dateWithTimeIntervalSinceNow:","NSTimeInterval -> IO (ID ())","Foundation.NSDate") +("isLoaded","isLoaded","IO Bool","AppKit.NSBrowser") +("isLoaded","isLoaded","IO Bool","AppKit.NSBrowserCell") +("isLoaded","isLoaded","IO Bool","Foundation.NSBundle") +("windowFrameTextColor","windowFrameTextColor","IO (NSColor ())","AppKit.NSColor") +("prefersAllColumnUserResizing","prefersAllColumnUserResizing","IO Bool","AppKit.NSBrowser") +("writeEPSInsideRectToPasteboard","writeEPSInsideRect:toPasteboard:","forall t2 . NSRect -> NSPasteboard t2 -> IO ()","AppKit.NSView") +("setLocationWithAdvancementsForStartOfGlyphRange","setLocation:withAdvancements:forStartOfGlyphRange:","NSPoint -> Ptr Float -> NSRange -> IO ()","AppKit.NSTypesetter") +("loadFileWrapperRepresentationOfType","loadFileWrapperRepresentation:ofType:","forall t1 t2 . NSFileWrapper t1 -> NSString t2 -> IO Bool","AppKit.NSDocument") +("encodePointForKey","encodePoint:forKey:","forall t2 . NSPoint -> NSString t2 -> IO ()","Foundation.NSKeyedArchiver") +("floatForKey","floatForKey:","forall t1 . NSString t1 -> IO Float","Foundation.NSUserDefaults") +("performSelectorWithObjectAfterDelayInModes","performSelector:withObject:afterDelay:inModes:","forall t2 t4 . SEL -> ID t2 -> NSTimeInterval -> NSArray t4 -> IO ()","Foundation.NSRunLoop") +("netServiceWillPublish","netServiceWillPublish:","forall t1 . NSNetService t1 -> IO ()","Foundation.NSNetServices") +("windowWillClose","windowWillClose:","forall t1 . NSNotification t1 -> IO ()","AppKit.NSWindow") +("initWithLocaleIdentifier","initWithLocaleIdentifier:","forall t1 . NSString t1 -> IO Inited","Foundation.NSLocale") +("splitViewCanCollapseSubview","splitView:canCollapseSubview:","forall t1 t2 . NSSplitView t1 -> NSView t2 -> IO Bool","AppKit.NSSplitView") +("didChangeValueForKey","didChangeValueForKey:","forall t1 . NSString t1 -> IO ()","Foundation.NSKeyValueObserving") +("columnResizingType","columnResizingType","IO NSBrowserColumnResizingType","AppKit.NSBrowser") +("contentRect","contentRect","IO NSRect","AppKit.NSTabView") +("isFlushWindowDisabled","isFlushWindowDisabled","IO Bool","AppKit.NSWindow") +("convertFontToFace","convertFont:toFace:","forall t1 t2 . NSFont t1 -> NSString t2 -> IO (NSFont ())","AppKit.NSFontManager") +("getBytesLength","getBytes:length:","Ptr () -> CUInt -> IO ()","Foundation.NSData") +("selectionShouldChangeInTableView","selectionShouldChangeInTableView:","forall t1 . NSTableView t1 -> IO Bool","AppKit.NSTableView") +("collectionNames","collectionNames","IO (NSArray ())","AppKit.NSFontManager") +("laterDate","laterDate:","forall t1 . NSDate t1 -> IO (NSDate ())","Foundation.NSDate") +("parserFoundElementDeclarationWithNameModel","parser:foundElementDeclarationWithName:model:","forall t1 t2 t3 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> IO ()","Foundation.NSXMLParser") +("allHeaderFields","allHeaderFields","IO (NSDictionary ())","Foundation.NSURLResponse") +("fontDescriptorWithMatrix","fontDescriptorWithMatrix:","forall t1 . NSAffineTransform t1 -> IO (NSFontDescriptor ())","AppKit.NSFontDescriptor") +("indexOfItemAtPoint","indexOfItemAtPoint:","NSPoint -> IO Int","AppKit.NSMenuView") +("textView","textView","IO (NSTextView ())","AppKit.NSTextContainer") +("insertDescriptorAtIndex","insertDescriptor:atIndex:","forall t1 . NSAppleEventDescriptor t1 -> CLong -> IO ()","Foundation.NSAppleEventDescriptor") +("initWithWindowNibPathOwner","initWithWindowNibPath:owner:","forall t1 t2 . NSString t1 -> ID t2 -> IO Inited","AppKit.NSWindowController") +("addSubview","addSubview:","forall t1 . NSView t1 -> IO ()","AppKit.NSView") +("isEntryAcceptable","isEntryAcceptable:","forall t1 . NSString t1 -> IO Bool","AppKit.NSCell") +("rectValue","rectValue","IO NSRect","Foundation.NSGeometry") +("deltaX","deltaX","IO Float","AppKit.NSEvent") +("defaultManager","defaultManager","IO (NSFileManager ())","Foundation.NSFileManager") +("deltaY","deltaY","IO Float","AppKit.NSEvent") +("setLineWidth","setLineWidth:","Float -> IO ()","AppKit.NSBezierPath") +("performSelectorWithObjectAfterDelay","performSelector:withObject:afterDelay:","forall t2 . SEL -> ID t2 -> NSTimeInterval -> IO ()","Foundation.NSRunLoop") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTextField") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSMatrix") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSDatePicker") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTextFieldCell") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSText") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSTabView") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSScrollView") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSDatePickerCell") +("drawsBackground","drawsBackground","IO Bool","AppKit.NSClipView") +("needsDisplay","needsDisplay","IO Bool","AppKit.NSMenuItemCell") +("needsDisplay","needsDisplay","IO Bool","AppKit.NSView") +("applicationShouldHandleReopenHasVisibleWindows","applicationShouldHandleReopen:hasVisibleWindows:","forall t1 . NSApplication t1 -> Bool -> IO Bool","AppKit.NSApplication") +("deltaZ","deltaZ","IO Float","AppKit.NSEvent") +("initWithRequestDelegate","initWithRequest:delegate:","forall t1 t2 . NSURLRequest t1 -> ID t2 -> IO Inited","Foundation.NSURLDownload") +("initWithRequestDelegate","initWithRequest:delegate:","forall t1 t2 . NSURLRequest t1 -> ID t2 -> IO Inited","Foundation.NSURLConnection") +("increaseLengthBy","increaseLengthBy:","CUInt -> IO ()","Foundation.NSData") +("fileSystemChanged","fileSystemChanged","IO Bool","AppKit.NSWorkspace") +("imageDidNotDrawInRect","imageDidNotDraw:inRect:","forall t1 . ID t1 -> NSRect -> IO (NSImage ())","AppKit.NSImage") +("setCurrentDirectoryPath","setCurrentDirectoryPath:","forall t1 . NSString t1 -> IO ()","Foundation.NSTask") +("heightTracksTextView","heightTracksTextView","IO Bool","AppKit.NSTextContainer") +("rotateByDegrees","rotateByDegrees:","Float -> IO ()","Foundation.NSAffineTransform") +("selectionAffinity","selectionAffinity","IO NSSelectionAffinity","AppKit.NSTextView") +("initWithTitleActionKeyEquivalent","initWithTitle:action:keyEquivalent:","forall t1 t3 . NSString t1 -> SEL -> NSString t3 -> IO Inited","AppKit.NSMenuItem") +("createContext","createContext","IO (NSGraphicsContext ())","AppKit.NSPrintOperation") +("buttonNumber","buttonNumber","IO Int","AppKit.NSEvent") +("urls","URLs","IO (NSArray ())","AppKit.NSOpenPanel") +("columnWithIdentifier","columnWithIdentifier:","forall t1 . ID t1 -> IO Int","AppKit.NSTableView") +("markerLocation","markerLocation","IO Float","AppKit.NSRulerMarker") +("urlhandleResourceDidFailLoadingWithReason","URLHandle:resourceDidFailLoadingWithReason:","forall t1 t2 . NSURLHandle t1 -> NSString t2 -> IO ()","Foundation.NSURLHandle") +("initWithWindow","initWithWindow:","forall t1 . NSWindow t1 -> IO Inited","AppKit.NSWindowController") +("getValuesForParameter","getValues:forParameter:","Ptr CLong -> NSOpenGLContextParameter -> IO ()","AppKit.NSOpenGL") +("horizontalScroller","horizontalScroller","IO (NSScroller ())","AppKit.NSScrollView") +("defaultPrinter","defaultPrinter","IO (NSPrinter ())","AppKit.NSPrintInfo") +("numberOfComponents","numberOfComponents","IO Int","AppKit.NSColor") +("spellingPanel","spellingPanel","IO (NSPanel ())","AppKit.NSSpellChecker") +("setEnvironment","setEnvironment:","forall t1 . NSDictionary t1 -> IO ()","Foundation.NSTask") +("moveLeftAndModifySelection","moveLeftAndModifySelection:","forall t1 . ID t1 -> IO ()","AppKit.NSResponder") +("setMinute","setMinute:","Int -> IO ()","Foundation.NSCalendar") +("pickedOrientation","pickedOrientation:","forall t1 . ID t1 -> IO ()","AppKit.NSPageLayout") +("saveGraphicsState","saveGraphicsState","IO ()","AppKit.NSGraphicsContext") +("netServiceDidResolveAddress","netServiceDidResolveAddress:","forall t1 . NSNetService t1 -> IO ()","Foundation.NSNetServices") +("compareOptionsRangeLocale","compare:options:range:locale:","forall t1 t4 . NSString t1 -> CUInt -> NSRange -> NSDictionary t4 -> IO NSComparisonResult","Foundation.NSString") +("setArgumentAtIndex","setArgument:atIndex:","Ptr () -> Int -> IO ()","Foundation.NSInvocation") +("disableUpdates","disableUpdates","IO ()","Foundation.NSMetadata") +("preferredPasteboardTypeFromArrayRestrictedToTypesFromArray","preferredPasteboardTypeFromArray:restrictedToTypesFromArray:","forall t1 t2 . NSArray t1 -> NSArray t2 -> IO (NSString ())","AppKit.NSTextView") +("minValue","minValue","IO Double","AppKit.NSStepper") +("minValue","minValue","IO Double","AppKit.NSSlider") +("minValue","minValue","IO Double","AppKit.NSLevelIndicator") +("minValue","minValue","IO Double","AppKit.NSStepperCell") +("minValue","minValue","IO Double","AppKit.NSSliderCell") +("minValue","minValue","IO Double","AppKit.NSProgressIndicator") +("minValue","minValue","IO Double","AppKit.NSLevelIndicatorCell") +("extendPowerOffBy","extendPowerOffBy:","Int -> IO Int","AppKit.NSWorkspace") +("thickness","thickness","IO Float","AppKit.NSStatusBar") +("canSelectPrevious","canSelectPrevious","IO Bool","AppKit.NSArrayController") +("numberOfGlyphs","numberOfGlyphs","IO CUInt","AppKit.NSLayoutManager") +("numberOfGlyphs","numberOfGlyphs","IO CUInt","AppKit.NSFont") +("abbreviationDictionary","abbreviationDictionary","IO (NSDictionary ())","Foundation.NSTimeZone") +("netServiceDidNotResolve","netService:didNotResolve:","forall t1 t2 . NSNetService t1 -> NSDictionary t2 -> IO ()","Foundation.NSNetServices") +("performKeyEquivalent","performKeyEquivalent:","forall t1 . NSEvent t1 -> IO Bool","AppKit.NSResponder") +("performKeyEquivalent","performKeyEquivalent:","forall t1 . NSEvent t1 -> IO Bool","AppKit.NSMenu") +("setNameFieldLabel","setNameFieldLabel:","forall t1 . NSString t1 -> IO ()","AppKit.NSSavePanel") +("tabStopType","tabStopType","IO NSTextTabType","AppKit.NSParagraphStyle") +("deserializeIntsCountAtCursor","deserializeInts:count:atCursor:","Ptr Int -> CUInt -> Ptr CUInt -> IO ()","Foundation.NSSerialization") +("scanLocation","scanLocation","IO CUInt","Foundation.NSScanner") +("removeObjectsForKeys","removeObjectsForKeys:","forall t1 . NSArray t1 -> IO ()","Foundation.NSDictionary") +("canBeDisabled","canBeDisabled","IO Bool","AppKit.NSInputServer") +("weekday","weekday","IO Int","Foundation.NSCalendar") +("setAutorepeat","setAutorepeat:","Bool -> IO ()","AppKit.NSStepper") +("setAutorepeat","setAutorepeat:","Bool -> IO ()","AppKit.NSStepperCell") +("tabViewType","tabViewType","IO NSTabViewType","AppKit.NSTabView") +("backingType","backingType","IO NSBackingStoreType","AppKit.NSWindow") +("nextEventMatchingMaskUntilDateInModeDequeue","nextEventMatchingMask:untilDate:inMode:dequeue:","forall t2 t3 . CUInt -> NSDate t2 -> NSString t3 -> Bool -> IO (NSEvent ())","AppKit.NSWindow") +("nextEventMatchingMaskUntilDateInModeDequeue","nextEventMatchingMask:untilDate:inMode:dequeue:","forall t2 t3 . CUInt -> NSDate t2 -> NSString t3 -> Bool -> IO (NSEvent ())","AppKit.NSApplication") +("defaultFocusRingType","defaultFocusRingType","IO NSFocusRingType","AppKit.NSView") +("defaultFocusRingType","defaultFocusRingType","IO NSFocusRingType","AppKit.NSCell") +("tokenFieldCellStyleForRepresentedObject","tokenFieldCell:styleForRepresentedObject:","forall t1 t2 . NSTokenFieldCell t1 -> ID t2 -> IO NSTokenStyle","AppKit.NSTokenFieldCell") +("setParagraphSpacingBefore","setParagraphSpacingBefore:","Float -> IO ()","AppKit.NSParagraphStyle") +("indexOfItemWithSubmenu","indexOfItemWithSubmenu:","forall t1 . NSMenu t1 -> IO Int","AppKit.NSMenu") +("setBaseWritingDirectionRange","setBaseWritingDirection:range:","NSWritingDirection -> NSRange -> IO ()","AppKit.NSTextView") +("setBaseWritingDirectionRange","setBaseWritingDirection:range:","NSWritingDirection -> NSRange -> IO ()","AppKit.NSAttributedString") +("initWithPickerMaskColorPanel","initWithPickerMask:colorPanel:","forall t2 . Int -> NSColorPanel t2 -> IO Inited","AppKit.NSColorPicking") +("locationForGlyphAtIndex","locationForGlyphAtIndex:","CUInt -> IO NSPoint","AppKit.NSLayoutManager") +("indexLessThanIndex","indexLessThanIndex:","CUInt -> IO CUInt","Foundation.NSIndexSet") +("shadowBlurRadius","shadowBlurRadius","IO Float","AppKit.NSShadow") +("interpretKeyEvents","interpretKeyEvents:","forall t1 . NSArray t1 -> IO ()","AppKit.NSResponder") +("lockFocus","lockFocus","IO ()","AppKit.NSView") +("lockFocus","lockFocus","IO ()","AppKit.NSImage") +("setDefaultNameServerPortNumber","setDefaultNameServerPortNumber:","CUShort -> IO ()","Foundation.NSPortNameServer") +("descriptionWithLocaleIndent","descriptionWithLocale:indent:","forall t1 . NSDictionary t1 -> CUInt -> IO (NSString ())","Foundation.NSDictionary") +("descriptionWithLocaleIndent","descriptionWithLocale:indent:","forall t1 . NSDictionary t1 -> CUInt -> IO (NSString ())","Foundation.NSArray") +("sortIndicatorRectForBounds","sortIndicatorRectForBounds:","NSRect -> IO NSRect","AppKit.NSTableHeaderCell") +("initialFirstResponder","initialFirstResponder","IO (NSView ())","AppKit.NSWindow") +("initialFirstResponder","initialFirstResponder","IO (NSView ())","AppKit.NSTabViewItem") +("decimalNumberByMultiplyingByWithBehavior","decimalNumberByMultiplyingBy:withBehavior:","forall t1 t2 . NSDecimalNumber t1 -> ID t2 -> IO (NSDecimalNumber ())","Foundation.NSDecimalNumber") +("xmlstring","XMLString","IO (NSString ())","Foundation.NSXMLNode") +("availableVoices","availableVoices","IO (NSArray ())","AppKit.NSSpeechSynthesizer") +("setPaperName","setPaperName:","forall t1 . NSString t1 -> IO ()","AppKit.NSPrintInfo") +("rootObject","rootObject","IO (ID ())","Foundation.NSConnection") +("browserNumberOfRowsInColumn","browser:numberOfRowsInColumn:","forall t1 . NSBrowser t1 -> Int -> IO Int","AppKit.NSBrowser") +("isAutodisplay","isAutodisplay","IO Bool","AppKit.NSWindow") +("parserValidationErrorOccurred","parser:validationErrorOccurred:","forall t1 t2 . NSXMLParser t1 -> NSError t2 -> IO ()","Foundation.NSXMLParser") +("stringForKey","stringForKey:","forall t1 . NSString t1 -> IO (NSString ())","Foundation.NSUserDefaults") +("contentViewMargins","contentViewMargins","IO NSSize","AppKit.NSBox") +("autosavedContentsFileURL","autosavedContentsFileURL","IO (NSURL ())","AppKit.NSDocument") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSCalendarDate") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSValue") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSSet") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSDictionary") +("descriptionWithLocale","descriptionWithLocale:","forall t1 . NSDictionary t1 -> IO (NSString ())","Foundation.NSArray") +("commandName","commandName","IO (NSString ())","Foundation.NSScriptCommandDescription") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSComboBox") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSTableView") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSMatrix") +("intercellSpacing","intercellSpacing","IO NSSize","AppKit.NSComboBoxCell") +("documentView","documentView","IO (ID ())","AppKit.NSScrollView") +("documentView","documentView","IO (ID ())","AppKit.NSClipView") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSWindow") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSScreen") +("deviceDescription","deviceDescription","IO (NSDictionary ())","AppKit.NSPrinter") +("serializePropertyListIntoData","serializePropertyList:intoData:","forall t1 t2 . ID t1 -> NSMutableData t2 -> IO ()","Foundation.NSSerialization") +("firstResponder","firstResponder","IO (NSResponder ())","AppKit.NSWindow") +("tableViewAcceptDropRowDropOperation","tableView:acceptDrop:row:dropOperation:","forall t1 t2 . NSTableView t1 -> ID t2 -> Int -> NSTableViewDropOperation -> IO Bool","AppKit.NSTableView") +("setCalendar","setCalendar:","forall t1 . NSCalendar t1 -> IO ()","AppKit.NSDatePicker") +("setCalendar","setCalendar:","forall t1 . NSCalendar t1 -> IO ()","AppKit.NSDatePickerCell") +("knobProportion","knobProportion","IO Float","AppKit.NSScroller") +("setSegmentCount","setSegmentCount:","Int -> IO ()","AppKit.NSSegmentedControl") +("setSegmentCount","setSegmentCount:","Int -> IO ()","AppKit.NSSegmentedCell") +("setVerticalScroller","setVerticalScroller:","forall t1 . NSScroller t1 -> IO ()","AppKit.NSScrollView") +("setStandalone","setStandalone:","Bool -> IO ()","Foundation.NSXMLDocument") +("parserResolveExternalEntityNameSystemID","parser:resolveExternalEntityName:systemID:","forall t1 t2 t3 . NSXMLParser t1 -> NSString t2 -> NSString t3 -> IO (NSData ())","Foundation.NSXMLParser") +("insertItemWithTitleAtIndex","insertItemWithTitle:atIndex:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSPopUpButtonCell") +("insertItemWithTitleAtIndex","insertItemWithTitle:atIndex:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSPopUpButton") +("setDuration","setDuration:","NSTimeInterval -> IO ()","AppKit.NSAnimation") +("completionsForPartialWordRangeIndexOfSelectedItem","completionsForPartialWordRange:indexOfSelectedItem:","NSRange -> Ptr Int -> IO (NSArray ())","AppKit.NSTextView") +("setAllowsTickMarkValuesOnly","setAllowsTickMarkValuesOnly:","Bool -> IO ()","AppKit.NSSlider") +("setAllowsTickMarkValuesOnly","setAllowsTickMarkValuesOnly:","Bool -> IO ()","AppKit.NSSliderCell") +("defaultVoice","defaultVoice","IO (NSString ())","AppKit.NSSpeechSynthesizer") +("archiverWillEncodeObject","archiver:willEncodeObject:","forall t1 t2 . NSKeyedArchiver t1 -> ID t2 -> IO (ID ())","Foundation.NSKeyedArchiver") +("setMenuBarVisible","setMenuBarVisible:","Bool -> IO ()","AppKit.NSMenu") +("moveToPoint","moveToPoint:","NSPoint -> IO ()","AppKit.NSBezierPath") +("txtrecordData","TXTRecordData","IO (NSData ())","Foundation.NSNetServices") +("setSeparatesColumns","setSeparatesColumns:","Bool -> IO ()","AppKit.NSBrowser") +("deleteForward","deleteForward:","forall t1 . ID t1 -> IO ()","AppKit.NSResponder") +("inputStreamWithFileAtPath","inputStreamWithFileAtPath:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSStream") +("valueWithRect","valueWithRect:","NSRect -> IO (NSValue ())","Foundation.NSGeometry") +("selectRowInColumn","selectRow:inColumn:","Int -> Int -> IO ()","AppKit.NSBrowser") +("gotoEnd","gotoEnd:","forall t1 . ID t1 -> IO ()","AppKit.NSMovieView") +("compare","compare:","forall t1 . ID t1 -> IO NSComparisonResult","AppKit.NSCell") +("compare","compare:","forall t1 . NSNumber t1 -> IO NSComparisonResult","Foundation.NSValue") +("compare","compare:","forall t1 . NSString t1 -> IO NSComparisonResult","Foundation.NSString") +("compare","compare:","forall t1 . NSIndexPath t1 -> IO NSComparisonResult","Foundation.NSIndexPath") +("compare","compare:","forall t1 . NSDate t1 -> IO NSComparisonResult","Foundation.NSDate") +("scrollColumnToVisible","scrollColumnToVisible:","Int -> IO ()","AppKit.NSTableView") +("scrollColumnToVisible","scrollColumnToVisible:","Int -> IO ()","AppKit.NSBrowser") +("invalidateCursorRectsForView","invalidateCursorRectsForView:","forall t1 . NSView t1 -> IO ()","AppKit.NSWindow") +("tabStops","tabStops","IO (NSArray ())","AppKit.NSParagraphStyle") +("setSharedURLCache","setSharedURLCache:","forall t1 . NSURLCache t1 -> IO ()","Foundation.NSURLCache") +("dataWithBytesNoCopyLengthFreeWhenDone","dataWithBytesNoCopy:length:freeWhenDone:","Ptr () -> CUInt -> Bool -> IO (ID ())","Foundation.NSData") +("removeWindowsItem","removeWindowsItem:","forall t1 . NSWindow t1 -> IO ()","AppKit.NSApplication") +("printerFont","printerFont","IO (NSFont ())","AppKit.NSFont") +("addItemsWithObjectValues","addItemsWithObjectValues:","forall t1 . NSArray t1 -> IO ()","AppKit.NSComboBox") +("addItemsWithObjectValues","addItemsWithObjectValues:","forall t1 . NSArray t1 -> IO ()","AppKit.NSComboBoxCell") +("defaultLineHeightForFont","defaultLineHeightForFont","IO Float","AppKit.NSFont") +("setBaseSpecifier","setBaseSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("baseSpecifier","baseSpecifier","IO (NSScriptObjectSpecifier ())","Foundation.NSScriptObjectSpecifiers") +("insertObjectAtIndex","insertObject:atIndex:","forall t1 . ID t1 -> CUInt -> IO ()","Foundation.NSArray") +("numberWithLong","numberWithLong:","CLong -> IO (NSNumber ())","Foundation.NSValue") +("addItemWithObjectValue","addItemWithObjectValue:","forall t1 . ID t1 -> IO ()","AppKit.NSComboBox") +("addItemWithObjectValue","addItemWithObjectValue:","forall t1 . ID t1 -> IO ()","AppKit.NSComboBoxCell") +("secondsFromGMT","secondsFromGMT","IO Int","Foundation.NSTimeZone") +("dragImageForRowsEventDragImageOffset","dragImageForRows:event:dragImageOffset:","forall t1 t2 . NSArray t1 -> NSEvent t2 -> NSPointPointer -> IO (NSImage ())","AppKit.NSTableView") +("titleOfColumn","titleOfColumn:","Int -> IO (NSString ())","AppKit.NSBrowser") +("setTitleOfColumn","setTitle:ofColumn:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSBrowser") +("lineScroll","lineScroll","IO Float","AppKit.NSScrollView") +("scriptingIsLessThanOrEqualTo","scriptingIsLessThanOrEqualTo:","forall t1 . ID t1 -> IO Bool","Foundation.NSScriptWhoseTests") +("setChildSpecifier","setChildSpecifier:","forall t1 . NSScriptObjectSpecifier t1 -> IO ()","Foundation.NSScriptObjectSpecifiers") +("initWithScrollViewOrientation","initWithScrollView:orientation:","forall t1 . NSScrollView t1 -> NSRulerOrientation -> IO Inited","AppKit.NSRulerView") +("drawWithFrameInViewCharacterIndexLayoutManager","drawWithFrame:inView:characterIndex:layoutManager:","forall t2 t4 . NSRect -> NSView t2 -> CUInt -> NSLayoutManager t4 -> IO ()","AppKit.NSTextAttachment") +("popUpContextMenuWithEventForViewWithFont","popUpContextMenu:withEvent:forView:withFont:","forall t1 t2 t3 t4 . NSMenu t1 -> NSEvent t2 -> NSView t3 -> NSFont t4 -> IO ()","AppKit.NSMenu") +("sharedDocumentController","sharedDocumentController","IO (ID ())","AppKit.NSDocumentController") +("lastIndex","lastIndex","IO CUInt","Foundation.NSIndexSet") +("timeIntervalSince1970","timeIntervalSince1970","IO NSTimeInterval","Foundation.NSDate") +("focusStack","focusStack","IO (Ptr ())","AppKit.NSGraphicsContext") +("modifyFontViaPanel","modifyFontViaPanel:","forall t1 . ID t1 -> IO ()","AppKit.NSFontManager") +("removePortForName","removePortForName:","forall t1 . NSString t1 -> IO Bool","Foundation.NSPortNameServer") +("cancelButtonCell","cancelButtonCell","IO (NSButtonCell ())","AppKit.NSSearchFieldCell") +("takeFloatValueFrom","takeFloatValueFrom:","forall t1 . ID t1 -> IO ()","AppKit.NSControl") +("takeFloatValueFrom","takeFloatValueFrom:","forall t1 . ID t1 -> IO ()","AppKit.NSCell") +("drawAtPointWithAttributes","drawAtPoint:withAttributes:","forall t2 . NSPoint -> NSDictionary t2 -> IO ()","AppKit.NSStringDrawing") +("ignoreWordInSpellDocumentWithTag","ignoreWord:inSpellDocumentWithTag:","forall t1 . NSString t1 -> Int -> IO ()","AppKit.NSSpellChecker") +("setCalendarFormat","setCalendarFormat:","forall t1 . NSString t1 -> IO ()","Foundation.NSCalendarDate") +("setSmartInsertDeleteEnabled","setSmartInsertDeleteEnabled:","Bool -> IO ()","AppKit.NSTextView") +("defaultTypesetterBehavior","defaultTypesetterBehavior","IO NSTypesetterBehavior","AppKit.NSTypesetter") +("printerTypes","printerTypes","IO (NSArray ())","AppKit.NSPrinter") +("initFileURLWithPath","initFileURLWithPath:","forall t1 . NSString t1 -> IO Inited","Foundation.NSURL") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSPopUpButtonCell") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSPopUpButton") +("itemWithTitle","itemWithTitle:","forall t1 . NSString t1 -> IO (ID ())","AppKit.NSMenu") +("isDataRetained","isDataRetained","IO Bool","AppKit.NSImage") +("parserParseErrorOccurred","parser:parseErrorOccurred:","forall t1 t2 . NSXMLParser t1 -> NSError t2 -> IO ()","Foundation.NSXMLParser") +("headerCell","headerCell","IO (ID ())","AppKit.NSTableColumn") +("setDrawsCellBackground","setDrawsCellBackground:","Bool -> IO ()","AppKit.NSMatrix") +("setOrientation","setOrientation:","NSRulerOrientation -> IO ()","AppKit.NSRulerView") +("setOrientation","setOrientation:","NSPrintingOrientation -> IO ()","AppKit.NSPrintInfo") +("allowsUserCustomization","allowsUserCustomization","IO Bool","AppKit.NSToolbar") +("createTextureFromViewInternalFormat","createTexture:fromView:internalFormat:","forall t2 . CULong -> NSView t2 -> CULong -> IO ()","AppKit.NSOpenGL") +("locationOfPrintRect","locationOfPrintRect:","NSRect -> IO NSPoint","AppKit.NSView") +("flatness","flatness","IO Float","AppKit.NSBezierPath") +("titleColor","titleColor","IO (NSColor ())","AppKit.NSSlider") +("titleColor","titleColor","IO (NSColor ())","AppKit.NSSliderCell") +("urlsFromRunningOpenPanel","URLsFromRunningOpenPanel","IO (NSArray ())","AppKit.NSDocumentController") +("setDirectParameter","setDirectParameter:","forall t1 . ID t1 -> IO ()","Foundation.NSScriptCommand") +("setAutohidesScrollers","setAutohidesScrollers:","Bool -> IO ()","AppKit.NSScrollView") +("lockFocusIfCanDraw","lockFocusIfCanDraw","IO Bool","AppKit.NSView") +("writeToFileAtomicallyUpdateFilenames","writeToFile:atomically:updateFilenames:","forall t1 . NSString t1 -> Bool -> Bool -> IO Bool","AppKit.NSFileWrapper") +("reloadColumn","reloadColumn:","Int -> IO ()","AppKit.NSBrowser") +("initWithTableStartingRowRowSpanStartingColumnColumnSpan","initWithTable:startingRow:rowSpan:startingColumn:columnSpan:","forall t1 . NSTextTable t1 -> Int -> Int -> Int -> Int -> IO Inited","AppKit.NSTextTable") +("shouldCreateUI","shouldCreateUI","IO Bool","AppKit.NSDocumentController") +("rightExpression","rightExpression","IO (NSExpression ())","Foundation.NSComparisonPredicate") +("dayOfCommonEra","dayOfCommonEra","IO Int","Foundation.NSCalendarDate") +("terminationStatus","terminationStatus","IO Int","Foundation.NSTask") +("refusesFirstResponder","refusesFirstResponder","IO Bool","AppKit.NSControl") +("refusesFirstResponder","refusesFirstResponder","IO Bool","AppKit.NSCell") +("sizeWithAttributes","sizeWithAttributes:","forall t1 . NSDictionary t1 -> IO NSSize","AppKit.NSStringDrawing") +("fileURLWithPath","fileURLWithPath:","forall t1 . NSString t1 -> IO (ID ())","Foundation.NSURL") +("caseInsensitiveCompare","caseInsensitiveCompare:","forall t1 . NSString t1 -> IO NSComparisonResult","Foundation.NSString") +("firstVisibleColumn","firstVisibleColumn","IO Int","AppKit.NSBrowser") +("setNeedsDisplayInRect","setNeedsDisplayInRect:","NSRect -> IO ()","AppKit.NSView") +("toggleBaseWritingDirection","toggleBaseWritingDirection:","forall t1 . ID t1 -> IO ()","AppKit.NSTextView") +("setMenuFormRepresentation","setMenuFormRepresentation:","forall t1 . NSMenuItem t1 -> IO ()","AppKit.NSToolbarItem") +("textViewForBeginningOfSelection","textViewForBeginningOfSelection","IO (NSTextView ())","AppKit.NSLayoutManager") +("contentWidth","contentWidth","IO Float","AppKit.NSTextTable") +("generateGlyphsForGlyphStorageDesiredNumberOfCharactersGlyphIndexCharacterIndex","generateGlyphsForGlyphStorage:desiredNumberOfCharacters:glyphIndex:characterIndex:","forall t1 . ID t1 -> CUInt -> Ptr CUInt -> Ptr CUInt -> IO ()","AppKit.NSGlyphGenerator") +("relativeString","relativeString","IO (NSString ())","Foundation.NSURL") +("dictionaryWithDictionary","dictionaryWithDictionary:","forall t1 . NSDictionary t1 -> IO (ID ())","Foundation.NSDictionary") +("scriptingProperties","scriptingProperties","IO (NSDictionary ())","Foundation.NSObjectScripting") +("deselectRow","deselectRow:","Int -> IO ()","AppKit.NSTableView") +("setHasShadow","setHasShadow:","Bool -> IO ()","AppKit.NSWindow") +("arrayByAddingObjectsFromArray","arrayByAddingObjectsFromArray:","forall t1 . NSArray t1 -> IO (NSArray ())","Foundation.NSArray") +("imageAnd... [truncated message content] |
From: <cod...@go...> - 2009-08-11 20:07:34
|
Revision: 392 Author: wol...@gm... Date: Tue Aug 11 13:06:49 2009 Log: make HOCWrap compile again http://code.google.com/p/hoc/source/detail?r=392 Modified: /trunk/hoc/Tools/HOCWrap.hs ======================================= --- /trunk/hoc/Tools/HOCWrap.hs Mon Sep 29 13:12:09 2008 +++ /trunk/hoc/Tools/HOCWrap.hs Tue Aug 11 13:06:49 2009 @@ -3,7 +3,7 @@ import Prelude hiding ( init ) import qualified Prelude -import Control.Exception ( handle, throw, handleJust, userErrors ) +import Control.Exception ( bracketOnError ) import Control.Monad ( when ) import Data.List ( isSuffixOf ) import System.Console.GetOpt @@ -60,7 +60,7 @@ ] -main = handleJust userErrors (\err -> putStrLn err) $ do +main = do prog <- getProgName args <- getArgs @@ -113,42 +113,41 @@ let executableInApp = take (length appName - length ".app") appName - fm # createDirectoryAtPathAttributes nsAppName nil - >>= failOnFalse "Couldn't create .app." - - handle (\ex -> do - fm # removeFileAtPathHandler (toNSString appName) nil - throw ex - ) $ do - fm # copyPathToPathHandler (toNSString contents) - {-toPath:-} (toNSString $ appName ++ "/Contents") - {-handler:-} nil - >>= failOnFalse "Couldn't copy Contents folder." - - let nsMacOSFolder = toNSString (appName ++ "/Contents/MacOS") - - exists <- fm # fileExistsAtPath nsMacOSFolder - when (not exists) $ - fm # createDirectoryAtPathAttributes nsMacOSFolder nil - >>= failOnFalse "Couldn't create Contents/MacOS" - - let copyMethod | justLink = linkPathToPathHandler - | otherwise = copyPathToPathHandler - - fm # copyMethod (toNSString executable) - (toNSString $ appName ++ "/Contents/MacOS/" - ++ executableInApp) - nil - >>= failOnFalse "Couldn't copy executable." - - let nsPListName = toNSString $ appName ++ "/Contents/Info.plist" - - infoPList <- _NSMutableDictionary # alloc - >>= initWithContentsOfFile nsPListName - infoPList # setObjectForKey (toNSString executableInApp) - (toNSString "CFBundleExecutable") - infoPList # writeToFileAtomically nsPListName False - >>= failOnFalse "Couldn't write plist." + + bracketOnError + (fm # createDirectoryAtPathAttributes nsAppName nil + >>= failOnFalse "Couldn't create .app.") + (\_ -> fm # removeFileAtPathHandler nsAppName nil >> return ()) + $ \_ -> do + fm # copyPathToPathHandler (toNSString contents) + {-toPath:-} (toNSString $ appName ++ "/Contents") + {-handler:-} nil + >>= failOnFalse "Couldn't copy Contents folder." + + let nsMacOSFolder = toNSString (appName ++ "/Contents/MacOS") + + exists <- fm # fileExistsAtPath nsMacOSFolder + when (not exists) $ + fm # createDirectoryAtPathAttributes nsMacOSFolder nil + >>= failOnFalse "Couldn't create Contents/MacOS" + + let copyMethod | justLink = linkPathToPathHandler + | otherwise = copyPathToPathHandler + + fm # copyMethod (toNSString executable) + (toNSString $ appName ++ "/Contents/MacOS/" + ++ executableInApp) + nil + >>= failOnFalse "Couldn't copy executable." + + let nsPListName = toNSString $ appName ++ "/Contents/Info.plist" + + infoPList <- _NSMutableDictionary # alloc + >>= initWithContentsOfFile nsPListName + infoPList # setObjectForKey (toNSString executableInApp) + (toNSString "CFBundleExecutable") + infoPList # writeToFileAtomically nsPListName False + >>= failOnFalse "Couldn't write plist." return () |