Skip to content

GitLab

  • Menu
Projects Groups Snippets
  • Help
    • Help
    • Support
    • Community forum
    • Submit feedback
  • Sign in / Register
  • GHC GHC
  • Project information
    • Project information
    • Activity
    • Labels
    • Members
  • Repository
    • Repository
    • Files
    • Commits
    • Branches
    • Tags
    • Contributors
    • Graph
    • Compare
    • Locked Files
  • Issues 4,859
    • Issues 4,859
    • List
    • Boards
    • Service Desk
    • Milestones
    • Iterations
  • Merge requests 453
    • Merge requests 453
  • CI/CD
    • CI/CD
    • Pipelines
    • Jobs
    • Schedules
    • Test Cases
  • Deployments
    • Deployments
    • Releases
  • Analytics
    • Analytics
    • Value stream
    • CI/CD
    • Code review
    • Insights
    • Issue
    • Repository
  • Wiki
    • Wiki
  • Snippets
    • Snippets
  • Activity
  • Graph
  • Create a new issue
  • Jobs
  • Commits
  • Issue Boards
Collapse sidebar
  • Glasgow Haskell Compiler
  • GHCGHC
  • Issues
  • #8634
Closed
Open
Created Dec 27, 2013 by danilo2@trac-danilo2

Relax functional dependency coherence check ("liberal coverage condition")

Abstract

Hi! I'm writing a compiler, which produces Haskell code. I've discovered it is impossible to keep currently used features / logic using GHC 7.7 instead of 7.6

Below is more detailed description of the problem:

The idea

I'm writing a [DSL][1], which compiles to Haskell.

Users of this language can define own immutable data structures and associated functions. By associated function I mean a function, which belongs to a data structure. For example, user can write (in "pythonic" pseudocode):

  data Vector a:
      x,y,z :: a
      def method1(self, x):
          return x

(which is equivalent to the following code, but shows also, that associated functions beheva like type classes with open world assumption):

    data Vector a:
      x,y,z :: a
    def Vector.method1(self, x):
      return x

In this example, method1 is a function associated with Vector data type, and can be used like v.testid(5) (where v is instance of Vector data type).

I'm translating such code to Haskell code, but I'm facing a problem, which I'm trying to solve for a long time.

The problem

I'm trying to move the code from GHC 7.6 over GHC 7.7. The code works perfectly under GHC 7.6, but does not under GHC 7.7. I want to ask you how can I fix it to make it working in the new version of the compiler?

Example code

Lets see a simplified version of generated (by my compiler) Haskell code:

    {-# LANGUAGE FlexibleInstances #-}
    {-# LANGUAGE ScopedTypeVariables #-}
    {-# LANGUAGE TypeFamilies #-}
    {-# LANGUAGE UndecidableInstances #-}
    {-# LANGUAGE FunctionalDependencies #-}
    
    import Data.Tuple.OneTuple

    ------------------------------
    -- data types
    ------------------------------
    data Vector a = Vector {x :: a, y :: a, z :: a} deriving (Show)
    -- the Vector_testid is used as wrapper over a function "testid". 
    newtype Vector_testid a = Vector_testid a

    ------------------------------
    -- sample function, which is associated to data type Vector
    ------------------------------
    testid (v :: Vector a) x = x

    ------------------------------
    -- problematic function (described later)
    ------------------------------
    testx x = call (method1 x) $ OneTuple "test"

    ------------------------------
    -- type classes
    ------------------------------
    -- type class used to access "method1" associated function
    class Method1 cls m func | cls -> m, cls -> func where 
        method1 :: cls -> m func
  
    -- simplified version of type class used to "evaluate" functions based on 
    -- their input. For example: passing empty tuple as first argument of `call` 
    -- indicates evaluating function with default arguments (in this example 
    -- the mechanism of getting default arguments is not available)
    class Call a b where
        call :: a -> b

    ------------------------------
    -- type classes instances
    ------------------------------
    instance (out ~ (t1->t1)) => Method1 (Vector a) Vector_testid out where
      method1 = (Vector_testid . testid)
    
    instance (base ~ (OneTuple t1 -> t2)) => Call (Vector_testid base) (OneTuple t1 -> t2) where
        call (Vector_testid val) = val
    
    ------------------------------
    -- example usage
    ------------------------------
    main = do
        let v = Vector (1::Int) (2::Int) (3::Int)
        -- following lines equals to a pseudocode of ` v.method1 "test" `
        -- OneTuple is used to indicate, that we are passing single element.
        -- In case of more or less elements, ordinary tuples would be used.
        print $ call (method1 v) $ OneTuple "test"
        print $ testx v

The code compiles and works fine with GHC 7.6. When I'm trying to compile it with GHC 7.7, I'm getting following error:

    debug.hs:61:10:
        Illegal instance declaration for
          ‛Method1 (Vector a) Vector_testid out’
          The liberal coverage condition fails in class ‛Method1’
            for functional dependency: ‛cls -> func’
          Reason: lhs type ‛Vector a’ does not determine rhs type ‛out’
        In the instance declaration for
          ‛Method1 (Vector a) Vector_testid out’

The error is caused by new rules of checking what functional dependencies can do, namely liberal coverage condition (as far as I know, this is coverage condition relaxed by using -XUndecidableInstances)

Some attemps to fix the problem

I was trying to overcome this problem by changing the definition of Method1 to:

    class Method1 cls m func | cls -> m where 
        method1 :: cls -> m func

Which resolves the problem with functional dependencies, but then the line:

    testx x = call (method1 x) $ OneTuple "test"

is not allowed anymore, causing a compile error (in both 7.6 and 7.7 versions):

    Could not deduce (Method1 cls m func0)
      arising from the ambiguity check for ‛testx’
    from the context (Method1 cls m func,
                      Call (m func) (OneTuple [Char] -> s))
      bound by the inferred type for ‛testx’:
                 (Method1 cls m func, Call (m func) (OneTuple [Char] -> s)) =>
                 cls -> s
      at debug.hs:50:1-44
    The type variable ‛func0’ is ambiguous
    When checking that ‛testx’
      has the inferred type ‛forall cls (m :: * -> *) func s.
                             (Method1 cls m func, Call (m func) (OneTuple [Char] -> s)) =>
                             cls -> s’
    Probable cause: the inferred type is ambiguous

It is also impossible to solve this issue using type families (as far as I know). If we replace Method1 type class and instances with following code (or simmilar):

    class Method1 cls m | cls -> m where 
        type Func cls
        method1 :: cls -> m (Func cls)
    
    instance Method1 (Vector a) Vector_testid where
        type Func (Vector a) = (t1->t1)
        method1 = (Vector_testid . testid)

We would get obvious error Not in scope: type variable ‛t1’, because type families does not allow to use types, which does not appear on LHS of type expression.

The final question

How can I make this idea work under GHC 7.7? I know the new liberal coverage condition allows GHC devs make some progress with type checking, but it should somehow be doable to port idea working in GHC 7.6 over never compiler version.

(without forcing user of my DSL to introduce any further types - everything so far, like type class instances, I'm genarating using Template Haskell)

Maybe is there a way to indroduce an extension, which will disable liberal coverage condition in such situations?

There is also a StackOverflow discussion available, here: http://stackoverflow.com/questions/20778588/liberal-coverage-condition-introduced-in-ghc-7-7-breaks-code-valid-in-ghc-7-6

[1]: http://en.wikipedia.org/wiki/Domain-specific_language

Trac metadata
Trac field Value
Version 7.7
Type Bug
TypeOfFailure OtherFailure
Priority high
Resolution Unresolved
Component Compiler
Test case
Differential revisions
BlockedBy
Related
Blocking
CC
Operating system
Architecture
Edited Mar 09, 2019 by Richard Eisenberg
To upload designs, you'll need to enable LFS and have an admin enable hashed storage. More information
Assignee
Assign to
Time tracking