I want to implement a dynamic programming algorithm polymorphic in the score type; here's a simplified 1D version with no boundary conditions:
{-# LANGUAGE ConstraintKinds, FlexibleContexts, RankNTypes, ScopedTypeVariables #-}
import Control.Monad
import Control.Monad.ST.Strict
import Data.Array.ST
import Data.Array.Unboxed
dynamicProgrammingSTU
:: forall e i . (
IArray UArray e,
forall s. MArray (STUArray s) e (ST s),
Ix i
)
=> (forall m . Monad m => (i -> m e) -> (i -> m e))
-> (i, i)
-> (i -> e)
dynamicProgrammingSTU prog bnds = (arr !) where
arr :: UArray i e
arr = runSTUArray resultArrayST
resultArrayST :: forall s . ST s (STUArray s i e)
resultArrayST = do
marr <- newArray_ bnds
forM_ (range bnds) $ \i -> do
result <- prog (readArray marr) i
writeArray marr i result
return marr
The constraint doesn't work;
Could not deduce (MArray (STUArray s) e (ST s))
arising from a use of `newArray_'
from the context (IArray UArray e,
forall s. MArray (STUArray s) e (ST s),
Ix i)
bound by the type signature for
dynamicProgrammingSTU :: (IArray UArray e,
forall s. MArray (STUArray s) e (ST s
), Ix i) =>
(forall (m :: * -> *). Monad m => (i -
> m e) -> i -> m e)
-> (i, i) -> i -> e
at example2.hs:(17,1)-(27,15)
Possible fix:
add (MArray (STUArray s) e (ST s)) to the context of
the type signature for resultArrayST :: ST s (STUArray s i e)
or the type signature for
dynamicProgrammingSTU :: (IArray UArray e,
forall s. MArray (STUArray s) e (ST s), I
x i) =>
(forall (m :: * -> *). Monad m => (i -> m
e) -> i -> m e)
-> (i, i) -> i -> e
or add an instance declaration for (MArray (STUArray s) e (ST s))
In a stmt of a 'do' block: marr <- newArray_ bnds
In the expression:
do { marr <- newArray_ bnds;
forM_ (range bnds) $ \ i -> do { ... };
return marr }
In an equation for `resultArrayST':
resultArrayST
= do { marr <- newArray_ bnds;
forM_ (range bnds) $ \ i -> ...;
return marr }
Failed, modules loaded: none.
To summarize, Could not deduce (MArray (STUArray s) e (ST s)) from the context forall s. MArray (STUArray s) e (ST s i)
. Note that adding the constraint to resultArrayST
just pushes the problem to runSTUArray
.
I currently know of four flawed solutions:
- Avoiding the problem with boxed
STArray
s or simply non-monadicArray
s, perhaps usingseq
and bang patterns to ease the resulting memory problems. - Breaking the type system with
unsafeFreeze
andunsafePerformIO
, for which the damning constraintMArray IOUArray e IO
works fine. - This solution to a similar problem using a typeclass and writing instances for every 'unboxable' type.
- This one using GHC rewrite rules to pick a different function for each type (and a generic
STArray
version).
However, I'm asking this question in the hopes that modern language extensions like ConstraintKinds
can allow me to express my original code's intent of forall s. MArray (STUArray s) e (ST s)
.
Malformed predicate `forall s. MArray (STUArray s) e (ST s)'
, which to me makes more sense. – Censorprog
function is monadic just for performance, I think your p. 1 (pure computations with probable bang patterns) would be the least of evils. – Lunik