[Haskell-cafe] PROPOSAL: Record field type inference

John Meacham john at repetae.net
Wed Jun 4 07:03:01 UTC 2014


Yeah, I am familier with that, this is fairly orthogonal actually and
both can be used together to good effect.

This proposal is more about making records 'lightweight', as in, I
have a recursive function that takes 5 or so recursive values and they
all have to be passed as independent options (or a tuple) right now
which is error prone, by making a lightweight inferred record we get
named parameters that are infered just like they were listed as
options and CPR analysis will even ensure there is no run time
penalty, the fields will be expanded out as positional parameters
internally.

An issue with OverloadedRecordFields is that it relies on a lot of
type system complexity, This builds on the existing
DisambiguateRecordFields extension and simply removes the restriction
that the records with the same field names be defined in different
modules. since field names declared this way don't share a namespace
with functions this isn't an issue.

Notably,  everything to disambiguate fields can take place in the
renamer and the fields can be typechecked exactly as if they were top
level pattern bindings.

Another possible extension is allowing it to infer scoped type
variables as well for a parameterized record type. working on
something concrete for that with my jhc implementation, the issue is
that the record will have to be parameterized by a type to keep them
from escaping. Perhaps just a single type parameter that is
existentially instantiated, syntax being
    data R t = R {fa,fb,fc}
or putting the data declaration in a local where or let binding. but
that will require some more work. (and scoped type variables in jhc
are a little iffy at the moment as is)

    John

On Tue, Jun 3, 2014 at 11:33 PM, Carter Schonwald
<carter.schonwald at gmail.com> wrote:
> Hey John
> in some respects, this sounds like syntax sugar around
> https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields
> have you had a look at that? (its not quite merged into HEAD yet, but that
> due soon i'm told)
>
>
> On Wed, Jun 4, 2014 at 2:26 AM, John Meacham <john at repetae.net> wrote:
>>
>> This is also available as html at
>>
>> http://repetae.net/computer/jhc/record_inference.html
>>
>> Record Type Inference
>> =====================
>>
>> An extension to the named field mechanism that will greatly enhance the
>> utility of them when combined with the existing
>> `DisambiguateRecordFields`,
>> `RecordPuns`, and `RecordWildCards`.
>>
>> The proposal is to allow the types of record fields to be inferred by the
>> normal type inference engine. It would look like
>>
>> ~~~~ {.haskell}
>> data Rec = Rec {fieldA,fieldB,fieldC}
>>
>> f Rec { .. } = Rec { .. } where
>>     fieldA = True
>>     fieldB = 4
>> ~~~~
>>
>> This would infer the types `Bool`, `Int`, and `forall a . a` for the
>> fields of
>> the record constructor and `f :: Rec -> Rec` for f. For the purposes of
>> type
>> checking the fields are treated as monomorphic and not generalized but
>> defaulted like normal after typechecking the module. Other than infering
>> the
>> types of the record fields, the records have the normal syntax. The
>> extensions
>> `RecordPuns`, `RecordWildCards` and `DisambiguateRecordFields` will be
>> enabled
>> when record field inference is enabled.
>>
>> Selector functions will not be created for infered records, as in, the
>> names
>> are field labels and not functions. This means they do not share a
>> namespace
>> with functions and do not conflict with each other. Multiple records may
>> have
>> the same field names in the same module. This means the following is fine.
>>
>> ~~~~ {.haskell}
>> data Rec1 = Rec1 {input, withFoo, withoutFoo }
>> data Rec2 = Rec2 {input, withBar, withoutBar }
>>
>> f Rec1 { .. } = case input of
>>     [] -> Rec1 { .. }
>>     (x:xs) -> if hasFoo x
>>         then Rec1 { withFoo = x:withFoo, .. }
>>         else Rec1 { withoutFoo = x:withoutFoo, .. }
>> ~~~~
>>
>> Possible extensions
>> -------------------
>>
>> ### as-pattern disambiguation
>>
>> In order to make the disambiguation of record fields more useful without
>> relying on the type checker for disambiguation, We can declare that
>> variables
>> explicitly bound to a constsructor in a pattern match use that constructor
>> to
>> disambiguate fields for operations on the variable. This is a purely
>> syntactic
>> transformation that can happen before typechecking. It can be used as
>> follows.
>>
>> ~~~~ {.haskell}
>> -- use the input bound by a Rec1 to update the input bound by a Rec2
>> f r1 at Rec1 { input } r2 at Rec2 {} = case input of
>>     xs | any hasBar xs = f r1 { input = [] } r2 { input }
>> ~~~~
>>
>> ### Field label inference
>>
>> It is concievable that we may want to infer the fields themselves of a
>> record,
>> as in:
>>
>> ~~~~ {.haskell}
>> -- infer that R has the field labels bob and susan
>> data R = R { ..}
>> f x at R {bob} = R {susan = bob}
>> ~~~~
>>
>> In order to implement this, a pass through the file will collect every
>> field
>> label that is used with an explicit R constructor and treat the record as
>> if
>> it were declared with those names as infered fields.
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>



-- 
John Meacham - http://notanumber.net/


More information about the Haskell-Cafe mailing list