[Haskell-iPhone] Automatically freeing function pointers
David Pollak
feeder.of.the.bears at gmail.com
Tue Jun 21 00:51:43 CEST 2011
On Mon, Jun 20, 2011 at 1:46 PM, Stephen Blackheath [to GHC-iPhone] <
likeliest.complexions.stephen at blacksapphire.com> wrote:
> David,
>
> I hadn't quite grasped your code. The problem with your code is that these
> two lines...
>
> > func <- funky
> > freeHaskellFunPtr func
>
> ...allocate then deallocate a function pointer, with a net result of
> nothing useful, and no effect on the function pointer you allocated on the
> third line.
>
> If you use this trick, however...
>
> {-# LANGUAGE DoRec #-}
>
> foreign import ccall safe "wrapper" mkInit
> :: (Ptr WorkerThread -> CInt -> IO ()) -> IO (FunPtr (Ptr WorkerThread
> -> CInt -> IO ()))
>
> applicationMain init dealloc = mdo
> fInit <- mkInit $ \callbackWorker fd -> do
> freeHaskellFunPtr fInit
> ...
> ...
>
> ...then you can do it quite painlessly. Note that DoRec is correct for ghc
> 6.10, but its name has changed in later ghc versions. The compiler will
> tell you.
>
Excellent! Thanks for the "pointer" oh wait... "thunk" oh wait... ;-)
>
>
> Steve
>
>
> On 21/06/11 05:00, David Pollak wrote:
>
>>
>>
>> On Sun, Jun 19, 2011 at 1:32 PM, Stephen Blackheath [to GHC-iPhone]
>> <likeliest.complexions.**stephen at blacksapphire.com<likeliest.complexions.stephen at blacksapphire.com>
>> <mailto:likeliest.complexions.**stephen at blacksapphire.com<likeliest.complexions.stephen at blacksapphire.com>>>
>> wrote:
>>
>> David,
>>
>> In GHC-iPhone the number of function pointers that are allowed to be
>> active for a given function is limited, but you can change the size
>> of the limit. This is documented in
>>
>>
>> Steve,
>>
>> Yep... I understand that there are not an unlimited number of function
>> pointers. However, the function that I wrote was "supposed" to
>> automatically release the function:
>>
>> runOnMain :: IO () -> IO ()
>> runOnMain todo = do
>> func <- funky
>> dispatchFunc func
>> where funky = mkStrCB $ \v -> do
>> todo
>> func <- funky
>> freeHaskellFunPtr func
>>
>> Note the freeHaskellFunPtr function call at the end of the lambda.
>>
>> I'm thinking that the "func <- funky" line is being treated as a
>> recursive call and I'm also thinking that this is a limitation of my
>> understanding the magic of lazy evaluation.
>>
>> So, please let me rephrase my question:
>>
>> How do I get the pointer to a wrapper function so that the pointer can
>> be used within the wrapped function itself?
>>
>> I have worked around the particular issue by making a call to
>> freeHaskellFunPtr in the Objective-C code that invokes the function.
>> It's less optimal that being able to have the Haskell code be able to
>> auto-free the function pointer after the function is invoked.
>>
>> Thanks,
>>
>> David
>>
>> http://projects.haskell.org/__**ghc-iphone/downloads/GHC-__**
>> iPhone.pdf<http://projects.haskell.org/__ghc-iphone/downloads/GHC-__iPhone.pdf>
>> <http://projects.haskell.org/**ghc-iphone/downloads/GHC-**iPhone.pdf<http://projects.haskell.org/ghc-iphone/downloads/GHC-iPhone.pdf>
>> >
>>
>> on p5 under 'Pool sizes for foreign function "wrapper" callbacks'.
>>
>>
>> Steve
>>
>>
>> On 18/06/11 11:29, David Pollak wrote:
>>
>> Howdy,
>>
>> I tried to build a function that would create an auto-freeing
>> function
>> pointer:
>>
>> runOnMain :: IO () -> IO ()
>> runOnMain todo = do
>> func <- funky
>> dispatchFunc func
>> where funky = mkStrCB $ \v -> do
>> todo
>> func <- funky
>> freeHaskellFunPtr func
>>
>> Unfortunately, I wind up getting:
>> internal error: iPhoneCreateAdjustor - adjustor pool
>> 'Main_d2K2' is
>> empty (capacity 32)
>> (GHC version 6.10.4-iphone-simulator for i386_apple_darwin)
>>
>> I'm not sure why, but I suspect that funky is being called
>> recursively
>> and thus stuff is never being freed.
>>
>> Any hints as to the issue and solutions?
>>
>> Thanks,
>>
>> David
>>
>>
>> --
>> Lift, the simply functional web framework http://liftweb.net
>> Simply Lift http://simply.liftweb.net
>> Follow me: http://twitter.com/dpp
>> Blog: http://goodstuff.im
>>
>>
>>
>> ______________________________**___________________
>> iPhone mailing list
>> iPhone at haskell.org <mailto:iPhone at haskell.org>
>>
>> http://www.haskell.org/__**mailman/listinfo/iphone<http://www.haskell.org/__mailman/listinfo/iphone>
>> <http://www.haskell.org/**mailman/listinfo/iphone<http://www.haskell.org/mailman/listinfo/iphone>
>> >
>>
>>
>> ______________________________**___________________
>> iPhone mailing list
>> iPhone at haskell.org <mailto:iPhone at haskell.org>
>>
>> http://www.haskell.org/__**mailman/listinfo/iphone<http://www.haskell.org/__mailman/listinfo/iphone>
>> <http://www.haskell.org/**mailman/listinfo/iphone<http://www.haskell.org/mailman/listinfo/iphone>
>> >
>>
>>
>>
>>
>> --
>> Lift, the simply functional web framework http://liftweb.net
>> Simply Lift http://simply.liftweb.net
>> Follow me: http://twitter.com/dpp
>> Blog: http://goodstuff.im
>>
>>
--
Lift, the simply functional web framework http://liftweb.net
Simply Lift http://simply.liftweb.net
Follow me: http://twitter.com/dpp
Blog: http://goodstuff.im
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/iphone/attachments/20110620/8ab805ae/attachment-0001.htm>
More information about the iPhone
mailing list