How do I maintain cohesion when wrapping C lib?

I’m wrapping a C library in Haskell right now and am having trouble in the following scenario:

  • The library offers the ability register “named properties”. You register these before giving up control to the library completely (i.e. the library runs your main loop).
  • The library loads the properties’ values from a database and you can query them in a callback.

In other words, this is the Haskell pseudocode for my wrapper:

main = do
  library_init ["property1", "property2"] afterInit
  library_start

afterInit ptr = do
  property1Value <- read_value ptr "property1"
  putStrLn property1Value

Hopefully, the problem is clear: With this raw a wrapper, you can call read_value on a property you haven’t specified in library_init, resulting in a run-time error.

Is there a Haskell-idiomatic way to make this safer? I was thinking about something like a “property parser” thingy, as in:

data MyProperties = MyProperties String String

readProps = MyProperties <$> readProp "property1" <*> readProp "property2"

And then somehow extracting “property1” and “property2” from this “applicatified” parser, passing that to library_init (and its values afterInit). But I’m not sure how to construct this and if it’s wise to do so.

Is there any prior work here, or any pointers?

In an ideal Haskell world you would have some cool type-level stuff like

data Library (props :: RadixTree a)

readProp :: Lookup props (prop :: Symbol) a => Library props -> IO a

Everything is resolved during compilation, the user can’t make mistakes, you win.


Unfortunately in the current version of GHC your compilation times are going to suffer exponentially if you ever do anything remotely similar. In my view the correct way to go is to expose near-raw C functions and then have the user define all the property operations in a separate module. It’s not as safe, but both simple and blazing fast.

1 Like

Maybe with some TemplateHaskell you can produce a data type to use in your code and the function to init the library with the values from that Template Haskell section? :thinking:

This reminds me of the motivation for justified-containers. I suspect you could do something similar.

That sounds like a job for a free applicative. Turn read_value into a constructor, so that you can list the accessed properties to pass them to init, and then interpret the constructor with the actual read_value in the callback.

data Free f a where
  Pure :: a -> Free f a
  Ap :: f a -> Free f (a -> b) -> Free f b

data Access a where
  ReadValue :: Property -> Access Value

run :: Free Access (IO ()) -> IO ()
run accesses = do
  library_init (getProperties accesses) afterInit
  library_start
 where
  afterInit ptr = join (runAp (\case ReadValue prop -> read_value ptr prop) accesses)

getProperties :: Free Access a -> [Property]
2 Likes

Oh wow, this was actually the perfect solution! The “library” now looks like this:

data Property a = Property
  { propName :: String,
    propReader :: String -> Maybe a
  }
  deriving (Functor)

prop :: String -> (String -> Maybe a) -> Ap Property a
prop name reader = liftAp $ Property name reader

-- This returns just the names, so I can pass it to init
propNames :: Ap Property a -> [String]
propNames = runAp_ (singleton . propName)

-- This resolves properties to the values using the library
resolveProperties :: Ptr () -> Ap Property a -> IO a
resolveProperties ptr = runAp deconstruct
  where
    deconstruct (Property {propName, propReader}) = do
      propValue <- read_property ptr propName
      case propReader propValue of
        Nothing -> error "oh no!"
        Just propValue' -> pure propValue'

I added the possibility to change the type of the property value from string to any a. The main module looks like this now:

data MyProperties = MyProperties
  { prop1 :: String,
    prop2 :: Int
  }
  deriving (Show)

myProperties :: Ap Property MyProperties
myProperties = MyProperties <$> prop "prop1" Just <*> prop "prop2" readMaybe

main = do
  library_init (propNames myProperties) afterInit
  library_start

afterInit ptr = do
  propertyValues :: MyProperties <- resolveProperties ptr
  print propertyValues

Works like a charm and it’s not even that intrusive, I can stay inside IO and use it as-needed.

1 Like