[GHC] #8634: Relax functional dependency coherence check ("liberal coverage condition")

GHC ghc-devs at haskell.org
Tue Sep 2 20:27:16 UTC 2014


#8634: Relax functional dependency coherence check ("liberal coverage condition")
-------------------------------------+-------------------------------------
              Reporter:  danilo2     |            Owner:
                  Type:  feature     |           Status:  new
  request                            |        Milestone:  7.10.1
              Priority:  high        |          Version:  7.7
             Component:  Compiler    |         Keywords:
            Resolution:              |     Architecture:  Unknown/Multiple
      Operating System:              |       Difficulty:  Unknown
  Unknown/Multiple                   |       Blocked By:
       Type of failure:              |  Related Tickets:  #1241, #2247,
  None/Unknown                       |  #8356, #9103, #9227
             Test Case:              |
              Blocking:              |
Differential Revisions:  Phab:D69    |
-------------------------------------+-------------------------------------

Comment (by neo):

 Hi! I'm not sure if I face the same problem as the issue author or if my
 code is just "wrong" but when testing my code with GHC 7.8 I get the
 [https://travis-ci.org/adp-multi/adp-multi/jobs/34132805#L437 same error]
 while it worked with 7.6. My library ([https://hackage.haskell.org/package
 /adp-multi adp-multi]) is a parsing library for running dynamic
 programming algorithms with sequences as input (used in bioinformatics to
 fold RNA secondary structures). The grammar is defined as a DSL where some
 syntax sugar is defined using type class instances. One of the two
 problematic instances is the following (simplified):

 {{{
 {-# LANGUAGE FunctionalDependencies #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE MultiParamTypeClasses #-}
 {-# LANGUAGE UndecidableInstances #-}
 {-# LANGUAGE DeriveDataTypeable #-}

 -- | To support higher dimensions, a subword is a list
 --   of indices. Valid list lengths are 2n with n>0.
 type Subword = [Int]

 type Parser a b = Array Int a   -- ^ The input sequence
                -> Subword       -- ^ Subword of the input sequence to be
 parsed
                -> [b]           -- ^ Parsing results

 class Parseable p a b | p -> a b where
     toParser :: p -> Parser a b

 data EPS = EPS deriving (Eq, Show, Data, Typeable)
 empty1 :: Parser a EPS
 empty1 _ [i,j] = [ EPS | i == j ]

 instance Parseable EPS a EPS where
     toParser _ = empty1
 }}}

 See [https://github.com/adp-multi/adp-
 multi/blob/0.2.3/src/ADP/Multi/ElementaryParsers.hs#L152 here] and
 [https://github.com/adp-multi/adp-multi/blob/0.2.3/src/ADP/Multi/Parser.hs
 here] for the full code.

 The error with 7.8 is:
 {{{
 Illegal instance declaration for ‘Parseable EPS a EPS’
   The liberal coverage condition fails in class ‘Parseable’
     for functional dependency: ‘p -> a b’
   Reason: lhs type ‘EPS’ does not determine rhs types ‘a’, ‘EPS’
 In the instance declaration for ‘Parseable EPS a EPS’
 }}}

 The other problematic instance is basically the same but for 2D inputs.

 In essence I want the empty word parser empty1 to work for any input type,
 e.g. for a char but also a number (which would then be a list of chars or
 numbers as the input sequence). Am I doing something terribly wrong or
 does this ticket also apply to me?

--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/8634#comment:46>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list