Promoting complex GADTs - haskell

I've been toying around with -XDataKinds recently, and was wondering why Foo below won't be automatically promoted:
{-# LANGUAGE
GADTs
, DataKinds
, KindSignatures #-}
import Data.HList
data Foo a where
Foo :: Bar a =>
a -> Foo a
data Baz where
Baz :: (a ~ HList (l :: [Foo *])) =>
a -> Baz
That is, Baz is a heterogenous list of Foo a's, where a is constrained by Bar.
Is there a way to manually create a promoted version of this data type? How would I go about doing so? Can kinds be declared? Could I make a dummy Haskell98 version of Foo, and separate it into a module or something? Ideally I'd like to keep the constraint context, but I don't think there's a Constraint sort. Any ideas would be very helpful!

Related

Haskell: interaction between ConstraintKinds, and TypeSynonymInstances

I'm getting an unexpected error when trying to compile a small Haskell file with GHC 8.6.1 when using ConstraintKinds and TypeSynonymInstances.
I'd like to make a class that takes a class as a parameter, and I'd like to use an alias when writing an instance. Here's the code:
{-# LANGUAGE ConstraintKinds, KindSignatures, TypeSynonymInstances #-}
module TypeAlias where
import Data.Kind
class Foo a
class Bar a
class Baz (c :: * -> Constraint)
instance Baz Foo -- compiles
instance Baz Bar -- compiles
type FooBar a = (Foo a, Bar a) -- compiles
instance Baz FooBar -- fails!
-- TypeAlias.hs:17:10-19: error:
-- • The type synonym ‘FooBar’ should have 1 argument, but has been given none
-- • In the instance declaration for ‘Baz FooBar’
-- |
-- 17 | instance Baz FooBar
-- | ^^^^^^^^^^
The error is surprising because, as far as I can tell, FooBar has the expected kind, namely * -> Constraint, but the compiler says it should be fed an argument.
Is it even possible to use a constraint alias in an instance declaration as I am trying here? If so, how do I make sense of the seemingly contradictory error message?
(I know I can simply declare FooBar as a class instead of an alias, but I really don't want to because I'd also want an instance and at that point I'd have to pull in UndecidableInstances.)
Turns out, Ed Kmett answered my question a year ago. I can't do it with type aliases, but using UndecidableInstances should be benign for this particular situation:
https://www.reddit.com/r/haskell/comments/5zjwym/when_is_undecidableinstances_okay_to_use/
Here's how Kmett might suggest fixing the above example:
{-# LANGUAGE ConstraintKinds, FlexibleInstances,
KindSignatures, UndecidableInstances #-}
module NotTypeAlias where
import Data.Kind
class Foo a
class Bar a
class Baz (c :: * -> Constraint)
instance Baz Foo -- compiles
instance Baz Bar -- compiles
class (Foo a, Bar a) => FooBar a
instance (Foo a, Bar a) => FooBar a -- compiles
instance Baz FooBar -- compiles
Kmett argues that if the instance of FooBar we provide is the sole instance ever in scope, then the type checker won't fall into an infinite loop from our use of UndecidableInstances. I'm satisfied to take him at his word.

Haskell - GADTs pattern match with class constraints

Consider the following example
{-# LANGUAGE DataKinds, GADTs #-}
data Phantom = A | B
data Foo (a :: Phantom) where
FooA :: Foo 'A
FooB :: Foo 'B
class PhantomConstraint (a :: Phantom)
instance PhantomConstraint 'A -- Note: No instance for 'B
someFunc :: PhantomConstraint a => Foo a -> ()
someFunc FooA = ()
If I do something like this GHC complains that the pattern matches are inexhaustive for someFunc, however, if I do try and include the case for FooB (which I don't want to do for domain specific reasons) it complains that it can't deduce the instance of PhantomConstraint for Foo 'B
Is there any way to make GADT pattern matching aware of typeclass constraints such that it eliminates required arms of pattern matching?
EDIT: More details around what I want to do. I have a bucket of types that are all somewhat related but have different properties. In the OO world this is what people use subtyping and inheritance for. However in the FP community, the consensus seems to be that there is no real good way to do subtyping, so in this case I need to hack around it. As such I have a GADT that unifies all of the types, but with different parameters on that type. I then proceed to write different typeclasses and typeclass instances on the type parameters (enabled by datakinds, no term representation). I want to be able to express that some of these types from the datakinds have a property that others don't, but they all do share certain common properties so I don't really want to break up the type. The only other option I can foresee is to create a taxonomy on the type part, but then the DataKinds types get messed up.
I can't reproduce the issue. This loads without warnings or errors in GHCi 8.4.3.
{-# LANGUAGE GADTs, DataKinds, KindSignatures #-}
{-# OPTIONS -Wall #-}
module GADTwarning2 where
data Phantom = A | B
data Foo (a :: Phantom) where
FooA :: Foo 'A
FooB :: Foo 'B
class PhantomConstraint (a :: Phantom)
instance PhantomConstraint 'A -- Note: No instance for 'B
someFunc :: PhantomConstraint a => Foo a -> ()
someFunc FooA = ()
someFunc FooB = ()
As luqui explained in a comment, we can't avoid the FooB case, since type classes are open, and another instance could be added later on by another module, making the pattern match non exhaustive.
If you are absolutely sure you don't need any other instances except the one for A, you can try to use
class a ~ 'A => PhantomConstraint (a :: Phantom)
Or, if the index a can be 'A or 'B, but never a third constructor 'C, then we can try to reify this fact:
class PhantomConstraint (a :: Phantom) where
aIsAOrB :: Either (a :~: 'A) (a :~: 'B)
and then exploit this member later on.

How to make this example of pseudo-ducktyping type unambiguously without annotations

I wanted to demonstrate the idea of statically verifiable duck typing in Haskell using MultiParamTypeClasses, but I am having trouble avoiding type ambiguity.
Here is the code:
{-# LANGUAGE MultiParamTypeClasses #-}
class HasBar a b where
bar :: b -> a
data Foo = Foo { barBool :: Bool } deriving (Show)
instance HasBar Bool Foo where
bar = barBool
data Bazz = Bazz { barInt :: Int } deriving (Show)
instance HasBar Int Bazz where
bar = barInt
When I load it into GHCi and try to do bar (Foo True) or bar (Bazz 5) I get a Non type-variable argument error and it suggests FlexibleContexts, which just changes the error to an ambiguity error. Now doing something like False || bar (Foo True) works fine. But that doesn't seem like it should be needed as Foo is only a member of the typeclass that returns a Bool.
It seems like the issue is something to do with the possibility of something like:
instance HasBar Int Foo where
bar = const 5
Which would necessitate the types being ambiguous. But if there is just one instance I don't see why there are any issues preventing Haskell from finding out the type (do I need some sort of extension). If I can't do it that way then is there an alternative to MultiParamTypeClasses that only allows one instance and would allow for this pseudo-ducktyping type of thing to work?
the problem is that it's not only looking for what it sees but what it can know - and there is the possibility for you to make an instance that will be HasBar Int Foo as well so it complains
You can get rid of this with either FunctionalDependencies or TypeFamilies
using functional dependencies
the first extension is probably the way to go here (you don't have to change much of your code). You can basically tell GHCi, that the type b in your class/constraint will be enough to decide the type a.
if you change it to:
{-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
class HasBar a b | b -> a where
bar :: b -> a
it'll work (you need the FlexibleContexts only in GHCi
λ> :set -XFlexibleContexts
λ> bar (Foo True)
True
using type families
In case you are interested here is the same thing with type-families and associated types:
{-# LANGUAGE TypeFamilies #-}
class HasBar a where
type Bar a :: *
bar :: a -> Bar a
data Foo = Foo { barBool :: Bool } deriving (Show)
instance HasBar Foo where
type Bar Foo = Bool
bar = barBool
data Bazz = Bazz { barInt :: Int } deriving (Show)
instance HasBar Bazz where
type Bar Bazz = Int
bar = barInt
note that you don't need the MultiParamTypeClasses any more

Prerequisite on types?

I have a type Foo a and want a type EnumFoo a that requires instance Enum (Foo a). How do you declare this type?
Let's say we declare Foo like this:
type Foo a = Maybe a
There can be Foo Int, Foo String and anything.
Now I declare an instance of Enum on Foo Int:
instance Enum (Foo Int) where
...
There might be some other Foo that has an instance of Enum like this. Let's call those types EnumFoo a. How do you express it?
This is not working but what I would like to do:
type (Enum (Foo a)) => EnumFoo a = Foo a
I am not sure what it's called, so the title should be making no sense.
As bheklilr suggested, it sounds like what you want is a GADT:
{-# LANGUAGE GADTs #-}
{-# LANGUAGE FlexibleContexts #-}
module Foo where
data Foo a = Foo (Maybe a)
data EnumFoo a where
EnumFoo :: Enum (Foo a) => Foo a -> EnumFoo a
The only way to make an EnumFoo a (aside from undefined) is to apply the EnumFoo constructor, which imposes an Enum (Foo a) context. You can then write things like
blah :: EnumFoo a -> [EnumFoo a]
blah (EnumFoo foo) = map EnumFoo [toEnum 1 .. foo]
Note that you need the FlexibleContexts extension because standard Haskell doesn't allow a context like Enum (Foo a); it only allows simple things like Enum Foo or Enum a.
bheklilr also mentioned an older declaration form, putting a context on a standard data declaration. While this form is standard Haskell (it is in the Haskell 98 and Haskell 2010 Reports), it is so widely considered a misfeature that GHC does not even allow it without a LANGUAGE pragma. The problem is that while it constrains what the type variables are allowed to be, it doesn't let you make use of these constraints.

Using constraint kinds and type families with 'limited' constraints

I'm working on an applicative functor that contains a monoid to "view" the execution. However, sometimes I don't care about this part at all, so the choice of monoid is irrelevant as it will never be consumed. I've simplified what I have into:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts
class Render a b where render :: a -> b
instance Render a () where render = const ()
class Merge a where
type Renderer a b :: Constraint
merge :: Renderer a b => a -> b
data Foo = Foo Bool
instance Merge Foo where
type (Renderer Foo) m = (Render Bool m)
merge (Foo b) = render b
Render is used to transform various as into a single b. Merge is a big simplification of my actual functor, but the point is it contains a type family/constraint and my intention of that is to specify exactly what Renderers a Merge requires.
Now, I might want to "run" the Merge, but discard the view, which is akin to something like:
runFoo :: Merge a => a -> Int
runFoo x = case merge x of () -> 5
But this will fail because:
Could not deduce (Renderer a ()) arising from a use of merge
I chose () as my monoid because forall a, we have an instance of Render a (). So if there was a way to say that Merge a just means a collection Render constraints then this would work fine. Of course, Merge a is more general than that - it could add arbitrary constraints, which explains the compilation error.
Is there anyway to achieve what I want without changing the signature of runFoo?
This might not scale if you have a lot of these cases, but this works:
class Renderer a () => Merge a where
...

Resources