Type Constraints in Typeclass - haskell

For fun I'm building a parser library. In this library I have a Parser data type:
data Parser e a = Parser (String -> Either e (a, String))
I'm able to define Functor and Applicative instances of Parser, but I don't think I can make an Alternative instance without constraining the "error" type or the "value" type the parser could return. Originally, this made me create an Applicative instance for when the error types are String messages, but I realized that I should be able to release this constraint to any message data type that has an Alternative (or maybe Monoid instead?) instance as well. With that in mind I wrote this:
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
instance Alternative e => Alternative (Parser e)
where
empty = Parser $ \s -> Left empty
(<|>) (Parser p1) (Parser p2) = Parser $ \s -> tryParser s p2 $ p1 s
where
tryParser s p2 (Left _ ) = p2 s
tryParser _ _ x = x
Unfortunately, this fails to compile. When I load it into ghci I get this error message:
Parsertest.hs:31:47:
Expecting one more argument to `e'
In the instance declaration for `Alternative (Parser e)'
Failed, modules loaded: none.
When I search online, this seems to be the solution, but it doesn't work for me. What am I missing?

The problem is that Alternative is for type constructors of kind * -> *, so if you say
instance Alternative e => ....
then e has to be a type constructor, not a type. So e could be [] or Maybe or something, but not Int.
Alternative's operator is <|> which has type Alternative e => e a -> e a -> e a. This forces e to take an argument to make a type, like Maybe has to take an argument, eg Maybe Int.
Use Monoid instead of Alternative, because it's a type class instead of a constructor class. It's operator mappend has type Monoid e => e -> e -> e which is what you want for combining errors.

Related

Pattern matching with Alternative empty or Applicative pure

I know it is possible, to pattern match against (named) constructors like so:
f1 :: Maybe a -> Bool
f1 Nothing = False
f1 (Just x) = True -- in reality have something that uses x here
f2 :: [a] -> Int
f2 [] = False
f2 x = True
How can I write such a function for general Alternatives similar to
f :: (Alternative m) => m a -> Bool
f empty = False
f x = True
If I try this, I get the error Parse error in pattern: empty. Which makes sense, I guess, as empty as a function here and not a constructor. But how can I accomplish this for general Alternatives idiomatically?
Edit 1:
My actual goal is to define a Monad instance (and probably also a MonadPlus instance) for a custom result type. Instead of the basic Either Error Result type, it should support a Maybe Error (and if possible also other Alternatives like [Error]) as error type and also some Applicative as result type in order to support lazy evaluation, for example with the result type (Maybe Error, [Tokens]) of a tokenizer.
I'd like something similar to
instance (Alterantive mErr, Applicative mRes) => Monad (mErr e, mRes a) where
return x = (empty, pure x)
(empty, pure x) >>= f = f x
(err, x) >>= f = (err, x)
The best you can do is:
f :: (Eq (m a), Alternative m) => m a -> Bool
f x | x == empty = False
| otherwise = True
It is in fact possible using -XPatternSynonyms and -XViewPatterns:
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
import Control.Applicative (empty)
pattern Empty :: (Eq (m a), Alternative m) => m a
pattern Empty <- ((==) empty -> True)
f :: (Eq (m a), Alternative m) => m a -> Bool
f Empty = False
f _ = True
Slipping in an Eq constraint, as in mithrandi's answer, is indeed the best that can be done. In any case, it is worth emphasising that it comes at a cost: we are now stuck with an Eq constant that would be unnecessary were we merely pattern match against, say, [] or Nothing. A common way to avoid this problem is using null :: Foldable t => t a -> Bool. Here, however, that option is not great either, as Foldable is largely unrelated to Alternative and rather alien to your use case. In particular, there is no guarantee that, in the general case, there will be just one value for which null holds, which means it might conceivably hold for values that aren't the empty of the relevant Alternative instance.
Ultimately, then, the only tool that would fully fit the requirements might well be some Alternative subclass with an isEmpty method. I don't think that exists anywhere, and the power-to-weight ratio doesn't seem encouraging when it comes to conjuring such a thing.

Is it possible to ensure that two GADT type variables are the same without dependent types?

I'm writing a compiler where I'm using GADTs for my IR but standard data types for my everything else. I'm having trouble during the conversion from the old data type to the GADT. I've attempted to recreate the situation with a smaller/simplified language below.
To start with, I have the following data types:
data OldLVal = VarOL Int -- The nth variable. Can be used to construct a Temp later.
| LDeref OldLVal
data Exp = Var Int -- See above
| IntT Int32
| Deref Exp
data Statement = AssignStmt OldLVal Exp
| ...
I want to convert these into this intermediate form:
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
-- Note: this is a Phantom type
data Temp a = Temp Int
data Type = IntT
| PtrT Type
data Command where
Assign :: NewLVal a -> Pure a -> Command
...
data NewLVal :: Type -> * where
VarNL :: Temp a -> NewLVal a
DerefNL :: NewLVal ('PtrT ('Just a)) -> NewLVal a
data Pure :: Type -> * where
ConstP :: Int32 -> Pure 'IntT
ConstPtrP :: Int32 -> Pure ('PtrT a)
VarP :: Temp a -> Pure a
At this point, I just want to write a conversion from the old data type to the new GADT. For right now, I have something that looks like this.
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
newLval <- convertLVal oldLval -- Either String (NewLVal a)
pure <- convertPure exp -- Either String (Pure b)
-- return $ Assign newLval pure -- Obvious failure. Can't ensure a ~ b.
pure' <- matchType newLval pure -- Either String (Pure a)
return $ Assign newLval pure'
-- Converts Pure b into Pure a. Should essentially be a noop, but simply
-- proves that it is possible.
matchType :: NewLVal a -> Pure b -> Either String (Pure a)
matchType = undefined
I realized that I couldn't write convert trivially, so I attempted to solve the problem using this idea of matchType which acts as a proof that these two types are indeed equal. The question is: how do I actually write matchType? This would be much easier if I had fully dependent types (or so I'm told), but can I finish this code here?
An alternative to this would be to somehow provide newLval as an argument to convertPure, but I think that essentially is just attempting to use dependent types.
Any other suggestions are welcome.
If it helps, I also have a function that can convert an Exp or OldLVal to its type:
class Typed a where
typeOf :: a -> Type
instance Typed Exp where
...
instance Typed OldLVal where
...
EDIT:
Thanks to the excellent answers below, I've been able to finish writing this module.
I ended up using the singletons package mentioned below. It was a little strange at first, but I found it pretty reasonable to use after I started understanding what I was doing. However, I did run into one pitfall: The type of convertLVal and convertPure requires an existential to express.
data WrappedPure = forall a. WrappedPure (Pure a, SType a)
data WrappedLVal = forall a. WrappedLVal (NewLVal a, SType a)
convertPure :: Exp -> Either String WrappedPure
convertLVal :: OldLVal -> Either String WrappedLVal
This means that you'll have to unwrap that existential in convert, but otherwise, the answers below show you the way. Thanks so much once again.
You want to perform a comparison at runtime on some type level data (namely the Types by which your values are indexed). But by the time you run your code, and the values start to interact, the types are long gone. They're erased by the compiler, in the name of producing efficient code. So you need to manually reconstruct the type level data that was erased, using a value which reminds you of the type you'd forgotten you were looking at. You need a singleton copy of Type.
data SType t where
SIntT :: SType IntT
SPtrT :: SType t -> SType (PtrT t)
Members of SType look like members of Type - compare the structure of a value like SPtrT (SPtrT SIntT) with that of PtrT (PtrT IntT) - but they're indexed by the (type-level) Types that they resemble. For each t :: Type there's precisely one SType t (hence the name singleton), and because SType is a GADT, pattern matching on an SType t tells the type checker about the t. Singletons span the otherwise strictly-enforced separation between types and values.
So when you're constructing your typed tree, you need to track the runtime STypes of your values and compare them when necessary. (This basically amounts to writing a partially verified type checker.) There's a class in Data.Type.Equality containing a function which compares two singletons and tells you whether their indexes match or not.
instance TestEquality SType where
-- testEquality :: SType t1 -> SType t2 -> Maybe (t1 :~: t2)
testEquality SIntT SIntT = Just Refl
testEquality (SPtrT t1) (SPtrT t2)
| Just Refl <- testEquality t1 t2 = Just Refl
testEquality _ _ = Nothing
Applying this in your convert function looks roughly like this:
convert :: Statement -> Either String Command
convert (AssignStmt oldLval exp) = do
(newLval, newLValSType) <- convertLVal oldLval
(pure, pureSType) <- convertPure exp
case testEquality newLValSType pureSType of
Just Refl -> return $ Assign newLval pure'
Nothing -> Left "type mismatch"
There actually aren't a whole lot of dependently typed programs you can't fake up with TypeInType and singletons (are there any?), but it's a real hassle to duplicate all of your datatypes in both "normal" and "singleton" form. (The duplication gets even worse if you want to pass singletons around implicitly - see Hasochism for the details.) The singletons package can generate much of the boilerplate for you, but it doesn't really alleviate the pain caused by duplicating the concepts themselves. That's why people want to add real dependent types to Haskell, but we're a good few years away from that yet.
The new Type.Reflection module contains a rewritten Typeable class. Its TypeRep is GADT-like and can act as a sort of "universal singleton". But programming with it is even more awkward than programming with singletons, in my opinion.
matchType as written is not possible to implement, but the idea you are going for is definitely possible. Do you know about Data.Typeable? Typeable is a class that provides some basic reflective operations for inspecting types. To use it, you need a Typeable a constraint in scope for any type variable a you want to know about. So for matchType you would have
matchType :: (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure a)
It needs also to infect your GADTs any time you want to hide a type variable:
data Command where
Assign :: (Typeable a) => NewLVal a -> Pure a -> Command
...
But if you have the appropriate constraints in scope, you can use eqT to make type-safe runtime type comparisons. For example
-- using ScopedTypeVariables and TypeApplications
matchType :: forall a b. (Typeable a, Typeable b) => NewLVal a -> Pure b -> Either String (Pure b)
matchType = case eqT #a #b of
Nothing -> Left "types are not equal"
Just Refl -> {- in this scope the compiler knows that
a and b are the same type -}

Does exporting type constructors make a difference?

Let's say I have an internal data type, T a, that is used in the signature of exported functions:
module A (f, g) where
newtype T a = MkT { unT :: (Int, a) }
deriving (Functor, Show, Read) -- for internal use
f :: a -> IO (T a)
f a = fmap (\i -> T (i, a)) randomIO
g :: T a -> a
g = snd . unT
What is the effect of not exporting the type constructor T? Does it prevent consumers from meddling with values of type T a? In other words, is there a difference between the export list (f, g) and (f, g, T()) here?
Prevented
The first thing a consumer will see is that the type doesn't appear in Haddock documentation. In the documentation for f and g, the type Twill not be hyperlinked like an exported type. This may prevent a casual reader from discovering T's class instances.
More importantly, a consumer cannot doing anything with T at the type level. Anything that requires writing a type will be impossible. For instance, a consumer cannot write new class instances involving T, or include T in a type family. (I don't think there's a way around this...)
At the value level, however, the main limitation is that a consumer cannot write a type annotation including T:
> :t (f . read) :: Read b => String -> IO (A.T b)
<interactive>:1:39: Not in scope: type constructor or class `A.T'
Not prevented
The restriction on type signatures is not as significant a limitation as it appears. The compiler can still infer such a type:
> :t f . read
f . read :: Read b => String -> IO (A.T b)
Any value expression within the inferrable subset of Haskell may therefore be expressed regardless of the availability of the type constructor T. If, like me, you're addicted to ScopedTypeVariables and extensive annotations, you may be a little surprised by the definition of unT' below.
Furthermore, because typeclass instances have global scope, a consumer can use any available class functions without additional limitation. Depending on the classes involved, this may allow significant manipulation of values of the unexposed type. With classes like Functor, a consumer can also freely manipulate type parameters, because there's an available function of type T a -> T b.
In the example of T, deriving Show of course exposes the "internal" Int, and gives a consumer enough information to hackishly implement unT:
-- :: (Show a, Read a) => T a -> (Int, a)
unT' = (read . strip . show') `asTypeOf` (mkPair . g)
where
strip = reverse . drop 1 . reverse . drop 9
-- :: T a -> String
show' = show `asTypeOf` (mkString . g)
mkPair :: t -> (Int, t)
mkPair = undefined
mkString :: t -> String
mkString = undefined
> :t unT'
unT' :: (Show b, Read b) => A.T b -> (Int, b)
> x <- f "x"
> unT' x
(-29353, "x")
Implementing mkT' with the Read instance is left as an exercise.
Deriving something like Generic will completely explode any idea of containment, but you'd probably expect that.
Prevented?
In the corners of Haskell where type signatures are necessary or where asTypeOf-style tricks don't work, I guess not exporting the type constructor could actually prevent a consumer from doing something they could with the export list (f, g, T()).
Recommendation
Export all type constructors that are used in the type of any value you export. Here, go ahead and include T() in your export list. Leaving it out doesn't accomplish anything other than muddying the documentation. If you want to expose an purely abstract immutable type, use a newtype with a hidden constructor and no class instances.

Why not a more general function than mappend in Haskell?

The mappend function is just a particular case of an associative operation where the two elements are of the same type. Why no packages propose an implementation of an associative function without that condition?
This would be pretty easy with the multi-parameters type classes extension:
{-# Language MultiParamTypeClasses #-}
module Append where
class Append a b where
(<->) :: a -> b -> a
Then, depending on the implementation of the instances, it would for example allow to concatenate an Int with a String:
"I am " <-> 42
> "I am 42"
or add optional parameter to data record types:
data MyType = MyType {_option :: Maybe String}
myType = MyType Nothing
myTypeWithOption = myType <-> "Hello!"
I have tried to search on Hoogle, Hayoo! and on the web but could not find such function.
So: a) does it exists? b) if not why?
There is a generalization (of sorts) of Monoid in base's Control.Category:
class Category cat where
id :: cat a a
(.) :: cat b c -> cat a b -> cat a c
It has the same laws as Monoid - in fact, the documentation explicitly says "id and (.) must form a monoid."
This isn't a true generalization, because it doesn't work with the same types. But associativity works exactly because of the restriction on the types it works with.
What you're describing is is an action of a monoid on a set. In Haskell this could be defined as
class Monoid m => MonoidAction m s where
act :: m -> s -> s
infixr 5 `act`
This is a left monoid action on s, you could also have a right action with the arguments reversed (as you have).
The action must be compatible with the monoid operations as follows:
a `act` (b `act` x) == (a <> b) `act` x
mempty `act` x == x
Another way how to view a monoid action and its laws is that Endo . act a homomorphism from monoid m to Endo s - the monoid of endomorphism on s.
Note that for every monoid you can define its action on itself by defining
instance Monoid m => MonoidAction m m where
act = mappend
See module Data.Monoid.Action.
You can't in general define associativity without the two arguments having the same type. If you try, it will not be type correct.

Illegal instance declaration for typeclass TF

I am having a problem declaring an instance of the following typeclass. I tried to follow the advice in the error message from the ghci compiler but still cannot get the code to compile. Any help would be appreciated.
class TF p where
valid :: p -> Bool
lequiv :: p -> p -> Bool
instance TF Bool
where
valid = id
lequiv f g = f == g
instance TF p => TF (Bool -> p)
where
valid f = valid (f True) && valid (f False)
lequiv f g = (f True) `lequiv` (g True)
&& (f False) `lequiv` (g False)
The error I am getting is:
Illegal instance declaration for ‘TF (Bool -> p)’
(All instance types must be of the form (T a1 ... an)
where a1 ... an are *distinct type variables*,
and each type variable appears at most once in the instance head.
Use FlexibleInstances if you want to disable this.)
In the instance declaration for ‘TF (Bool -> p)’
The problem here is that you have a type constructor (->) applied to things that aren't type variables. There's a lot of ways you can deal with that:
FlexibleInstances. This relaxes the assumption (made in the early days of Haskell, when it wasn't yet clear how difficult implementing type classes would be). This is not very controversial at all. On the other hand, it doesn't play that well with type inference: your instance will only be chosen when we know that we're supplying something of the shape Bool -> p -- and in particular something that's polymorphic in the first argument will not match that shape. So valid id will not typecheck without further annotations.
TypeFamilies. This gives us (among other things) access to a constraint which demands that two particular types be equal. So with this extension, you could write
instance (bool ~ Bool, TF p) => TF (bool -> p) where ...
Now this matches whenever the thing we're supplying has shape bool -> p -- that is, any function at all -- and only after we have selected this instance does it check (in fact, enforce) that the argument type is Bool. This means valid id will typecheck; on the other hand, it also means you cannot declare instances for any other argument types.
Add a typeclass. In fact, the only thing you really care about is that you can list all the inhabitants of Bool in not too much time. So you could instead declare a typeclass, say, Finite, which you will instantiate at such types, and use it as the constraint on the argument type. Thus:
instance (Finite arg, TF p) => TF (arg -> p) where
valid f = all (valid . f) universe
lequiv f g = all (\x -> f x `lequiv` g x) universe
-- could also spell that lambda "liftA2 lequiv f g"
Then you would want to provide a Finite instance for Bool (which, luckily, is already available for you in the universe package). This is nice because it combines the strengths of the previous two approaches: this instance will be chosen as soon as we know the argument is a function, and you can declare instances for many argument types by adding Finite instances for them.

Resources