Motivation
Suppose you’re writing bindings to a node library that has some classes which can emit events. You may have several FFI definitions that look like this:
exports.onError = function (obj) {
return function (callback) {
return function () {
obj.on("error", function (err) {
callback(err)();
}
}
}
}foreign import data LIB_EFFECT :: Effect
foreign import data Obj :: Type
type ErrorCallback e = Error -> Eff (le :: LIB_EFFECT | e) Unit
foreign import onError :: forall e. Obj -> ErrorCallback e -> Eff (le :: LIB_EFFECT | e) UnitLet’s say you have onError and onSuccess, but their callbacks look different (maybe they have different arities or take different argument types). You could just expose those two methods for handling events, and that wouldn’t be so bad. But if you find out you need to expose many more, you may want to find a DRYer approach than having a bunch of onEvent functions.
Suppose you’ve cleaned up your FFI so that instead of exporting a bunch of event handling functions, you have one catchall:
Unfortunately we can’t safely use this from Purescript – if we want type safety we’ll still need to export a bunch of functions, like onError = unsafeOn "error".
So, the goal is to have a single on combinator that somehow takes an event type, object type, callback type and combines them in the right way.
First attempt
Let’s try enumerating all our events.
data Event = Error | Success | Other
eventToString :: Event -> String
eventToString = case _ of
Error -> "error"
Success -> "success"
Other -> "other"Then we might try something like this:
on :: forall callback e. Event -> Obj -> callback -> Eff (le :: LIB_EFFECT | e) Unit
on ev = unsafeOn (eventToString ev)The problem with this is that we can pass literally any value as a callback, so this won’t do.
Second attempt
Odds are we know exactly what the types of our callbacks are, so we’ll just enumerate those too – at most one callback constructor per Event constructor.
data Callback e
= ErrorCallback (Eff.Error -> Eff (le :: LIB_EFFECT | e) Unit)
| SuccessCallback (Result -> Eff (le :: LIB_EFFECT | e) Unit)
| OtherCallback (Eff (le :: LIB_EFFECT | e) Unit)on2 :: forall e cb. Event -> Obj -> Callback e -> Eff (le :: LIB_EFFECT | e) Unit
on2 ev obj cb = case ev, cb of
Error, ErrorCallback cb -> unsafeOn "error" obj cb
Success, SuccessCallback cb -> unsafeOn "success" obj cb
Other, OtherCallback cb -> unsafeOn "other" obj cb
_, _ -> pure unitThis is terrible! We’re silently failing if the wrong callback type is associated with the wrong event, which is surprising to say the least.
noOp :: forall e. Obj -> Eff (le :: LIB_EFFECT | e) Unit
noOp obj = on2 Success obj $ ErrorCallback \ err -> log (message err)Thus we also want to be able to rule out illegal argument combinations and in a way that’s transparent to the caller.
Third attempt
Good for us that there’s a standard way of dealing with the possibility of failure (defined in our case as passing a bad combination of arguments to the on2 function).
on3 :: forall e cb. Event -> Obj -> Callback e -> Maybe (Eff (le :: LIB_EFFECT | e) Unit)
on3 ev obj cb = case ev, cb of
Error, ErrorCallback cb -> Just (unsafeOn "error" obj cb)
Success, SuccessCallback cb -> Just (unsafeOn "success" obj cb)
Other, OtherCallback cb -> Just (unsafeOn "other" obj cb)
_, _ -> NothingBut this is not ideal. While it solves the problem of making failure explicit, it pushes validation to runtime, and this problem definitely feels like something that can be prevented at compilation.
And let’s be honest, odds are this would be used by pattern-matching on Nothing and handling that with pure unit – so, the same as the on2 definition but with more misdirection.
Fourth attempt
Now we know that we want the event to somehow determine the type of the callback. This suggests we should use a typeclass: if we can somehow exploit the lack of an instance to mean that an event is given the wrong callback type, we’ve succeeded.
class On evt obj callback | evt -> obj callback where
on :: forall e. evt -> obj -> callback -> Eff (le :: LIB_EFFECT | e) Unit
data Success = Success
data Error = Error
data Other = Other
instance onObjError :: On Error Obj (Eff.Error -> Eff (le :: LIB_EFFECT | e) Unit) where
on _ = unsafeOn "error"Nope: Could not match type ( le :: LIB_EFFECT | e0 ) with type ( le :: LIB_EFFECT | e01 )
The problem here is that the e in the callback type is not actually the same as the e in the result type.
Fifth attempt
Instead of hiding the e behind a quantifier in the class method, let’s factor out the whole result type.
class On evt obj callback out | evt -> obj callback out where
on :: evt -> obj -> callback -> out
data Success = Success
data Error = Error
data Other = Other
instance onObjError :: On Error Obj (Eff.Error -> Eff (le :: LIB_EFFECT | e) Unit) (Eff (le :: LIB_EFFECT | e) Unit) where
on _ = unsafeOn "error"Success! This finally compiles. But why stop here when we can go type-crazy?
Fifth attempt, alternate
foreign import kind Event
data EventProxy (e :: Event) = EventProxy
class On (evt :: Event) obj callback out | evt -> obj callback out where
on :: forall proxy. proxy evt -> obj -> callback -> out
foreign import data Success :: Event
foreign import data Error :: Event
foreign import data Other :: Event
instance onObjError :: On Error Obj (Eff.Error -> Eff (le :: LIB_EFFECT | e) Unit) (Eff (le :: LIB_EFFECT | e) Unit) where
on _ = unsafeOn "error"Usage
Now we can turn this:
main = do
obj <- newObj config
onSuccess obj \ result -> do
log "Success!"
logShow result
onError obj \ err -> do
log "Error :("
log (message err)into this:
main = do
obj <- newObj config
on success obj \ result -> do
log "Success!"
logShow result
on error obj \ err -> do
log "Error :("
log (message err)
where
success = EventProxy :: EventProxy Success
error = EventProxy :: EventProxy ErrorBut note that the following wo(uld)n’t compile:
main = do
obj <- newObj config
on success obj \ err -> do
log "Error :("
log (message err)
where
success = EventProxy :: EventProxy SuccessThis is because using success tells the compiler the callback must be a success callback – whether that means (as is defined in the instance) that it takes multiple arguments, or that its one argument isn’t an Eff.Error. Also, the use of message tells the compiler that the callback’s argument is an Eff.Error.
Or you may prefer the original Attempt 5 way:
main = do
obj <- newObj config
on Success obj \ result -> do
log "Success!"
logShow result
on Error obj \ err -> do
log "Error :("
log (message err)¯\_(ツ)_/¯
Conclusion
As presented, there should be one Event for each instance. But sometimes you may want to use the same event for two different objects. In that case, the definition of On can be changed as follows:
Now you can use the same Event for two different objects instead of defining e.g. SuccessObj1 and SuccessObj2.