"Could not deduce (MArray (STUArray s) Int (ST s)) from context ()" when applying runST

Hi, I'm in the process of learning haskell and came across this problem: Using `Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2 booted by GHC version 6.10.1` Common beginning of the file ============================ {-# LANGUAGE FlexibleContexts #-} module UPSO where import Control.Monad(forM,forM_) import Control.Monad.ST.Lazy (ST,runST) import Data.Array.MArray (MArray, Ix, getBounds, newArray, readArray, writeArray) import Data.Array.ST (STArray,STUArray) minmax xs@(x:_) = foldr (\x (l,u) -> (min x l,max x u)) (x,x) xs modify a i f = do x <- readArray a i writeArray a i (f x) increment a i = modify a i (+1) decrement a i = modify a i (\x -> x - 1) uniquePermutationsM t 0 = return $! [[]] uniquePermutationsM t pos = do (l,u) <- getBounds t perms <- forM [l..u] (\d -> do count <- readArray t d -- t[d] if count == 0 then return $! [] else do decrement t d pss <- uniquePermutationsM t (pos-1) increment t d return $! (map (d:) pss) ) return $! (concat perms) Using STArray (works) ===================== mkArray :: (Int,Int) -> (ST s) (STArray s Int Int) mkArray bounds = newArray bounds 0 uniquePermutationsST :: [Int] -> ST s [[Int]] uniquePermutationsST xs = do let bounds@(l,u) = (minmax xs) t <- mkArray bounds forM_ xs (increment t) pos <- sum `fmap` mapM (readArray t) [l..u] uniquePermutationsM t pos uniquePermutations xs = runST (uniquePermutationsST xs) Using STUArray (doesn't work) ============================= But when I try to switch to unboxed arrays, I get an error message. mkArray :: (Int,Int) -> (ST s) (STUArray s Int Int) mkArray bounds = newArray bounds 0 uniquePermutationsST :: [Int] -> ST s [[Int]] uniquePermutationsST xs = do let bounds@(l,u) = (minmax xs) t <- mkArray bounds forM_ xs (increment t) pos <- sum `fmap` mapM (readArray t) [l..u] uniquePermutationsM t pos uniquePermutations xs = runST (uniquePermutationsST xs) Error messages ============== Could not deduce (MArray (STUArray s) Int (ST s)) from the context () arising from a use of 'newArray' at UPSO.hs:35:17-33 Possible fix: add (MArray (STUArray s) Int (ST s)) to the context of the type signature for 'mkArray' or add an instance declaration for (MArray (STUArray s) Int (ST s)) In the expression: newArray bounds 0 In the definition of 'mkArray': mkArray bounds = newArray bounds 0 and also: Could not deduce (MArray (STUArray s) Int (ST s)) from the context () arising from a use of 'increment' at UPSO.hs:41:14-24 After almost two hours of fiddling with the type annotations I hope someone can point me in the right direction. What on earth is going wrong? Thank you for your time.

On Tue, Jul 21, 2009 at 5:30 PM, Christian Klauser
Hi, I'm in the process of learning haskell and came across this problem:
Using `Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2 booted by GHC version 6.10.1`
Common beginning of the file ============================ {-# LANGUAGE FlexibleContexts #-}
module UPSO where
import Control.Monad(forM,forM_) import Control.Monad.ST.Lazy (ST,runST)
This works if I replace Control.Monad.ST.Strict instead of
Control.Monad.ST.Lazy.
The problem is that the MArray instances are declared for the strict
ST monad; there appear to be no corresponding instances for the lazy
ST monad.
--
Dave Menendez

Hi,
Thank you, works indeed with the strict ST monad. Didn't think of that. But
makes kind of sense not to define these instances, since unboxed values
cannot have their computation delayed. It's a bit unfortunate, however, that
a single use
of an unboxed array "forces" the whole state thread to become strict.
-----Original Message-----
From: d4ve.menendez@gmail.com [mailto:d4ve.menendez@gmail.com] On Behalf Of
David Menendez
Sent: Mittwoch, 22. Juli 2009 00:53
To: Christian Klauser
Cc: glasgow-haskell-users@haskell.org
Subject: Re: "Could not deduce (MArray (STUArray s) Int (ST s)) from context
()" when applying runST
On Tue, Jul 21, 2009 at 5:30 PM, Christian Klauser
Hi, I'm in the process of learning haskell and came across this problem:
Using `Glasgow Haskell Compiler, Version 6.10.4, for Haskell 98, stage 2 booted by GHC version 6.10.1`
Common beginning of the file ============================ {-# LANGUAGE FlexibleContexts #-}
module UPSO where
import Control.Monad(forM,forM_) import Control.Monad.ST.Lazy (ST,runST)
This works if I replace Control.Monad.ST.Strict instead of
Control.Monad.ST.Lazy.
The problem is that the MArray instances are declared for the strict
ST monad; there appear to be no corresponding instances for the lazy
ST monad.
--
Dave Menendez

On 22/07/2009, at 9:16 AM, Christian Klauser wrote:
Thank you, works indeed with the strict ST monad. Didn't think of that. But makes kind of sense not to define these instances, since unboxed values cannot have their computation delayed. It's a bit unfortunate, however, that a single use of an unboxed array "forces" the whole state thread to become strict.
Hmm. Have you seen the strictToLazyST function? http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad-ST-... cheers peter

Interesting. Would be used like this: uniquePermutations xs = runST $ strictToLazyST $ (uniquePermutationsST xs) After also swapping `runST` to the lazy version, it compiles and runs. Thank you! -----Original Message----- From: Peter Gammie [mailto:peteg42@gmail.com] Sent: Mittwoch, 22. Juli 2009 01:25 To: Christian Klauser Cc: glasgow-haskell-users@haskell.org Subject: Re: "Could not deduce (MArray (STUArray s) Int (ST s)) from context ()" when applying runST On 22/07/2009, at 9:16 AM, Christian Klauser wrote:
Thank you, works indeed with the strict ST monad. Didn't think of that. But makes kind of sense not to define these instances, since unboxed values cannot have their computation delayed. It's a bit unfortunate, however, that a single use of an unboxed array "forces" the whole state thread to become strict.
Hmm. Have you seen the strictToLazyST function? http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad-ST- Lazy.html#v%3AstrictToLazyST cheers peter
participants (3)
-
Christian Klauser
-
David Menendez
-
Peter Gammie