Open pjones opened 7 years ago
I'll look into this.
Grepping for foreign import ccall unsafe
yields 303 results. Should I just slap something like
safely :: IO a -> IO (Maybe a)
safely a = either (const Nothing) Just <$> try a
safeGetWindowAttributes :: Display -> Window -> IO (Maybe WindowAttributes)
safeGetWindowAttributes d w = safely $ getWindowAttributes d w
around all of them or is there a way to narrow the results down by "notoriety"?
Awesome @SirBoonami, Thanks!
So, you have a good question. Can the calls into the C library produce exceptions? If so, then I like your approach. If not, it might be better to just get rid of the calls to throwIfZero
.
We should also bring @geekosaur into this discussion. I wonder if we should even bother preserving the API. We could bump the version number to 2.0 and actually change the function signatures so we don't need unsafe/safe versions.
Thoughts?
A more useful check is to look for all occurrences of throwErrorIf
and change them to produce Maybe
instead.
Good call. Including definitions and imports, there are currently 36 occurences of throwIf*
. Changing these is a good start, we can take a look at foreign exceptions after that.
One more thing: All of these throwIf*
calls supply error strings (like "xGetCommand returned status " ++ show status
). Replacing these with a simple return Nothing
discards this potentially helpful debug information. Wouldn't Either String a
be a better choice?
I was actually thinking about that, either via Except or by logging to
stderr (which you'll find in a few other places, some of which are annoying
to other users of the X11 package); we might want to go with an Except String
-based setup instead.
On Tue, Apr 11, 2017 at 2:12 PM, Felix Hirn notifications@github.com wrote:
Good call. Including definitions and imports, there are currently 36 occurences of throwIf*. Changing these is a good start, we can take a look at foreign exceptions after that.
One more thing: All of these throwIf* calls supply error strings (like "xGetCommand returned status " ++ show status). Replacing these with a simple return Nothing discards this potentially helpful debug information. Wouldn't Either String a be a better choice?
— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/xmonad/X11/issues/51#issuecomment-293351947, or mute the thread https://github.com/notifications/unsubscribe-auth/AB8SoGvoJWJj2w5aKaFZjM9PKMm9SlgUks5ru8KrgaJpZM4M5Poh .
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
Not a fan of unconditional stderr logging either, even when tied to a compilation flag. Wouldn't want to drown the user in a flood of exception messages if he's looking for a specific one. Also, some exceptions naturally occur during normal production use, logging everything would needlessly inflate log files like ~/.xsession-errors
for xmonad
with useless clutter. Using a monad allows for much better control over what exactly get printed out.
Also, what is this Except
thing you mentioned? Hoogle doesn't show anything useful...
Ah, thank you. I was thinking about EitherT
from either myself (which is virtually the same thing). But I don't know if refactoring large parts of the lib to use a different monad, sprinkling liftIO
s and runExceptT
s all over the place is really worth the effort...
EitherT
is deprecated; ExceptT
is the replacement. Also, nobody said
you had to use its Monad
interface; how many people use Either a
's
Monad
?
On Tue, Apr 11, 2017 at 2:42 PM, Felix Hirn notifications@github.com wrote:
Ah, thank you. I was thinking about EitherT from either https://hackage.haskell.org/package/either myself (which is virtually the same thing). But I don't know if refactoring large parts of the lib to use a different monad, sprinkling liftIOs and runExceptTs all over the place is really worth the effort...
— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/xmonad/X11/issues/51#issuecomment-293362581, or mute the thread https://github.com/notifications/unsubscribe-auth/AB8SoI-kPZMGDP2fzKgH5gsvgk_CljV5ks5ru8mKgaJpZM4M5Poh .
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
So you mean our functions should look something like a -> IO (Except String b)
? Because that's probably our best option imo...
Probably. Either
would also work for that usage, but both the old
Either
and the Error
instances were deprecated in order to make
Either
a simple product type that doesn't favor either alternative and
Except
the one that specifically considers its right type the normal one.
On Tue, Apr 11, 2017 at 3:11 PM, Felix Hirn notifications@github.com wrote:
So you mean our functions should look something like a -> IO (Except String b)? Because that's probably our best option imo...
— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/xmonad/X11/issues/51#issuecomment-293370556, or mute the thread https://github.com/notifications/unsubscribe-auth/AB8SoCU092GOawOaDPycM0-cvm639ZDhks5ru9B1gaJpZM4M5Poh .
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
Sounds good, I'll get to it then.
All right, this is what I've got so far:
IO (MayFail a)
. MayFail
currently is Either String
instead of Except String
because Except
needs to be unwrapped to Either
anyway before it can be pattern-matched, but this can still be changed if you insist.throwIf*
:
guard' :: (a -> Bool) -> (a -> String) -> IO a -> (a -> IO b) -> IO (MayFail b)
guard_ :: (a -> Bool) -> String -> IO a -> (a -> IO b) -> IO (MayFail b)
guardNotZero :: String -> IO Status -> IO a -> IO (MayFail a)
guardNotNull :: String -> IO (Ptr a) -> (Ptr a -> IO b) -> IO (MayFail b)
safely :: IO a -> IO (MayFail a)
(currently not in use but probably handy later on)throwIf*
with the new alternaltives, deprecated throwIfZero
.outParameters*
wrappers into two different sets:
outParameters2 :: (Ptr a -> Ptr b -> IO r) -> IO (a,b)
for safe calls (previously realized with outParameters2 id
)outParametersF2 :: (r -> Maybe String) -> (Ptr a -> Ptr b -> IO r) -> IO (MayFail (a,b))
for unsafe calls (previously realized with outParameters2 (throwIf*)
)outParameters*
calls with the new versions.Result: There are no more exceptions thrown from Haskell code, the only occurences of throwIf*
still left are from the definition of the now deprecated throwIfZero
.
Still TODO:
Thoughts?
Wow @SirBoonami, great work!
My first thought is how do we make this easy to compose? In xmonad there are several places where we call a handful of X11 functions in a row. With ExceptT
I can chain them together in a do
block and only have to pattern match on the final Either
coming out of runExceptT
. This would make it a lot easier to integrate these changes back into xmonad at least.
Perhaps it's overkill, but if it were me, I'd write a newtype
called X11
that is just EitherT String IO
and include a runX11
function that unwraps the EitherT
and calls runExeptT
. Again, just a thought.
For testing, I have no idea. The best I can come up with is refactor xmonad to use these new functions and then play around in xmonad-testing.
Pity we need to support 7.6.3, or we could use a pattern synonym to reduce the noise.
(snark re testing: do it and wait for a distro maintainer to make xmonad 0.13 build against it...)
We'll have to decide on a trade-off here:
getWindowAttributes w >>= \case {...}
runExceptT (ExceptT getWindowAttributes w >>= ExceptT rmRfSlash) >>= \case {...}
ExceptT
runExceptT (getWindowAttributes w) >>= \case {...}
runExceptT (getWindowAttributes w >>= rmRfSlash) >>= \case {...}
liftIO
s in our code, but the guard*
functions could be implemented a bit nicer.X11
monad?It depends on the most common use case, but I am slightly in favour of option 2.
Nice description of trade offs! I still like ExceptT
since it's very rare to just call just one X11 function. I think the safe functions should also return the X11 monad so that everything composes nicely.
I think the liftIO
s could be minimized with good helper functions, like you suggest.
Just my $0.02 though.
@SirBoonami If you want help on this project I'd be happy to point other volunteers towards this issue. Just let me know.
I think I'll be fine as far as the refactoring of X11 goes. Applying the changes to the xmonad core is where I'll probably need some help. (Not sure about xmonad-contrib.)
But I'll need somebody with a bit more experience and authority than me to make a call on the Except
vs ExceptT
decision before I can continue. Considering the impact of the proposed changes that's not something I feel entitled to decide on my own.
@geekosaur What are your feelings on newtype X11 = X11 { unX11 :: ExceptT ...}
?
Could work. I've actually been thinking about something a little stronger, but it's not happening soon and this would be a waypoint toward it anyway.
On Sat, Apr 15, 2017 at 1:37 PM, Peter J. Jones notifications@github.com wrote:
@geekosaur https://github.com/geekosaur What are your feelings on newtype X11 = X11 { unX11 :: ExceptT ...}?
— You are receiving this because you were mentioned. Reply to this email directly, view it on GitHub https://github.com/xmonad/X11/issues/51#issuecomment-294307478, or mute the thread https://github.com/notifications/unsubscribe-auth/AB8SoNrdbESPpciEUxIQYt0wv1VKE0Dhks5rwQB1gaJpZM4M5Poh .
-- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
So we agree that it's a good idea, but nobody is bold enough to say "let's do this"? Then I'll call it here:
type X11 = ExceptT String IO
runX11 :: X11 a -> IO (Either String a)
will be it. The exact representation could still be changed at a later date without the need to rewrite everything if we use the abstract runX11
.
I'll start with all the unsafe functions again, in the meantime we can discuss whether using X11
for safe functions as well is a good idea because I'm not so sure about that.
Implementing them that way would force users to write lots of dead error handling code that is absolutely guaranteed to never run. We could document which functions are safe and provide a runSafeX11 :: X11 a -> IO a
, but this would lead us down the same dark path we are trying to escape from right now.
On the other hand, the only real costs of leaving safe functions as IO
are:
type SafeX11 = IO
(and maybe calling the other one UnsafeX11
),liftIO
s in our UnsafeX11
code.Am I missing something?
I'm going to be bold:
There should be no difference between "safe" and "unsafe" functions. Doing so breaks composability. If you look in the xmonad source you will see several X11 calls in a row inside a do
block. This usage pattern should stay the same.
To make porting code easier we should have a couple helper functions:
unsafeX11 :: X11 a -> IO a
maybeX11 :: X11 a -> IO (Maybe a)
I don't see how that would break composability. All you'd have to do is lift the safe function(s):
eitherResult <- do
unsafe1
liftIO $ safe1
unsafe2
(x, y) <- liftIO $ do
x <- safe2
safe3 x
y <- safe4
return (x, y)
unsafe3 x y
Maybe even with a custom lifting function (liftSafe :: SafeX11 a -> UnsafeX11 a
) for future compatibility.
It's a bit more cumbersome, yes. But I don't see how taking out exceptions only to replace them with partial functions like unsafeX11
is an improvement in code quality. Haskell's amazing type system offers to help us here by telling us exactly what can fail and what can't, why shouldn't we make use of that?
I think we should avoid using the terms safe and unsafe, I'm getting confused.
We all agree that functions that might throw exceptions should return a variant of Either
. The question is what to do with functions that are IO
values but should be okay to call without worrying about exceptions. In the libraries that I've reviewed and written it has seemed helpful to give both types of functions the same interface. For example, in xmonad there are functions that return X a
even though they cannot fail. Should they just return IO a
instead? I would say no.
IMO the whole point of this abstract type is to defer error handling until the end of a series of computations. If I'm already "in" the X11
monad I don't want to have to lift some other function that is doing X11 work.
I'll let @geekosaur weigh in, but I think any function calling into libx11 should be prepared to fail and should have the same interface.
Alright Gentlemen, I'd like to direct your attention towards this once more.
ExceptT String IO
, a few helpers were necessary as well.UnnamedMonad
so I can easily sed
it to MayFailX11
, UnsafeX11
, just X11
or whatever we decide to settle on.Graphics.X11.Xinerama
contains some a -> IO (Maybe b)
style functions, maybe it would be smart to use UnnamedMonad
here as well?@SirBoonami Just a note that I haven't had a chance to review your recent changes but I still care and will do so as soon as I can. Thanks.
No worries, take your time =)
What's the status of this? travitch/taffybar#105 Needs this to be fixed for rawGetWindowProperty and its various flavors.
There is another sense in which all the X11 calls need to be safed (this has nothing to do with return types on in haskell exceptions):
To properly handle exceptions from X11, a proper error handler needs to be set as in: https://github.com/taffybar/taffybar/blob/1d57f895d3b9af3dca086c98d6390219bfd91fb4/src/System/Taffybar/Information/SafeX11.hs#L120
but this will only work at all if calls like XGetWindowProperty (for example) are marked interruptible in their FFI imports:
@geekosaur @pjones I'm willing to do some of this work, but I think one thing we need to think about is whether or not we want X11 to be responsible for installing the error handler.
xmonad currently sets its own error handler, and things like this could interfere with this libraries handling of errors https://github.com/ivanmalison/xmonad/blob/bb13853929f8f6fc59b526bcc10631e1bac309ad/src/XMonad/Main.hs#L191
My opinion is that the best thing to do would be to stop exposing any ability to set the error handler, and handle all error internally in X11 and then expose haskell values to indicate what went wrong in those cases. It might be difficult to do something like this without having some sort of signaling mechanism as in SafeX11, so this could be a quite significant change.
There also might be some performance implications to marking functions interruptible/safe over unsafe. I think it does need to be done though.
The only calls that should be unsafe
are the ones that are cpp
macro lookups, and those are also irrelevant for interruptible
. Anything else risks (for example) xmonad
unexpectedly blocking, which you really don't want in a window manager.
The error handler is set in xmonad
because the library has no business making that decision for applications given how things work now — and in particular outputting a message that mentions xmonad
without getting that name from the application somehow. This does need to be thought about, and probably redesigning the API to do something more sane.
The only calls that should be unsafe are the ones that are cpp macro lookups
Yes, but atm as far as I can tell, literally everything is marked unsafe, and as such, I actually don't think there is much point in setting a non C error handler.
The error handler is set in xmonad because the library has no business making that decision for applications given how things work now — and in particular outputting a message that mentions xmonad without getting that name from the application somehow.
Yes I agree, but the current reality, is that you can actually only set the C error handler which mentions xmonad, because this was not factored out properly, and this actually occurs in the X11 library:
https://github.com/xmonad/X11/blob/9f6df0d79665a285ef9923124a58b38053b8ca1e/cbits/XUtils.c#L19
We actually have this:
But the comment explains that it is experimental, and in fact, it actually doesn't work, becase things really need to be marked interruptible if we are going to be calling back into the haskell runtime.
This does need to be thought about, and probably redesigning the API to do something more sane.
Again, my proposal is this:
Yes, I was agreeing with you. But X11 isn't "mine" and in any case I am not in a position to do anything useful with xmonad or anything else, and won't be any time soon. :/
@liskin Why was this removed from 2.0. IMO this is one of the most important things that could be done to the x11 lib.
@IvanMalison I just removed the milestone itself because we don't really have any plan or hope to actually work towards a 2.0 X11 Haskell bindings. It's not the sort of thing that's got a high return on investment in 2021. An xcb binding would be more valuable, but even that might be seen by many as silly in a world that's increasingly moving towards Wayland.
That being said, if someone comes with a PR that implements all of this I'll be happy to help review it and guide the release process and make sure we don't break any dependencies. It's just not something I'd allocate any resources on, myself.
I'm creating this ticket to help us track the work going on over at xmonad/xmonad-contrib#146.
Starting with the
getWindowAttributes
function, start creating versions that returnMaybe a
instead of throwing an exception. I'm not sure what the new naming scheme should be, but the original functions should just call the new version and throw if they getNothing
back.