ConstraintKinds explained on a super simple example

♀尐吖头ヾ 提交于 2019-12-04 07:50:08

问题


What is a Constraint kind?

Why would someone use it (in practice)?

What is it good for?

Could you give a simple code example to illustrate the answers to the previous two questions?

Why is it used in this code for example?


回答1:


Well, I'll mention two practical things it allows you to do:

  1. Parametrize a type by a type class constraint
  2. Write type classes that allow their instances to specify constraints that they need.

Maybe it's best to illustrate this with an example. One of the classic Haskell warts is that you cannot make a Functor instance for types that impose a class constraint on their type parameter; for example, the Set class in the containers library, which requires an Ord constraint on its elements. The reason is that in "vanilla" Haskell, you'd have to have the constraint on the class itself:

class OrdFunctor f where
    fmap :: Ord b => (a -> b) -> f a -> f b

...but then this class only works for types that require specifically an Ord constraint. Not a general solution!

So what if we could take that class definition and abstract away the Ord constraint, allowing individual instances to say what constraint they require? Well, ConstraintKinds plus TypeFamilies allow that:

{-# LANGUAGE ConstraintKinds, TypeFamilies, FlexibleInstances #-}

import Prelude hiding (Functor(..))
import GHC.Exts (Constraint)
import Data.Set (Set)
import qualified Data.Set as Set

-- | A 'Functor' over types that satisfy some constraint.
class Functor f where
   -- | The constraint on the allowed element types.  Each
   -- instance gets to choose for itself what this is.
   type Allowed f :: * -> Constraint

   fmap :: Allowed f b => (a -> b) -> f a -> f b

instance Functor Set where
    -- | 'Set' gets to pick 'Ord' as the constraint.
    type Allowed Set = Ord
    fmap = Set.map

instance Functor [] where
    -- | And `[]` can pick a different constraint than `Set` does.
    type Allowed [] = NoConstraint
    fmap = map

-- | A dummy class that means "no constraint."
class NoConstraint a where

-- | All types are trivially instances of 'NoConstraint'.
instance NoConstraint a where

(Note that this isn't the only obstacle to making a Functor instance to Set; see this discussion. Also, credit to this answer for the NoConstraint trick.)

This sort of solution hasn't been generally adopted just yet, though, because ConstraintKinds are still more or less a new feature.


Another use of ConstraintKinds is to parametrize a type by a class constraint or class. I'll reproduce this Haskell "Shape Example" code that I wrote:

{-# LANGUAGE GADTs, ConstraintKinds, KindSignatures, DeriveDataTypeable #-}
{-# LANGUAGE TypeOperators, ScopedTypeVariables, FlexibleInstances #-}

module Shape where

import Control.Applicative ((<$>), (<|>))
import Data.Maybe (mapMaybe)
import Data.Typeable
import GHC.Exts (Constraint)

-- | Generic, reflective, heterogeneous container for instances
-- of a type class.
data Object (constraint :: * -> Constraint) where
    Obj :: (Typeable a, constraint a) => a -> Object constraint
           deriving Typeable

-- | Downcast an 'Object' to any type that satisfies the relevant
-- constraints.
downcast :: forall a constraint. (Typeable a, constraint a) =>
            Object constraint -> Maybe a
downcast (Obj (value :: b)) = 
  case eqT :: Maybe (a :~: b) of
    Just Refl -> Just value
    Nothing -> Nothing

Here the parameter of the Object type is a type class (kind * -> Constraint), so you can have types like Object Shape where Shape is a class:

class Shape shape where
  getArea :: shape -> Double

-- Note how the 'Object' type is parametrized by 'Shape', a class 
-- constraint.  That's the sort of thing ConstraintKinds enables.
instance Shape (Object Shape) where
    getArea (Obj o) = getArea o

What the Object type does is a combination of two features:

  1. An existential type (enabled here by GADTs), which allows us to store values of heterogeneous types inside the same Object type.
  2. ConstraintKinds, which allows us to, instead of hardcoding Object to some specific set of class constraints, have the users of the Object type specify the constraint they want as a parameter to the Object type.

And now with that we can not only make a heterogeneous list of Shape instances:

data Circle = Circle { radius :: Double }
            deriving Typeable

instance Shape Circle where
  getArea (Circle radius) = pi * radius^2


data Rectangle = Rectangle { height :: Double, width :: Double }
               deriving Typeable

instance Shape Rectangle where
  getArea (Rectangle height width) = height * width

exampleData :: [Object Shape]
exampleData = [Obj (Circle 1.5), Obj (Rectangle 2 3)]

...but thanks to the Typeable constraint in Object we can downcast: if we correctly guess the type contained inside an Object, we can recover that original type:

-- | For each 'Shape' in the list, try to cast it to a Circle.  If we
-- succeed, then pass the result to a monomorphic function that 
-- demands a 'Circle'.  Evaluates to:
--
-- >>> example
-- ["A Circle of radius 1.5","A Shape with area 6.0"]
example :: [String]
example = mapMaybe step exampleData
  where step shape = describeCircle <$> (downcast shape)
                 <|> Just (describeShape shape)

describeCircle :: Circle -> String
describeCircle (Circle radius) = "A Circle of radius " ++ show radius

describeShape :: Shape a => a -> String
describeShape shape = "A Shape with area " ++ show (getArea shape)



回答2:


The ConstraintKind extension allows the use of the Constraint kind. Every expression that appears in a context (generally the things between :: and =>), has kind Constraint. For example, in ghci:

Prelude> :kind Num
Num :: * -> Constraint

Generally, it is not possible to manually use this kind, but the ConstraintKinds extension allows it. For example, one can now write:

Prelude> :set -XConstraintKinds
Prelude> type HasRequiredProperties a = (Num a, Read a, Show a, Monoid a)
Prelude> :kind HasRequiredProperties
HasRequiredProperties :: * -> Constraint

Now that you have something that takes a type (kind *), and gives a Constraint, you can write code like this.

Prelude> :{
Prelude| let myAwesomeFunction :: HasRequiredProperties a => a -> IO ()
Prelude|     myAwesomeFunction x = undefined
Prelude| :}

It is possible that the library you linked to uses MonadWidget as a type synonym with Constraint kind, but you'll have to take a closer look to make sure.



来源:https://stackoverflow.com/questions/31317159/constraintkinds-explained-on-a-super-simple-example

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!