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 #-}
import GHC.OverloadedLabels
newtype Text = Text { getText :: String } deriving Show
data Person = Person { _id :: Int , _name :: String }
instance IsLabel "name" (Person -> String) where
instance IsLabel symbol (Person -> String) => IsLabel symbol (Person -> Text) where
fromLabel _ = Text . fromLabel (proxy# :: (Proxy# (Person -> String)))
person = Person 123 "Horace"
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?