[GHC] #7633: Checkable "minimal complete definitions"

#7633: Checkable "minimal complete definitions" -----------------------------+---------------------------------------------- Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: 6028 -----------------------------+---------------------------------------------- #6028 suggested warning on cyclic unimplemented defaults. This doesn't work for the reasons mentioned there, among others (also e.g. [http://hackage.haskell.org/packages/archive/base/4.6.0.0/doc/html /Control-Applicative.html#g:2 `Alternative`] has mutually recursive `some` and `many` methods, which shouldn't be warned about). Figuring out when to warn automatically seems hard. But Haskell already has an ad-hoc mechanism for specifying which methods need to be implemented: A "minimal complete definition" specified in the comments of almost every class definition that has optional methods. Unfortunately comments are aren't compiler-checked. It seems that the simplest solution would be to specify these in a way that the compiler can understand. The obvious approach is to add a pragma for it in the class definition. In particular, one could write a pragma for each "minimal set" of definitions, and the compiler could warn if none of them are implemented (and suggest which methods to implement). This lets us keep the convenience of default method implementations without losing safety. Without any pragmas, the compiler could fall back to the set "all methods without defaults", which is what it uses now. It might look something like this: {{{ class Functor m => Monad m where return :: a -> m a (>>=) :: m a -> (a -> m b) -> m b m >>= f = join (fmap f m) join :: m (m a) -> m a join m = m >>= id {-# MINIMAL return, join #-} {-# MINIMAL return, (>>=) #-} class Eq a where (==), (/=) :: a -> a -> Bool x == y = not (x /= y) x /= y = not (x == y) {-# MINIMAL (==) #-} {-# MINIMAL (/=) #-} }}} -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" -----------------------------+---------------------------------------------- Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Component: Compiler Version: 7.6.1 | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Blockedby: Blocking: | Related: 6028 -----------------------------+---------------------------------------------- Changes (by goldfire): * cc: eir@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by simonpj): * difficulty: => Unknown Comment: It's a bit ad hoc, but probably a jolly useful feature. Nothing technically hard about implementing it. If anyone wants to have a go, I'm happy to advise. Simon -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by byorgey): * cc: byorgey@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by igloo): * milestone: => 7.8.1 -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by dmwit): * cc: daniel@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by hvr): * cc: hvr@… (added) -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Changes (by Lemming): * cc: ghc@… (added) Comment: I would prefer that the minimal implementation specification is a logical expression consisting of ANDs and ORs. This way we can better show, what has to be implemented always and where choices exist. That is, instead of {{{ {-# MINIMAL return, join #-} {-# MINIMAL return, (>>=) #-} }}} I prefer {{{ {-# MINIMAL return AND (join OR (>>=)) #-} }}} I also wonder whether it is possible for GHC to make some plausibility checks. E.g., if a method has no default implementation and is not mentioned in the MINIMAL specification, this should cause a warning. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

E.g., if a method has no default implementation and is not mentioned in
#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Comment(by hvr): the MINIMAL specification, this should cause a warning. Wouldn't this require ''all'' no-default-implementation carrying methods to be mentioned in the MINIMAL specification? -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Comment(by dmwit): This might be a bit of feature creep, but I thought I would try to archive a bit of #haskell discussion: it might be worth thinking about how to do cross-class MINIMAL pragmas. For example, imagine a world where we had something like this: {{{ {-# LANGUAGE DefaultSignatures #-} class Functor f where fmap :: (a -> b) -> (f a -> f b) default fmap :: Traversable f => (a -> b) -> (f a -> f b) fmap = getId . traverse (Id . f) class Functor f => Traversable f where traverse :: Applicative f => (a -> f b) -> t a -> f (t b) traverse f = sequenceA . fmap f sequenceA :: Applicative f => t (f a) -> f (t a) sequenceA = traverse id }}} I might like to be able to say that either "fmap and sequenceA" or "traverse" are okay minimal definitions for the two classes together. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Comment(by simonpj): twanl: your points are valid, but I still vote for putting it in `Sig`. The `SPECIALISE instance` pragmas for an instance decl are in `Sig`, for example (`SpecInstSig` constructor). And `GenericSig` is valid only in a class decl, and nowhere else. It's true that, as a result, the `Sig` data type isn't as precise as it could be, but lumping them together reduces the number of fields, arguments, and plumbing. A judgement call, I agree, but doing it this way would be consistent with what we have. Once we get all the way to a `Class`, then indeed we need a special purpose field. I'm only talking about `HsSyn`. -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" ---------------------------------+------------------------------------------ Reporter: shachaf | Owner: Type: feature request | Status: patch Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Keywords: | Os: Unknown/Multiple Architecture: Unknown/Multiple | Failure: None/Unknown Difficulty: Unknown | Testcase: Blockedby: | Blocking: Related: 6028 | ---------------------------------+------------------------------------------ Comment(by simonpj): dmwit: yes, I think this is feature creep :-). -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:22 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#7633: Checkable "minimal complete definitions" -------------------------------+-------------------------------------------- Reporter: shachaf | Owner: Type: feature request | Status: new Priority: normal | Milestone: 7.8.1 Component: Compiler | Version: 7.6.1 Resolution: | Keywords: Os: Unknown/Multiple | Architecture: Unknown/Multiple Failure: None/Unknown | Difficulty: Unknown Testcase: | Blockedby: Blocking: | Related: 6028 -------------------------------+-------------------------------------------- Changes (by igloo): * status: patch => new -- Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7633#comment:23 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (2)
-
GHC
-
GHC