[GHC] #8310: Can we change the semantics of `Trustworthy`?

#8310: Can we change the semantics of `Trustworthy`? ------------------------------------+------------------------------------- Reporter: ekmett | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Keywords: | Operating System: Unknown/Multiple Architecture: Unknown/Multiple | Type of failure: None/Unknown Difficulty: Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | ------------------------------------+------------------------------------- I would like to propose that if I put `{-# LANGUAGE Trustworthy #-}` on a module and it infers as Safe, then the module should get marked `Safe` instead of `Trustworthy`. Putting `Trustworthy` in right now has the semantics "it is at most `Trustworthy`". It would be far more useful to have the semantics "it is at least `Trustworthy`". The current situation is actually a maintenance nightmare. Currently, if I incur a dependency on a package has some `Safe` versions and some non-Safe versions, but I know I'm not using any unsafe componentry of it, I have to either a.) Mark my package Trustworthy unnecessarily enlarging the trusted code base a lot. b.) Track ALL of the dependencies of my dependencies to know when it will be Safe rather than Trustworthy, then insert brittle CPP pragmas that often fail. Consider that `hashable` 1.2.1.0 recently became flagged `Trustworthy`, but was previously not. Now, if I want to properly infer as `Safe`, I have to track the exact version of `hashable` I depend on _and_ whether or not my `Typeable` instance is being rolled manually and make an enormous composite `#ifdef` at the top of the module. Worse, we got the patch in about a month ago, so to future proof my code I'd have had to be psychic. Now consider that I have 50 other packages to maintain in this same manner. I wind up shotgunning `Trustworthy`, do deal with the fact that I deigned to provide instances for `vector`. If `vector` ever refactored to support Safe Haskell, I'd have to go fix up 50 very arcane CPP pragmas to match the internal details of an external package. Then I wind up checking them by round tripping through cabal installs and checking my haddocks. This is further complicated by the fact that some things are just becoming Safe "for free" as they go, due to the fact that they no longer need or can supply hand-rolled `Typeable` instances. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------ Reporter: ekmett | Owner: dterei Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Changes (by dterei): * owner: => dterei Comment: I like it! I'll check with the other Safe Haskell gurus and assuming they're happy it's an easy change to make. Not sure if 7.8 window has passed, hopefully we can get it in for that. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------ Reporter: ekmett | Owner: dterei Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by dterei): @monoidal no trouble, yes I've been thinking it over and discussing with David Mazieres. There is a complication that isn't clear how to resolve. Mazieres is away in France right now so that's been delaying me. The problem. Imagine this situation. * `Data.ByteString` is marked and compiled as Trustworthy * module `A` imports Data.ByteString * module `A` is marked Trustworthy * module `A` resides in package P (and P only contains A) Assume that A could be inferred as `Safe`. Right now if you compile A with the following Safe Haskell flags you get these package trust dependencies: * Safe: bytestring, base * Trustworthy (ByteString imported without safe keyword): p * Trustworthy (ByteString imported with safe keyword): p, bytestring * (Inferred Safe): bytestring, base So if we changed it so `Trustworthy` marked modules could be inferred Safe, what package trust dependencies should be attached? Options: 1) bytestring, base 2) p 3) p, bytestring 4) p, bytestring, base It becomes unintuitive what packages you'll need to trust and that set will change unpredictably over time. Currently, package trust has a clear relationship and direct with `Trustworthy`, this change either makes that relation indirect, or confuses the boundary of `Safe` vs. `Trustworthy`. I'd love to hear any thoughts you or @ekmett have on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------ Reporter: ekmett | Owner: dterei Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by ekmett): My understanding was that if I import a module that is Trustworthy, my module could still infer as Safe-Inferred. Perhaps that was a naïve interpretation. I'll need to go back through and re-read the specification, and understand the safe import machinery better. Right now my main problem is that no matter what I do, I've just not proven smart enough to make the most specific annotation that works for all of my dependencies without unnecessarily enlarging the trusted code base. One possible middle ground that doesn't muddle those semantics is that we could issue a warning when you needlessly mark a module as Trustworthy, when it would otherwise infer as Safe-Inferred. Then I'd at least get some kind of feedback during the development process and from my end-users, and cleaning up warnings would catalyze users into writing patches. This would still result in me having to maintain some painfully complicated logic to get the right safety properties, but it would at least tell me pointwise when I was in a situation where I'd gotten it wrong. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------ Reporter: ekmett | Owner: dterei Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Unknown/Multiple Type of failure: None/Unknown | Difficulty: Unknown Test Case: | Blocked By: Blocking: | Related Tickets: -------------------------------------+------------------------------------ Comment (by dterei): @ekmett yes importing a Trustworthy module still allows you to be inferred as `Safe-Inferred`. The question is, marking a module as `Trustworthy` has a different set of package-trust dependencies today than if you had left that module unmarked and let it be inferred as `Safe-Inferred`. If we change `Trustworthy` to be 'at-least' trustworthy and allow those modules to still be inferred `Safe-Inferred`, then what package-trust dependencies should apply? That isn't clear. The warning is a good idea and makes sense. I think the 'at-least' semantics may also be a good idea, just need to think through what package-trust dependencies should be applied and if that complication to the semantics is worth enough. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------- Reporter: ekmett | Owner: dterei Type: feature | Status: new request | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: Resolution: | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Comment (by thomie): I saw some Trustworthy changes fly by, maybe this is fixed as well? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8310: Can we change the semantics of `Trustworthy`? -------------------------------------+------------------------------------- Reporter: ekmett | Owner: dterei Type: feature | Status: closed request | Milestone: Priority: normal | Version: 7.6.3 Component: Compiler | Keywords: Resolution: fixed | Architecture: Unknown/Multiple Operating System: | Difficulty: Unknown Unknown/Multiple | Blocked By: Type of failure: | Related Tickets: None/Unknown | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Changes (by dterei): * status: new => closed * resolution: => fixed Comment: Yes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8310#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC