15 июля 2010 г. 2:01 пользователь Victor Gorokhov <m...@rkit.pp.ru> написал: > You can implement pure pointers on top of Data.Map with O(log n) time: > > {-# LANGUAGE ExistentialQuantification #-} > import Data.Map ( Map ) > import qualified Data.Map as Map > import Data.Typeable > import Control.Monad.State > import Data.Maybe > > type PointerSpace = Map Int PackedValue > newtype Pointer a = Pointer Int > data PackedValue = forall a. Typeable a => PackedValue a > > readPointer :: Pointer a -> State PointerSpace a > readPointer ( Pointer key ) = do > space <- get > return $ fromJust $ cast $ Map.find key space > > writePointer :: a -> Pointer a -> State PointerSpace () > writePointer a ( Pointer key ) = do > space <- get > put $ Map.insert key ( PackedValue a ) space > > newPointer :: a -> State PointerSpace ( Pointer a ) > newPointer a = do > space <- get > let key = findEmptyKey space -- implement it yourself > p = Pointer key > writePointer a p > return p
Thanks for an example! Probably, one can think about using Arrays instead of Map or IntMap in order to achieve 'true' O(1) in pure. But I suppose that there are some trouble with array expanding. Or somebody would already make it. -- Thanks, Sergey _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe