Efficiency of using field labels vs pattern matching
Brian Hulley
brianh at metamilk.com
Sun Aug 20 15:47:11 EDT 2006
Bulat Ziganshin wrote:
> btw, if you want beter efficiency, you may use unboxed
> references (http://haskell.org/haskellwiki/Library/ArrayRef)
Thanks for the pointer to your ArrayRef library. I've downloaded it and it
will be very useful - its extremely neat that the fact that something is
stored as unboxed can be hidden from the rest of the program.
One thing I wondered was if the functional dependency in Data.Ref.Universal
from the result type to the monad is actually necessary, since this FD
prevents me adding an instance for MonadIO ie the following instance is not
valid:
instance MonadIO m => URef m IOURef where
-- m -> r is fine
-- r -> m restricts m too much
Of course this isn't a big problem because I can simply define lifted
versions separately ie:
import Data.Ref hiding(newURef, readURef, writeURef)
import GHC.Unboxed
import Control.Monad.Trans
-- instance MonadIO m => URef m IOURef where
newURef :: (Unboxed a, MonadIO m) => a -> m (IOURef a)
newURef v = liftIO $ newIOURef v
readURef :: (Unboxed a, MonadIO m) => IOURef a -> m a
readURef ref = liftIO $ readIOURef ref
writeURef :: (Unboxed a, MonadIO m) => IOURef a -> a -> m ()
writeURef ref v = liftIO $ writeIOURef ref v
-- test monad
newtype SomeIO a = SomeIO {runSomeIO :: (IO a)} deriving (Monad,
MonadIO)
foo :: SomeIO Int
foo = do
xRef <- newURef (57::Int)
readURef xRef
main = do
x <- runSomeIO foo
print x
_ <- getChar
return ()
Anyway thanks for sharing your library. I'm going to put the URef functions
above into a module so I can use the same names for URef functions (ie
URef.T, new, read, write) as I'm already using for boxed refs.
Best regards,
Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.
http://www.metamilk.com
More information about the Glasgow-haskell-users
mailing list