我想在得分类型中实现动态编程算法多态;这是一个没有边界条件的简化1D版本:
{-# 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
约束不起作用;
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.
总结一下,Could not deduce (MArray (STUArray s) e (ST s)) from the context forall s. MArray (STUArray s) e (ST s i)
。请注意,将约束添加到resultArrayST
只会将问题推送到runSTUArray
。
我目前知道有四个有缺陷的解决方案:
STArray
或简单的非monadic Array
来解决问题,可能使用seq
和爆炸模式来缓解由此导致的内存问题。 unsafeFreeze
和unsafePerformIO
打破类型系统,该死刑约束MArray IOUArray e IO
正常工作。STArray
版本)选择不同的函数。但是,我问这个问题是希望像ConstraintKinds
这样的现代语言扩展可以让我表达我原来代码forall s. MArray (STUArray s) e (ST s)
的意图。
答案 0 :(得分:1)
鉴于Haskell社区的传奇帮助,此时缺乏答案强烈表明目前的类型系统没有好的解决方案。
我已经在问题中概述了有缺陷的解决方案,所以我将发布我的示例的完整版本。这基本上就是我用来解决Rosalind上大多数对齐问题的原因:
{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-}
import Control.Applicative
import Control.Monad
import Control.Monad.ST
import Data.Maybe
import Data.Array.ST
import Data.Array.Unboxed
class IArray UArray e => Unboxable e where
newSTUArray_ :: forall s i. Ix i => (i, i) -> ST s (STUArray s i e)
readSTUArray :: forall s i. Ix i => STUArray s i e -> i -> ST s e
writeSTUArray :: forall s i. Ix i => STUArray s i e -> i -> e -> ST s ()
instance Unboxable Bool where
newSTUArray_ = newArray_
readSTUArray = readArray
writeSTUArray = writeArray
instance Unboxable Double where
newSTUArray_ = newArray_
readSTUArray = readArray
writeSTUArray = writeArray
{-
Same for Char, Float, (Int|Word)(|8|16|32|64)...
-}
{-# INLINE dynamicProgramming2DSTU #-}
dynamicProgramming2DSTU
:: forall e i j . (
Unboxable e,
Ix i,
Ix j,
Enum i,
Enum j
)
=> (forall m . (Monad m, Applicative m) => (i -> j -> m e) -> (i -> j -> m e))
-> (i -> j -> Maybe e)
-> (i, i)
-> (j, j)
-> (i -> j -> e)
dynamicProgramming2DSTU program boundaryConditions (xl, xh) (yl, yh) = arrayLookup where
arrayLookup :: i -> j -> e
arrayLookup xi yj = fromMaybe (resultArray ! (xi, yj)) $ boundaryConditions xi yj
arrB :: ((i, j), (i, j))
arrB = ((xl, yl), (xh, yh))
resultArray :: UArray (i, j) e
resultArray = runSTUArray resultArrayST
resultArrayST :: forall s. ST s (STUArray s (i, j) e)
resultArrayST = do
arr <- newSTUArray_ arrB
let acc xi yj = maybe (readSTUArray arr (xi, yj)) return $ boundaryConditions xi yj
forM_ [xl..xh] $ \xi -> do
forM_ [yl..yh] $ \yj -> do
result <- program acc xi yj
writeSTUArray arr (xi, yj) result
return arr