No kind signatures

From HaskellWiki
Revision as of 23:01, 5 April 2021 by Atravers (talk | contribs) (Minor formatting changes)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Question

I have a datatype that needs other kinds than the compiler infers but my compiler does not support KindSignatures.

An example

I want to define

newtype MonadTransformer t m a = MonadTransformer (t m a)

with:

  • a :: *,
  • m :: * -> *,
  • t :: (* -> *) -> (* -> *),

but the compiler infers

  • a :: *,
  • m :: *,
  • t :: * -> * -> *!

Answer

You can achieve this using the phantom type of the Const functor.

import Control.Applicative (Const(Const))

newtype MonadTransformer t m a = MonadTransformer (Const (t m a) (m a))

monadTransformer :: t m a -> MonadTransformer t m a
monadTransformer = MonadTransformer . Const

runMonadTransformer :: MonadTransformer t m a -> t m a
runMonadTransformer (MonadTransformer (Const m)) = m

For more than one kind specification you still need only one Const, since you can use a tuple type like so Const (t m a) (t m a, m a, a). So to speak, the second type argument of Const allows you to specify examples of how to use the type parameters of MonadTransformer.