higher kind in parametric type

Dear cafe, I am writing a library for parsing higher-kinded data, based on the czipwith package [1]. I ran into the following problem. I have a type class class Config p f | f -> p where f :: (* -> *) -> * is the higher-kinded data and p :: * -> * is the associated parser type. I want to add a class member that does not mention f in its type, e.g. heading :: p String Naturally, this would lead to ambiguity checks to fail, as the usage of heading does not tell which Config instance to use. My usual workaround would be to wrap `heading` in a phantom type, e.g. data Heading f p = Heading (p String) and give `heading` the type Heading f p. However, ghc-8.0.2 complains about f not being a type: • Expecting one more argument to ‘f’ Expected a type, but ‘f’ has kind ‘(* -> *) -> *’ • In the first argument of ‘Heading’, namely ‘f’ In the type signature: heading :: Heading f p In the class declaration for ‘Config’ Is there a restriction of the kinds that can be used in parametric types? Cheers, Olaf [1] http://hackage.haskell.org/package/czipwith

Olaf Klinke
Dear cafe,
I am writing a library for parsing higher-kinded data, based on the czipwith package [1]. I ran into the following problem.
I have a type class class Config p f | f -> p where f :: (* -> *) -> * is the higher-kinded data and p :: * -> * is the associated parser type.
I want to add a class member that does not mention f in its type, e.g.
heading :: p String
Naturally, this would lead to ambiguity checks to fail, as the usage of heading does not tell which Config instance to use. My usual workaround would be to wrap `heading` in a phantom type, e.g. data Heading f p = Heading (p String) and give `heading` the type Heading f p. However, ghc-8.0.2 complains about f not being a type:
• Expecting one more argument to ‘f’ Expected a type, but ‘f’ has kind ‘(* -> *) -> *’ • In the first argument of ‘Heading’, namely ‘f’ In the type signature: heading :: Heading f p In the class declaration for ‘Config’
Is there a restriction of the kinds that can be used in parametric types?
Cheers, Olaf
I think you can just a kind signature to 'f' in your Heading datatype. I.e. the following seems to compile/typecheck here: {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-} newtype Heading (f :: k) (p :: * -> *) = Heading (p String) class Config (p :: * -> *) (f :: (* -> *) -> *) | f -> p where foo :: Heading f p -> String -- - Frank

Am 11.07.2018 um 16:31 schrieb Frank Staals
: Olaf Klinke
writes: Dear cafe,
I am writing a library for parsing higher-kinded data, based on the czipwith package [1]. I ran into the following problem.
I have a type class class Config p f | f -> p where f :: (* -> *) -> * is the higher-kinded data and p :: * -> * is the associated parser type.
I want to add a class member that does not mention f in its type, e.g.
heading :: p String
Naturally, this would lead to ambiguity checks to fail, as the usage of heading does not tell which Config instance to use. My usual workaround would be to wrap `heading` in a phantom type, e.g. data Heading f p = Heading (p String) and give `heading` the type Heading f p. However, ghc-8.0.2 complains about f not being a type:
• Expecting one more argument to ‘f’ Expected a type, but ‘f’ has kind ‘(* -> *) -> *’ • In the first argument of ‘Heading’, namely ‘f’ In the type signature: heading :: Heading f p In the class declaration for ‘Config’
Is there a restriction of the kinds that can be used in parametric types?
Cheers, Olaf
I think you can just a kind signature to 'f' in your Heading datatype. I.e. the following seems to compile/typecheck here:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-}
newtype Heading (f :: k) (p :: * -> *) = Heading (p String)
class Config (p :: * -> *) (f :: (* -> *) -> *) | f -> p where foo :: Heading f p -> String
You solved it, Frank, thanks a lot! Actually, it seems that this line makes all the difference: {-# LANGUAGE PolyKinds #-} In ghc-7.4.2 my code compiles with the pragma, and yields the above error message without. Usually the compiler is kind enough to suggest adding the language extension when encountering an error. This time it didn't. Maybe this is a case for the ghc developers? Olaf

It seems to work with the latest GHC (8.4.3). GHC 7.4.2 is six years old :) On 07/11/2018 02:15 PM, Olaf Klinke wrote:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-}
newtype Heading (f :: k) (p :: * -> *) = Heading (p String)
class Config (p :: * -> *) (f :: (* -> *) -> *) | f -> p where foo :: Heading f p -> String

On 07/11/2018 03:15 PM, Olaf Klinke wrote:
Am 11.07.2018 um 16:31 schrieb Frank Staals
: I think you can just a kind signature to 'f' in your Heading datatype. I.e. the following seems to compile/typecheck here:
{-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE PolyKinds #-}
newtype Heading (f :: k) (p :: * -> *) = Heading (p String)
class Config (p :: * -> *) (f :: (* -> *) -> *) | f -> p where foo :: Heading f p -> String
You solved it, Frank, thanks a lot!
Actually, it seems that this line makes all the difference: {-# LANGUAGE PolyKinds #-}
In ghc-7.4.2 my code compiles with the pragma, and yields the above error message without. Usually the compiler is kind enough to suggest adding the language extension when encountering an error. This time it didn't. Maybe this is a case for the ghc developers?
Hello, There is also a solution without the PolyKinds extension: newtype Heading (f :: (* -> *) -> *) (p :: * -> *) = ... I think the error message could be improved here but should probably not recommend the PolyKinds extension because it has a few surprising behaviors (IIRC it can break existing code, though I don't have an example off-hand). A safer alternative is to encourage kind annotations on higher-kinded types, that also mirrors the existing practice of giving signatures to toplevel functions. Li-yao
participants (4)
-
Frank Staals
-
Li-yao Xia
-
Olaf Klinke
-
Vanessa McHale