I took a stab at this. The result isn't beautiful, but it works. The TL;DR is that, by the end, we can write your function like this, assuming I made no crippling errors:
haskellFunc string foo bar = cFunc <^ string <^> foo ^> bar
We need some GHC extensions for this to work, but they're pretty tame:
{-# LANGUAGE MultiParamTypeClasses #-}
-- So that we can declare an instance for String,
-- aka [Char]. Without this extension, we'd only
-- be able to declare an instance for [a], which
-- is not what we want.
{-# LANGUAGE FlexibleInstances #-}
First I define a typeclass to represent the common nature of CString
, CFoo
, and CBar
, using withCType
as the single name for withC___
:
-- I use c as the type variable to indicate that
-- it represents the "C" version of our type.
class CType a c where
withCType :: a -> (c -> IO b) -> IO b
Then some dummy types and instances so that I could typecheck this in isolation:
-- I'm using some dummy types I made up so I could
-- typecheck this answer standalone.
newtype CString = CString String
newtype CInt = CInt Int
newtype CChar = CChar Char
instance (CType String CString) where
-- In reality, withCType = withCString
withCType str f = f (CString str)
instance (CType Int CInt) where
withCType str f = f (CInt str)
instance (CType Char CChar) where
withCType str f = f (CChar str)
My initial thought was that we'd have something like this that we'd use to invoke our functions on the underlying C types...
liftC :: CType a c => (c -> IO b) -> (a -> IO b)
liftC cFunc x = withCType x cFunc
But that only lets us lift functions of one argument. We'd like to lift functions of multiple arguments...
liftC2 :: (CType a c, CType a' c') => (c -> c' -> IO b) -> (a -> a' -> IO b)
liftC2 cFunc x y = withCType x (\cx -> withCType y (cFunc cx))
That works just fine, but it would be great if we didn't need to define one of those for every arity we're after. We already know that you can replace all of the liftM2
, liftM3
, etc. functions with chains of <$>
and <*>
, and it would be nice to do the same here.
So my first thought was to try to turn liftC
into an operator, and intersperse it between each argument. So it would look something like this:
func <^> x <^> y <^> z
Well... we can't quite do that. Because the types don't work. Consider this:
(<^>) :: CType a c => (c -> IO b) -> (a -> IO b)
cFunc <^> x = withCType x cFunc
The IO
part of withCType
makes this difficult. In order for this to chain nicely, we would need to get back another function of the form (c -> IO b)
but instead we get back the IO
recipe to produce that. The result of invoking the above <^>
on a "binary" function, for example, is IO (c -> IO b)
. That's troubling.
We can hack around this by providing three different operators... some of which work in IO
and some of which don't, and using them in the right position in a call chain. This isn't very neat or nice. But it does work. There must be a cleaner way to do this same thing...
-- Start of the chain: pure function to a pure
-- value. The "pure value" in our case will be
-- the "function expecting more arguments" after
-- we apply its first argument.
(<^) :: CType a c => (c -> b) -> (a -> IO b)
cFunc <^ x = withCType x (\cx -> return (cFunc cx))
-- Middle of the chain: we have an IO function now,
-- but it produces a pure value -- "gimme more arguments."
(<^>) :: CType a c => IO (c -> b) -> a -> IO b
iocFunc <^> x = iocFunc >>= (<^ x)
-- End of the chain: we have an IO function that produces
-- an IO value -- no more arguments need to be provided;
-- here's the final value.
(^>) :: CType a c => IO (c -> IO b) -> a -> IO b
iocFunc ^> x = withCType x =<< iocFunc
We can use this weird frankenstein like this (adding more <^>
s for higher-arity functions):
main = do
x <- cFunc <^ "hello" <^> (10 :: Int) ^> 'a'
print x
cFunc :: CString -> CInt -> CChar -> IO ()
cFunc _ _ _ = pure ()
This is somewhat inelegant. I'd love to see a cleaner way to get at this. And I don't love the symbols I chose for those operators...
(| cFunc (cont (withCString string)) (cont (withCFoo foo)) (cont (withCBar bar)) |)
– Lion