Advice for implementing GADTs?
Benjamin Redelings
benjamin.redelings at gmail.com
Fri Jul 29 16:07:25 UTC 2022
Hi,
I've been working on implementing the Haskell type system for my
specialized Haskell interpreter. I have now constructed a system that
can type-check and run Haskell code that contains explicit type
signatures, type constraints, and arbitrary-rank types.
I'm now thinking that I may need to implement GADTs -- i.e. constructors
that introduce local constraints, including equality constraints. I'm
looking at the paper "OutsideIn(X): Modular type inference with local
assumptions" from 2011. I have three questions about implementing GADTs
-- I'd be grateful for answers to any of them.
QUESTION 1: Are there any obviously important resources that I've
overlooked?
The 2011 OutsideIn paper mentions several previous papers that seem
quite helpful:
* Peyton Jones el at 2006. Simple Unification-based type inference for GADTs
* Schrijvers etal 2007. Towards open type functions for Haskell
* Peyton Jones et al 2004. Wobbly Types: etc.
* Schrijvers et al 2008. Type checking with open type functions.
* Shrijvers et al 2009. Complete and decidable type inference for GADTs
* Vytiniotis et al 2010. Let should not be generalized.
And of course the GHC source code. (I'm not looking at coercions at the
present time, because my type-checker translates to the plain lambda
calculus without type annotations, not system F or F_C. Hopefully I can
remedy this later...)
QUESTION 2: if my quick scan is correct, none of the papers mention the
GHC technique of determining untouchability by assigning "levels" to
type variables. Is there any written paper (outside the GHC sources)
that discusses type levels?
QUESTION 3: My impression is that:
(a) type variable levels were introduced in order to clarify which
MetaTyVars are "untouchable", but
(b) levels now also check that type variables do not escape their
quantification scope.
(c) levels can also be used to figure out which variables are free in
the type environment, and therefore should not be generalized over.
Does this sound right? I suspect that I might be wrong about the last
one...
Thanks again, and sorry for the long e-mail.
-BenRI
On 1/18/22 8:55 PM, Benjamin Redelings wrote:
>
> Hi,
>
> 1. I think I have clarified my problem a bit. It is actually not
> related to pattern bindings. Here's an example:
>
> h = let f c i = if i > 10 then c else g c 'b'
> g 'a' w = f 'b' 10
> g z w = z
> in (f 'a' (1::Int), f 'a' (1.0::Double))
>
> If I am understanding the Haskell type system correctly,
>
> * the definitions of f and g form a recursive group
>
> * the monomorphism restriction is not invoked
>
> * the inner binding (to f and g) leads to a local value environment (LVE):
>
> { f :: Char -> a -> Char; g :: Char -> Char -> Char }
>
> with predicates (Num a, Ord a)
>
> 2. In this situation, Typing Haskell in Haskell suggests that we
> should NOT apply the predicates to the environment because the type
> for g does not contain 'a', and would become ambiguous (section
> 11.6.2). Instead, we should only apply predicates to the environment
> if their type variables are present in ALL types in the current
> declaration group.
>
> Since the predicates (Num a, and Ord a) are not retained, then we
> cannot quantify over a.
>
> It seems like this should make `f` monomorphic in a, and thus we
> should not be able apply (f 'a') to both (1::Int) and (1::Double).
>
> Does that make any sense?
>
> 3. GHC, however, compiles this just fine. However, if I add "default
> ()", then it no longer compiles.
>
> 4. On further reflection, Typing Haskell in Haskell applies defaulting
> rules when evaluating each binding, and not just at the top level. So
> this might be part of where my code is going wrong.
>
> -BenRI
>
>
> On 1/15/22 11:09 AM, Benjamin Redelings wrote:
>> Hi,
>>
>> 1. I'm reading "A Static semantics for Haskell" and trying to code it
>> up. I came across some odd behavior with pattern bindings, and I was
>> wondering if someone could explain or point me in the right direction.
>>
>> Suppose you have the declaration
>>
>> (x,y) = ('a',2)
>>
>> My current code is yielding:
>>
>> x :: Num a => Char
>>
>> y :: Num a => a
>>
>> However, I notice that ghci gives x the type Char, with no
>> constraint, which is what I would expect. It also gives y the type
>> 'Num b => b', so I don't think it is defaulting a to Int here.
>>
>> The weird results from my code stem from rule BIND-PRED in Figure 15
>> of
>> https://homepages.inf.ed.ac.uk/wadler/papers/staticsemantics/static-semantics.ps
>>
>> E |- bind ~~> \dicts : theta -> monobinds in bind :
>> (LIE_{encl}, theta => LVE)
>>
>> Here theta = ( Num a ) and LVE = { x :: Char, y :: a }. So, theta =>
>> LVE is
>>
>> { x :: Num a => Char, y :: Num a => a }
>>
>> The obvious thing to do is avoid changing a type T to Num a => T if T
>> does not contain a. Also I'm not totally sure if that trick gets to
>> the bottom of the issue. However, the paper doesn't mention define
>> theta => LVE that way. Is there something else I should read on this?
>>
>> 2. If we just chop out predicates which mention variables not in the
>> type ( == ambiguous predicates?) then I'm not totally sure how to
>> create code for this.
>>
>> I would imagine that we have something like
>>
>> tup dn = ('a', fromInteger dn 2)
>>
>> x = case (tup dn) of (x,y) -> x
>>
>> y dn case (tup dn) of (x,y) -> y
>>
>> In this case its not clear where to get the `dn` argument of `tup`
>> from, in the definition of `x`. Can we pass in `undefined`? Should
>> we do something else?
>>
>> If anyone can shed light on this, I would be grateful :-)
>>
>> -BenRI
>>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20220729/96e1b386/attachment.html>
More information about the ghc-devs
mailing list