Is there a way to chain functions like withCString?

别说谁变了你拦得住时间么 提交于 2019-12-09 14:50:06

问题


Is there a way to chain functions like withCString? By that I mean any function that looks something like f :: Foo -> (CFoo -> IO a) -> IO a.

For example, lets say there is a function cFunc :: CString -> CFoo -> CBar -> IO ()

Usualy, I would do something like:

haskellFunc string foo bar =
  withCString string $ \ cString ->
    withCFoo foo $ \ cFoo ->
      withCBar bar $ \ cBar ->
        cFunc cString cFoo cBar

But i would like to do something like:

haskellFunc = (withCString |.| withCFoo |.| withCBar) cFunc

with some appropriate composition operator |.|.

I'm writing library with a lot of C bindings, and this boilerplate comes often. Am I doing something wrong?


回答1:


You can use the Continuation applicative for composing these a -> (b -> IO c) -> IO c functions:

import Control.Monad.Cont

haskellFunc :: String -> Foo -> Bar -> IO ()
haskellFunc string foo bar = flip runCont id $ 
    cFunc <$> 
      cont (withCString string) <*> 
      cont (withCFoo foo) <*> 
      cont (withCBar bar)

Or with a bit of extra syntax:

haskellFunc' :: String -> Foo -> Bar -> IO ()
haskellFunc' string foo bar = flip runCont id $
    cFunc <<$>> withCString string <<*>> withCFoo foo <<*>> withCBar bar
  where
    f <<$>> x = f <$> cont x
    f <<*>> x = f <*> cont x



回答2:


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...




回答3:


Unfortunately, you can't write a function which does something as general as you would like to do. The problem is with Haskell's type system. In your example, cFunc takes three arguments, so when you wrote your convenience function it would expect a C function which took three arguments. There would be no way to write a function which could accept a cFunc of any number of arguments; Haskell's type system is too strict. With that in mind, however, you can write several different functions, each for a cFunc with a different number of arguments. Whether or not this is worth the effort depends on how often you will need to use that kind of boiler plate.

cApply2 :: (a' -> b' -> c) 
        -> (a -> (a' -> c)) 
        -> (b -> (b' -> c))
        -> a -> b -> c
cApply2 cFunc withArg1 withArg2 arg1 arg2 = 
  withArg1 arg1 $ \cArg1 ->
    withArg2 arg2 $ \cArg2 ->
      cFunc cArg1 cArg2

cApply3 :: (a' -> b' -> c' -> d)
        -> (a' -> (a -> d))
        -> (b' -> (b -> d))
        -> (c' -> (c -> d))
        -> a -> b -> c -> d
cApply3 cFunc withArg1 withArg2 withArg3 arg1 arg2 arg3 =
  withArg1 arg1 $ \cArg1 ->
    withArg2 arg2 $ \cArg2 ->
      withArg3 arg3 $ \cArg3 ->
        cFunc cArg1 cArg2 cArg3

Now, you can use the C functions like so.

haskellFunc :: String -> Foo -> Bar -> IO ()
haskellFunc = cApply3 cFunc withCString withCFoo withCBar


来源:https://stackoverflow.com/questions/37379984/is-there-a-way-to-chain-functions-like-withcstring

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!