[Hugs-users] one more problem with Hugs

Bulat Ziganshin bulat.ziganshin at gmail.com
Tue Mar 7 06:57:47 EST 2006


Hello ,

The following code compiles with GHC but not with Hugs. moreover, if
you replace STURef with STRef in instance definition, all will be
fine. bug?



{-# OPTIONS_GHC -cpp -fglasgow-exts #-}
import Control.Monad.ST
import Data.STRef

-- -----------------------------------------------------------------------------
-- Unboxed references in ST monad

type STURef = STRef

-- | Create new unboxed reference in ST monad
newSTURef :: e -> ST s (STURef s e)
newSTURef = newSTRef

-- -----------------------------------------------------------------------------
-- Monad-neutral interface for fast unboxed references

class (Monad m) => URef m r | m->r, r->m where
    newURef   :: a -> m (r a)

instance URef (ST s) (STURef s) where
    newURef = newSTURef

-- -----------------------------------------------------------------------------
-- Main

test = runST ( do newURef (0::Int)
                  return '1'
             )

  

-- 
Best regards,
 Bulat                          mailto:Bulat.Ziganshin at gmail.com



More information about the Hugs-Users mailing list