[Haskell-cafe] Playing with OverloadedLabels in GHC 8 RC2, how to do this?

Daniel Díaz diaz.carrete at gmail.com
Tue Feb 23 22:07:17 UTC 2016


It works, thanks!

I was wondering: if I define a bunch of records in a module, how to make 
this the behaviour for all records in the module, without much boilerplate 
and without affecting any records elsewhere?

One possible solution would be to define a empty type class that will not 
be exported:

class Marker r


and the following instance:

instance (Marker r,IsLabel symbol (r -> String)) => IsLabel symbol (r -> 
Text) where
    fromLabel _ =  Text . fromLabel (proxy# :: (Proxy# symbol))


And make every record in the module an instance of Marker:

instance Marker Person


I'm not sure if there's a simpler way.

Even if we don't export the fields directly, another way to employ 
OverloadedLabels (OverloadedRecordFields, once it arrives) is for giving 
default implementations of public interfaces, in combination with 
DefaultSignatures. A not very useful example:

class Named r where
    name :: r -> String      
    default name :: IsLabel "name" (r -> String) => r -> String
    name = #name


           instance Named Person

On Tuesday, February 23, 2016 at 10:16:21 AM UTC+1, Adam Gundry wrote:
>
> Hi, 
>
> The type of `fromLabel` is 
>
>     forall (x :: Symbol) a . IsLabel x a => Proxy# x -> a 
>
> where `x` represents the text of the label, so rather than applying it to 
>
>     (proxy# :: (Proxy# (Person -> String))) 
>
> you need to apply it to 
>
>     (proxy# :: Proxy# symbol) 
>
> and you will need to turn on the ScopedTypeVariables extension (so that 
> `symbol` refers to the variable bound in the class instance). With that 
> change, your program works. 
>
> That's a truly atrocious error message though. It's marginally better if 
> you enable -fprint-explicit-kinds: 
>
>     • Expected kind ‘Proxy# GHC.Types.Symbol ((->) Person String)’, 
>         but ‘proxy# :: Proxy# (Person -> String)’ has kind 
>           ‘Proxy# * (Person -> String)’ 
>
> This shows the real problem, namely that you have `Proxy# *` instead of 
> `Proxy# Symbol`. However, `Proxy# Symbol ((->) Person String)` is 
> blatantly ill-kinded, so the error message doesn't make much sense. I 
> suggest you file a GHC ticket, if there isn't a suitable one already. 
>
> Hope this helps, 
>
> Adam 
>
>
> On 23/02/16 08:29, Daniel Díaz wrote: 
> > Hi all, 
> > 
> > I'm playing with the OverloadedLabels extension in GHC 8 RC2. I have 
> > been able to define simple record accessors, like in this 
> > gist: https://gist.github.com/danidiaz/3b9a6865686c777f328c 
> > 
> > After realizing than with OverloadedLabels a single symbol can be used 
> > to extract two different types from the same record, I tried to define 
> > an instance that says: "if a symbol can be used to extract an string 
> > from my record, then it can also be used to extract that a Text value". 
> > 
> > Here's my attempt (using a dummy Text type): 
> > 
> >     {-# LANGUAGE OverloadedLabels #-} 
> >     {-# LANGUAGE DataKinds #-} 
> >     {-# LANGUAGE FlexibleInstances #-} 
> >     {-# LANGUAGE FlexibleContexts #-} 
> >     {-# LANGUAGE UndecidableInstances #-} 
> >     {-# LANGUAGE MultiParamTypeClasses #-} 
> >     {-# LANGUAGE MagicHash #-} 
> >     module Main where 
> > 
> >     import GHC.OverloadedLabels 
> >     import GHC.Prim 
> > 
> >     newtype Text = Text { getText :: String } deriving Show 
> > 
> >     data Person = Person { _id :: Int ,  _name :: String } 
> > 
> >     instance IsLabel "name" (Person -> String) where 
> >         fromLabel _ =  _name 
> > 
> >     instance IsLabel symbol (Person -> String) => IsLabel symbol (Person 
> >     -> Text) where 
> >         fromLabel _ =  Text . fromLabel (proxy# :: (Proxy# (Person -> 
> >     String))) 
> > 
> >     person :: Person 
> >     person = Person 123 "Horace" 
> > 
> >     main :: IO () 
> >     main = do 
> >         print (#name person :: String) 
> >         print (#name person :: Text) 
> > 
> > 
> > Bu this doesn't work. The error I get is puzzling: 
> > 
> >         • Expected kind ‘Proxy# ((->) Person String)’, 
> >             but ‘proxy# :: Proxy# (Person -> String)’ has kind ‘Proxy# 
> >     (Person -> String)’ 
> >         • In the first argument of ‘fromLabel’, namely 
> >             ‘(proxy# :: Proxy# (Person -> String))’ 
> > 
> > 
> > Is this a bug? What is going on here? 
>
>
> -- 
> Adam Gundry, Haskell Consultant 
> Well-Typed LLP, http://www.well-typed.com/ 
> _______________________________________________ 
> Haskell-Cafe mailing list 
> Haskel... at haskell.org <javascript:> 
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe 
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20160223/b45322b7/attachment.html>


More information about the Haskell-Cafe mailing list