
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/