[Haskell-cafe] Some thoughts on Type-Directed Name Resolution

Kevin Quick quick at sparq.org
Thu Feb 2 08:11:03 CET 2012


On Wed, 01 Feb 2012 19:42:19 -0700, AntC <anthony_clayden at clear.net.nz>  
wrote:

> A piece of background which has perhaps been implicit in the discussions  
> up to
> now. Currently under H98:
>        f.g    -- (both lower case, no space around the dot)
> Is taken as function composition -- same as (f . g).
>        f.  g  -- is taken as func composition (f . g)
>        f  .g  -- is taken as func composition (f . g)

And so it is.  Could have sworn these weren't accepted, but clearly I'm  
wrong.  Thanks for pointing this out.

> All proposals are saying that if you want to use dot as function  
> composition
> you must always put the spaces round the dot (or at least between the  
> dot and
> any name) -- even if you're part-applying. So:
>       (f .)   -- part-apply function composition on f
>       (. g)   -- part-apply function composition

+1

> "SOPR"? SPJ's current proposal is abbreviated as "SORF" (Simple  
> Overloaded
> Record Fields).

Yes, I caught this 5 minutes *after* hitting send (of course).

> In these examples you're giving, I assume recs is a list of records(?).

Yes.  I err'd on the side of brevity.

>>
>> ...
>
> In the "RHCT" examples, I assume r is a record, f is a field (selector
> function) -- or is it 'just some function'?

It should be a field selector.

>> RHCT:      map (\r -> f r) recs
> is the same as:  map f recs                -- by eta reduction
> so map f takes a list of records, returns a list of the f field from each
> This also works under H98 record fields, with type enforcement that the
> records must be of the single type f comes from.
>
>> RHCT:      map (\r -> r.$rev_ f) recs
> Beware that (.$) is an operator, so it binds less tightly than function
> application, so it's a poor 'fake' syntactically. Did you mean .$ to  
> simulate
> dot-notation to extract field rev_ from r?

Sort of.  I didn't fully grasp your implemenation and based on your  
clarification I think I should have written:

     map (\r -> r.$f) recs

to extract field f from a single record r (from the recs collection).

>
>> RHCT:      map ((.$)f) recs
> If you mean this to return a list of the f fields from recs, put:
>              map f recs
> I don't know what else you could be trying to do.

I was trying to eta-reduce my previous (corrected) situation *but* also  
indicate that I specifically want the field selector rather than some  
arbitrary f.  I wanted to extract the field f of every record in recs but  
clearly indicate that f was a field selector and not a free function.

>> If partial application is allowed (against SPJ's inclination and  
>> explicitly
>> disallowed in your scheme), I could have:
>>
>>     map .f recs
>
> If you mean this to return a list of the f fields from recs, put:
> DORF:          map f recs        -- are you beginning to see how easy  
> this is?
>
> I'm saying the ".f" should be rejected as too confusing.
> (That is, under DORF aka RHCT. Under SORF or TDNR I'm not sure, which is  
> why I
> don't like their proposals for dot notation, which is why I  
> re-engineered it
> so that dot notation is tight-binding reverse function application **and
> nothing more**.)

And this is finally our difference.  I had wanted the no-space preceeding  
dot syntax (.f) to specifically indicate I was selecting a field.  This  
desire was based on expectations of partial application and being unaware  
of the H98 valid interpretation of this as partial function application. I  
think perhaps I was overly concerned on this point though.  The issue can  
be resolved by explicit module namespace notation (ala. Prelude.map v.s.  
Data.List.map).

In addition, under SORF, SPJ indicated that "Dot notation must work in  
cascades (left-associatively), and with an expression to the left:
   r.x
   r.x.y
   (foo v).y
"
I assume DORF would also support this as well and that "r.x.y.z" would  
desugar to "z (y (x r))".

With regards to module namespace notation, neither SORF nor DORF mentions  
anything that I found, but I'm assuming that the assertion is that it's  
not needed because of the type-directed resolution.  To wit:

Rlib/Recdef.hs:
>     module Rlib.Recdef (R(..)) where
>
>     data Rec = R { foo :: String } deriving Show

Rlib/Rong.hs:
>     module Rong (T(..)) where
>     import Rlib.Recdef
>     data Rstuff = T { baz :: R }
>
>     foo :: Rec -> String
>     foo = show

main.hs:
>     import Rlib.Recdef
>     import Rlib.Rong
>     main = let r = R "hi"
>                t = T r
>                bar, bar_pf :: Rstuff -> String
>                bar_pf = Rlib.Recdef.foo . Rlib.Rong.baz
>                bar x = x.baz.foo
>            in assert $ bar_pf t == bar t
>               assert $ Rlib.Rong.foo r /= Rlib.Recdef.foo r

The assumptions are that the syntax of bar and bar_pf would be the same  
for both SORF and DORF, and that no namespace qualifiers are needed (or  
allowed) for bar  (i.e. you wouldn't write something like "bar x =  
x.Rlib.Rong.baz.Rlib.Recdef.foo").

Apologies for putting you through the syntax grinder, and especially when  
I'm not really qualified to be operating said grinder.  I know it's not  
the interesting part of the work, but it's still a part.

Thanks, Anthony!

-Kevin

-- 
-KQ



More information about the Haskell-Cafe mailing list