此代码编译没有问题:
import Control.Monad.ST (ST)
import Data.Array.MArray (MArray)
import Data.Array.Unboxed (UArray)
import Data.Array.ST (runSTUArray, newArray, STUArray)
new :: Double -> UArray Int Double
new a = runSTUArray (newArray (0, 9) a)
但是,这个:
new :: e -> UArray Int e
new a = runSTUArray (newArray (0, 9) a)
正如人们所料,失败,错误:
No instance for (MArray (STUArray s) e (ST s))
arising from a use of ‘newArray’
In the first argument of ‘runSTUArray’, namely
‘(newArray (0, 9) a)’
In the expression: runSTUArray (newArray (0, 9) a)
In an equation for ‘new’: new a = runSTUArray (newArray (0, 9) a)
但是,添加类型类约束无济于事,因为将类型签名更改为
new :: (MArray (STUArray s) e (ST s)) => e -> UArray Int e
仍会失败
Could not deduce (MArray (STUArray s0) e (ST s0))
from the context (MArray (STUArray s) e (ST s))
bound by the type signature for
new :: MArray (STUArray s) e (ST s) => e -> UArray Int e
at pilot.hs:7:8-58
The type variable ‘s0’ is ambiguous
In the ambiguity check for the type signature for ‘new’:
new :: forall e s.
MArray (STUArray s) e (ST s) =>
e -> UArray Int e
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
In the type signature for ‘new’:
new :: (MArray (STUArray s) e (ST s)) => e -> UArray Int e
任何使这项工作的方法?
编辑:发现这已经在Haskell和Haskell-Cafe邮件列表上进行了讨论,这个最小的解决方案取自here:
-- https://mail.haskell.org/pipermail/haskell/2005-August/016354.html
{-# LANGUAGE Rank2Types, FlexibleContexts #-}
import Control.Monad.ST (ST)
import Data.Array.MArray (MArray)
import Data.Array.Unboxed (UArray, Ix)
import Data.Array.ST (runSTUArray, newArray, STUArray)
new :: UArrayElement e => e -> UArray Int e
new a = case freezer of
Freezer runSTUArray' -> runSTUArray' $ (newArray (0, 9) a)
data Freezer i e = Freezer
((forall s. MArray (STUArray s) e (ST s) => ST s (STUArray s i e))
-> UArray i e)
class UArrayElement e where
freezer :: Ix i => Freezer i e
instance UArrayElement Bool where freezer = Freezer runSTUArray
instance UArrayElement Char where freezer = Freezer runSTUArray
instance UArrayElement Double where freezer = Freezer runSTUArray
答案 0 :(得分:7)
以下似乎有效。我不知道它是否可以最小化。一个缺点是,您需要为您希望能够使用的每个Unboxable
实例添加MArray
的实例 - 但至少要感谢您DefaultSignatures
必须写任何实际的代码。我已经为Int
添加了一个实例来展示我的意思。
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE FlexibleContexts #-}
import Control.Monad.ST
import Data.Constraint
import Data.Array.Unboxed
import Data.Array.ST
class Unboxable e where
unboxable :: Dict (MArray (STUArray s) e (ST s))
default unboxable :: MArray (STUArray s) e (ST s) => Dict (MArray (STUArray s) e (ST s))
unboxable = Dict
new :: forall e. Unboxable e => e -> UArray Int e
new e = runSTUArray build where
build :: forall s. ST s (STUArray s Int e)
build = case unboxable :: Dict (MArray (STUArray s) e (ST s)) of
Dict -> newArray (0, 9) e
instance Unboxable Int
Dict
类型来自Edward Kmett的constraints包。
答案 1 :(得分:5)
作为Daniel Wagner答案的改进,鉴于我们已经在使用constraints
,我们可以利用Data.Constraint.Forall
一次性获取所有Unboxable
个实例:
{-# LANGUAGE
ScopedTypeVariables, TypeOperators,
MultiParamTypeClasses, FlexibleContexts,
FlexibleInstances, UndecidableInstances #-}
import Control.Monad.ST (ST)
import Data.Array.MArray (MArray)
import Data.Array.Unboxed (UArray)
import Data.Array.ST (runSTUArray, newArray, STUArray)
import Data.Constraint
import Data.Constraint.Forall
class MArray (STUArray s) e (ST s) => Unboxable e s
instance MArray (STUArray s) e (ST s) => Unboxable e s
new :: forall e. Forall (Unboxable e) => e -> UArray Int e
new a = runSTUArray build where
build :: forall s. ST s (STUArray s Int e)
build = case inst :: Forall (Unboxable e) :- Unboxable e s of
Sub Dict -> newArray (0, 9) a
-- can be specialized to Double
new' :: Double -> UArray Int Double
new' = new