Avoid `undefined` when using `TypeError` in type-class constraint - haskell

I have a type-class instance like this:
instance {-# OVERLAPPABLE #-} (TypeError ( 'Text "Some error")) => SomeClass x where
someMethod = undefined
This instance exists at the end of other (valid) instances. The idea is to have the compiler throw a type error when the user writes a type that doesn't adhere to these valid instances. TypeError in instance constraint achieves this, but this also forces me to fill in the method with undefined, which feels like a hack.
Is there a way to avoid this? Or do it better?
Here's the real-world code with this pattern.

The best I could achieve is this. Essentially, I defined a TypeErr type family standing for both the standard TypeError constraint and an additional Impossible constraint providing the needed witness. Impossible would always fail to resolve as a constraint, but the type error is triggered first anyway.
{-# LANGUAGE DataKinds, UndecidableInstances, TypeFamilies #-}
import GHC.TypeLits (
ErrorMessage (Text),
TypeError,
)
class Impossible where
impossible :: a
type family TypeErr t where
TypeErr t = (TypeError t, Impossible)
-- Dummy example
class SomeClass x where
someMethod :: x -> Maybe x
instance {-# OVERLAPPABLE #-} (TypeErr ( 'Text "Some error"))
=> SomeClass x where
someMethod = impossible
main :: IO ()
main = print (someMethod True)
{-
<source>:19:15: error:
* Some error
* In the first argument of `print', namely `(someMethod True)'
In the expression: print (someMethod True)
In an equation for `main': main = print (someMethod True)
-}

We have the Disallowed class in the trivial-constraint package. It offers the nope pseudo-method, which is a version of undefined that can only be used in impossible contexts (and witnesses this by being possible to “use” unboxed, which you can't do with standard undefined).
instance {-# OVERLAPPABLE #-} (Disallowed "fallback for `SomeClass`")
=> SomeClass x where
someMethod = nope

Related

Apply constraint within constraint in Haskell

Is there anyway to apply a constraint within another constraint such that this
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
module Test where
type Con a = (Num a, Show a)
type App c a b = (c a, c b)
program :: App Con a b => a -> b -> String
program a b = show a ++ " " ++ show (b+1)
will work?
Currently GHC is giving me the following errors:
[1 of 1] Compiling Test ( Test.hs, interpreted )
Test.hs:9:12: error:
• Expected a constraint, but ‘App Con a b’ has kind ‘*’
• In the type signature: program :: App Con a b => a -> b -> String
|
9 | program :: App Con a b => a -> b -> String
| ^^^^^^^^^^^
Test.hs:9:16: error:
• Expected kind ‘* -> *’, but ‘Con’ has kind ‘* -> Constraint’
• In the first argument of ‘App’, namely ‘Con’
In the type signature: program :: App Con a b => a -> b -> String
|
9 | program :: App Con a b => a -> b -> String
| ^^^
Failed, no modules loaded.
Thanks!
An easy way to fix this is to use the LiberalTypeSynonyms extension. This extension allows GHC to first treat the type synonyms as substitutions and only afterwards check that the synonyms are fully applied. Note that GHC can be a little silly at kind inference, so you'll need to be very clear with it (i.e., an explicit signature). Try this:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE LiberalTypeSynonyms #-}
module Test where
import Data.Kind (Constraint)
type Con a = (Num a, Show a)
type App c a b = (c a, c b) :: Constraint
program :: App Con a b => a -> b -> String
program a b = show a ++ " " ++ show (b+1)
Before I understood that this could be solved with LiberalTypeSynonyms, I had a different solution, which I'll keep here in case anyone's interested.
Although the error message you're getting is a bit misleading, the fundamental problem with your code comes down to the fact that GHC does not support partial application of type synonyms, which you have in App Con a b. There are a few ways to fix this, but I find the simplest is to convert the type synonym constraint into a class constraint following this pattern:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
type Con' a = (Num a, Show a)
class Con' a => Con a
instance Con' a => Con a
You can use this definition of Con anywhere you were intending to use your old one.
If you're interested in how/why this works, it's basically a trick to get around GHC's lack of support for partial type synonym/family application for the particular cases where those type synonyms/families define simple constraints.
What we're doing is defining a class, and every class comes with a constraint of the same name. Now, notice that the class has no body, but critically, the class itself has a constraint (in the above case Con' a), which means that every instance of the class must have that same constraint.
Next, we make an incredibly generic instance of Con, one that covers any type so long as the constraint Con' holds on that type. In essence, this assures that any type that is an instance of Con' is also an instance of Con, and the Con' constraint on the Con class instance assures that GHC knows that anything that's an instance of Con also satisfies Con'. In total, the Con constraint is functionally equivalent to Con', but it can be partially applied. Success!
As another side note, the GHC proposal for unsaturated type families was recently accepted, so there may be a not-too-far-off future where these tricks are unnecessary because partial application of type families becomes allowed.
Haskell does not support type-level lambdas, nor partial application of type families / type synonyms. Your Con must always be fully applied, it can not passed unapplied to another type synonym.
At best, we can try to use "defunctionalization" as follows, effectively giving names to the type-level lambdas we need.
{-# LANGUAGE ConstraintKinds, KindSignatures, TypeFamilies #-}
import Data.Kind
-- Generic application operator
type family Apply f x :: Constraint
-- A name for the type-level lambda we need
data Con
-- How it can be applied
type instance Apply Con x = (Show x, Num x)
-- The wanted type-level function
type App c a b = (Apply c a, Apply c b)
-- Con can now be passed since it's a name, not a function
program :: App Con a b => a -> b -> String
program a b = show a ++ " " ++ show (b+1)
To call App with a different first argument, one would need to repeat this technique: define a custom dummy type name (like Con) and describe how to apply it (using type instance Apply ... = ...).

Is there a way to show "showable" stuff [duplicate]

Suppose I have a simple data type in Haskell for storing a value:
data V a = V a
I want to make V an instance of Show, regardless of a's type. If a is an instance of Show, then show (V a) should return show a otherwise an error message should be returned. Or in Pseudo-Haskell:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
How could this behaviour be implemented in Haskell?
As I said in a comment, the runtime objects allocated in memory don't have type tags in a Haskell program. There is therefore no universal instanceof operation like in, say, Java.
It's also important to consider the implications of the following. In Haskell, to a first approximation (i.e., ignoring some fancy stuff that beginners shouldn't tackle too soon), all runtime function calls are monomorphic. I.e., the compiler knows, directly or indirectly, the monomorphic (non-generic) type of every function call in an executable program. Even though your V type's show function has a generic type:
-- Specialized to `V a`
show :: V a -> String -- generic; has variable `a`
...you can't actually write a program that calls the function at runtime without, directly or indirectly, telling the compiler exactly what type a will be in every single call. So for example:
-- Here you tell it directly that `a := Int`
example1 = show (V (1 :: Int))
-- Here you're not saying which type `a` is, but this just "puts off"
-- the decision—for `example2` to be called, *something* in the call
-- graph will have to pick a monomorphic type for `a`.
example2 :: a -> String
example2 x = show (V x) ++ example1
Seen in this light, hopefully you can spot the problem with what you're asking:
instance Show (V a) where
show (V a) = if a instanceof Show
then show a
else "Some Error."
Basically, since the type for the a parameter will be known at compilation time for any actual call to your show function, there's no point to testing for this type at runtime—you can test for it at compilation time! Once you grasp this, you're led to Will Sewell's suggestion:
-- No call to `show (V x)` will compile unless `x` is of a `Show` type.
instance Show a => Show (V a) where ...
EDIT: A more constructive answer perhaps might be this: your V type needs to be a tagged union of multiple cases. This does require using the GADTs extension:
{-# LANGUAGE GADTs #-}
-- This definition requires `GADTs`. It has two constructors:
data V a where
-- The `Showable` constructor can only be used with `Show` types.
Showable :: Show a => a -> V a
-- The `Unshowable` constructor can be used with any type.
Unshowable :: a -> V a
instance Show (V a) where
show (Showable a) = show a
show (Unshowable a) = "Some Error."
But this isn't a runtime check of whether a type is a Show instance—your code is responsible for knowing at compilation time where the Showable constructor is to be used.
You can with this library: https://github.com/mikeizbicki/ifcxt. Being able to call show on a value that may or may not have a Show instance is one of the first examples it gives. This is how you could adapt that for V a:
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
import IfCxt
import Data.Typeable
mkIfCxtInstances ''Show
data V a = V a
instance forall a. IfCxt (Show a) => Show (V a) where
show (V a) = ifCxt (Proxy::Proxy (Show a))
(show a)
"<<unshowable>>"
This is the essence of this library:
class IfCxt cxt where
ifCxt :: proxy cxt -> (cxt => a) -> a -> a
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
I don't fully understand it, but this is how I think it works:
It doesn't violate the "open world" assumption any more than
instance {-# OVERLAPPABLE #-} Show a where
show _ = "<<unshowable>>"
does. The approach is actually pretty similar to that: adding a default case to fall back on for all types that do not have an instance in scope. However, it adds some indirection to not make a mess of the existing instances (and to allow different functions to specify different defaults). IfCxt works as a a "meta-class", a class on constraints, that indicates whether those instances exist, with a default case that indicates "false.":
instance {-# OVERLAPPABLE #-} IfCxt cxt where ifCxt _ t f = f
It uses TemplateHaskell to generate a long list of instances for that class:
instance {-# OVERLAPS #-} IfCxt (Show Int) where ifCxt _ t f = t
instance {-# OVERLAPS #-} IfCxt (Show Char) where ifCxt _ t f = t
which also implies that any instances that were not in scope when mkIfCxtInstances was called will be considered non-existing.
The proxy cxt argument is used to pass a Constraint to the function, the (cxt => a) argument (I had no idea RankNTypes allowed that) is an argument that can use the constraint cxt, but as long as that argument is unused, the constraint doesn't need to be solved. This is similar to:
f :: (Show (a -> a) => a) -> a -> a
f _ x = x
The proxy argument supplies the constraint, then the IfCxt constraint is solved to either the t or f argument, if it's t then there is some IfCxt instance where this constraint is supplied which means it can be solved directly, if it's f then the constraint is never demanded so it gets dropped.
This solution is imperfect (as new modules can define new Show instances which won't work unless it also calls mkIfCxtInstances), but being able to do that would violate the open world assumption.
Even if you could do this, it would be a bad design. I would recommend adding a Show constraint to a:
instance Show a => Show (V a) where ...
If you want to store members in a container data type that are not an instance of Show, then you should create a new data type fore them.

Haskell Constraint Kinds - default constraint for default implementation

Headline: I would like to provide a default implementation for a class method parametrised over a constraint, which uses the default instance for that constraint.
Consider the following:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
import GHC.Exts (Constraint)
class Foo a where
type Ctx a :: Constraint
type Ctx a = Show a
foo :: (Ctx a) => a -> String
foo = show
main :: IO ()
main = putStrLn "Compiles!"
This fails to compile with the error of:
Could not deduce (Show a) arising from a use of ‘show’
from the context (Foo a)
From my perspective, it should be using the default constraint of Show, which would let this compile. Is there any reason this doesn't work, or can anyone suggest a good way to achieve this?
You can achieve this using DefaultSignatures:
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DefaultSignatures #-}
import GHC.Exts (Constraint)
class Foo a where
type Ctx a :: Constraint
type Ctx a = Show a
foo :: (Ctx a) => a -> String
default foo :: Show a => a -> String
foo = show
main :: IO ()
main = putStrLn "Compiles!"
From my perspective, it should be using the default constraint of Show, which would let this compile.
The reason your approach doesn't work is that the user of your class should be able to override any number of defaults. Your code would break if someone tried to override Ctx but not foo.

Undefined at the type level

Often when I'm playing with Haskell code, I stub things out with a type annotation and undefined.
foo :: String -> Int
foo = undefined
Is there a type-level "undefined" that I could use in a similar way?
(Ideally, in conjunction with a kind annotation)
type Foo :: * -> *
type Foo = Undefined
Further thought on the same thread: is there a way for me to stub out typeclass instances for types created this way? An even easier way than the following theoretical way?
instance Monad Foo where
return = undefined
(>>=) = undefined
You can use EmptyDataDecls to stub out a type, and with KindSignatures you can give it a kind:
{-# LANGUAGE EmptyDataDecls, KindSignatures #-}
data Foo :: * -> *
You can also stub out the Monad instance without warnings with this option to GHC.
{-# OPTIONS_GHC -fno-warn-missing-methods #-}
instance Monad Foo
And then you don't need to leave any implementation for return and >>=.
This question was asked and answered a long time ago; best practices have evolved since.
These days, instead of undefined, for stubbing out code you should be using typed holes, and their type-level analogue, partial type signatures.

Haskell -- get TypeRep from concrete type instance

I want to write a function with this type signature:
getTypeRep :: Typeable a => t a -> TypeRep
where the TypeRep will be the type representation for a, not for t a. That is, the compiler should automatically return the correct type representation at any call sites [to getTypeRep], which will have concrete types for a.
To add some context, I want to create a "Dynamic type" data type, with the twist that it will remember the top-level type, but not its parameter. For example, I want to turn MyClass a into Dynamic MyClass, and the above function will be used to create instances of Dynamic MyClass that store a representation of the type parameter a.
Well, how about using scoped type variables to select the inner component:
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE ScopedTypeVariables #-}
import Data.Dynamic
import Data.Typeable
getTypeRep :: forall t a . Typeable a => t a -> TypeRep
getTypeRep _ = typeOf (undefined :: a)
Works for me:
*Main> getTypeRep (Just ())
()
*Main> getTypeRep (Just 7)
Integer
*Main> getTypeRep ([True])
Bool
Interesting design.
On a tangential note to Don's solution, notice that code rarely require ScopedTypeVariables. It just makes the solution cleaner (but less portable). The solution without scoped types is:
{-# LANGUAGE ExplicitForAll #-}
import Data.Typeable
helper :: t a -> a
helper _ = undefined
getTypeRep :: forall t a. Typeable a => t a -> TypeRep
getTypeRep = typeOf . helper
This function (now) exists in Data.Typeable typeRep

Resources