Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

How to create a polymorphic unboxed array within ST monad?

Tags:

haskell

This code compiles with no problem:

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)

But, this:

new :: e -> UArray Int e
new a = runSTUArray (newArray (0, 9) a)

fails as one would expect, with error:

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)

However, adding the type-class constraint would not help, as changing the type signature to

new :: (MArray (STUArray s) e (ST s)) => e -> UArray Int e

would still fail with

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

any way to make this work?


EDIT: Found out this has already been discussed on Haskell and Haskell-Cafe mailing list, with this minimal solution taken from 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
like image 202
behzad.nouri Avatar asked Nov 30 '25 05:11

behzad.nouri


1 Answers

The following seems to work. I don't know if it can be minimized. One downside is that you will need to add an instance of Unboxable for each MArray instance that you'll want to be able to use -- but at least thanks to DefaultSignatures you don't have to write any actual code. I've included an instance for Int to show what I mean.

{-# 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

The Dict type comes from Edward Kmett's constraints package.

like image 50
Daniel Wagner Avatar answered Dec 01 '25 21:12

Daniel Wagner