
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 Code can contain some typos. Sergey Mironov пишет:
Hi cafe! I have a question of C-to-Haskell type:)
Imagine web application wich allows users to browse some shared filesystem located at the server. Application stores every users's position within that filesystem (current directory or file).
In C this can be implemented with the help of following data types:
struct tree_node { union item { // some file data struct file *file;
// struct dir has link to another list of tree_node struct dir *dir; }; int type;
// List of tree_nodes struct tree_node *next; struct tree_node *prev; };
struct user { struct tree_node *position;
// List of users struct user *next; struct user *prev; };
This implementation will give us 1) O(1) time to insert to shared tree 2) O(1) time to access user's current position
Is it possible to reach this requirements in haskell?
For example, managing distinct tree type like
data TreeNode = File | Dir [TreeNode]
will lead to failure of req. 2 (have to traverse this tree to find each user's position).
Also one could manage several zipper types (one for every user):
data TreeNodeCtx = Top | TreeNodeCtx { left :: [TreeNode], right :: [TreeNode], up :: TreeNodeCtx }
data TreeNodeZ = TreeNodeZ { ctx :: [TreeNodeCtx] pos :: TreeNode }
It works for one user but not for many because of req. 1 (have to insert new item into several zippers).
Any ideas?