[Haskell-cafe] Any precedent or plan for guaranteed-safe Eq and Ord instances?

Ryan Newton rrnewton
Tue Oct 1 20:56:38 UTC 2013


Here are some examples:

---------------------------------------------
data Foo = Bar | Baz

instance Eq Foo where
  _ == _ = True

instance Ord Foo where
  compare Bar Bar = EQ
  compare Bar Baz = LT
  compare _   _   = error "I'm partial!"
---------------------------------------------

These would allow LVish's "runPar" to non-determinstically return Bar or
Baz (thinking they're the same based on Eq).  Or it would allow runPar to
nondeterministically crash based on different schedulings hitting the
compare error or not [1].

FYI here's LVish:

    http://www.cs.indiana.edu/~rrnewton/haddock/lvish/
    https://github.com/iu-parfunc/lvars

(More info in this POPL paper:
http://www.cs.indiana.edu/~rrnewton/papers/2013_07_LVish_quasiDet_working_draft.pdf
)

   -Ryan

[1] If you're curious why this happens, its because the Ord instance is
used by, say, Data.Set and Data.Map for the keys.  If you're inserting
elements in an arbitrary order, the final contents ARE deterministic, but
the comparisons that are done along the way ARE NOT.



On Tue, Oct 1, 2013 at 4:13 PM, Ryan Newton <rrnewton at gmail.com> wrote:

> Hello all,
>
> Normally, we don't worry *too* much about incorrect instances of standard
> classes (Num, Eq, Ord) etc.  They make the user's program wrong, but they
> don't compromise the type system.
>
> Unfortunately, with the LVish parallel programming library we do have a
> situation where incorrect instances of Eq and Ord can cause the "types to
> lie".  In particular, something that claims to be a pure, non-IO type, can
> actually yield a different result on different runs, including throwing
> exceptions on some runs but not others.
>
> So what's the best way to lock down "SafeEq" and "SafeOrd" instances,
> taking control away from the user (at least with -XSafe is turned on)?
>
> We could derive our own SafeEq and SafeOrd instances based on
> GHC.Generics.  BUT, that only helps if we can forbid the user from writing
> their own incorrect Generics instances when Safe Haskell is turned on.  It
> looks like GHC.Generics is currently marked as "TrustWorthy":
>
>
> http://www.haskell.org/ghc/docs/7.4.1/html/libraries/ghc-prim-0.2.0.0/GHC-Generics.html
>
> So.... could we get GHC.Generics marked as "Unsafe" and enable some more
> limited interface that is "Trustworthy"?  (Allowing the user ONLY to do
> 'deriving Generic').
>
> This would be similar to the new policy in GHC 7.8 of only allowing
> derived Typeable instances...
>
>   -Ryan
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20131001/8caa5c25/attachment.htm>



More information about the Haskell-Cafe mailing list