Liberalny warunek pokrycia wprowadzony w GHC 7.7 łamie kod ważny w GHC 7.6

Pomysł

Piszę aDSL, który kompiluje się do Haskella.

Użytkownicy tego języka mogą definiować własne niezmienne struktury danych i powiązane funkcje. Przez skojarzoną funkcję mam na myśli funkcję, która należy do struktury danych. Na przykład użytkownik może pisać (w pseudokodzie „pytonicznym”):

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

(co jest równoważne poniższemu kodowi, ale pokazuje również, że powiązane funkcje są podobne do klas typów z założeniem otwartego świata):

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

W tym przykładziemethod1 jest funkcją powiązaną zVector typ danych i może być używany jakv.testid(5) (gdziev jest instancjąVector typ danych).

Tłumaczę taki kod na kod Haskella, ale mam problem, który próbuję rozwiązać przez długi czas.

Problem

Próbuję przenieść kod z GHC 7.6GHC 7.7 (wersja wstępna 7.8) (Można skompilować nowsze wersjeze źródeł). Kod działa doskonale pod GHC 7.6, ale nie działa pod GHC 7.7. Chcę zapytać, jak mogę to naprawić, aby działało w nowej wersji kompilatora?

Przykładowy kod

Zobaczmy uproszczoną wersję wygenerowanego przez mojego kompilatora kodu Haskella:

{-# 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

Kod kompiluje się i działa poprawnie z GHC 7.6. Kiedy próbuję skompilować go z GHC 7.7, otrzymuję następujący błąd:

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’

Błąd jest spowodowany nowymi regułami sprawdzania, jakie zależności funkcjonalne mogą zrobić, a mianowicieliberal coverage condition (o ile wiem, to jestcoverage condition zrelaksowany za pomocą-XUndecidableInstances)

Niektóre próby rozwiązania problemu

Próbowałem przezwyciężyć ten problem, zmieniając definicjęMethod1 do:

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

Który rozwiązuje problem z zależnościami funkcjonalnymi, ale potem linia:

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

nie jest już dozwolony, co powoduje błąd kompilacji (zarówno w wersji 7.6, jak i 7.7):

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

EDYTOWAĆ:

Nie jest też możliwe rozwiązanie tego problemu za pomocą rodzin typów (o ile wiem). Jeśli wymienimyMethod1 wpisz klasę i instancje z następującym kodem (lub podobnym):

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)

Otrzymalibyśmy oczywisty błądNot in scope: type variable ‛t1’, ponieważ rodziny typów nie zezwalają na używanie typów, które nie pojawiają się w LHS wyrażenia typu.

Ostatnie pytanie

Jak mogę sprawić, by ten pomysł działał w GHC 7.7? Znam to noweliberal coverage condition pozwala programistom GHC poczynić pewne postępy w sprawdzaniu typu, ale w jakiś sposób powinno być możliwe przeniesienie pomysłu działającego w wersji GHC 7.6 na nigdy kompilatora.

(bez zmuszania użytkownika mojego DSL do wprowadzania jakichkolwiek dalszych typów - wszystko do tej pory, jak instancje klas typu, genaryzuję za pomocą Template Haskell)

questionAnswers(1)

yourAnswerToTheQuestion