ghc-8.8 does not infer kind
Rejected by ghc-8.8.4 with
should.hs:27:12: error:
• Expected kind ‘* -> *’, but ‘solver’ has kind ‘*’
• In the first argument of ‘Solver’, namely ‘solver’
In the type ‘(Solver solver, Queue q, Transformer t) =>
Int -> q -> t -> EvalState t -> solver (Int, [a])’
In the type declaration for ‘ContinueSig’
but accepted by 8.6.5, 8.10.2. 9.0.1-alpha1.
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GADTs #-}
class Monad solver => Solver solver where
type Constraint solver :: *
type Label solver :: *
class Queue q
data Tree s a where
NewVar :: Term s t => (t -> Tree s a) -> Tree s a
class Solver solver => Term solver term
class Transformer t where
type EvalState t :: *
type TreeState t :: *
type ForSolver t :: (* -> *)
type ForResult t :: *
nextT :: SearchSig (ForSolver t) q t (ForResult t)
returnT :: ContinueSig solver q t (ForResult t)
type ContinueSig solver q t a =
( Solver solver, Queue q, Transformer t )
=> Int -> q -> t -> EvalState t
-> solver (Int, [a])
type SearchSig solver q t a =
(Solver solver, Queue q, Transformer t )
=> Int -> Tree solver a -> q -> t -> EvalState t -> TreeState t
-> solver (Int,[a])
8.8 accepts this after introducing this:
type ContinueSig (solver :: * -> *) q t a =
...