module Data.Binding.List (module Data.Binding.Simple, BindingList, toBindingList, fromBindingList, length, position, seek, seekBy, next, prev, remove', remove, insert', insert) where
import Prelude hiding (length)
import qualified Prelude as P
import Control.Monad
import Data.Binding.Simple
data BindingList v a = Variable v => BindingList {source :: Source v a
,list :: v [v a]
,pos :: v Int}
toBindingList :: Variable v => [a] -> IO (BindingList v a)
toBindingList [] = error "empty list"
toBindingList list = do list'<- mapM newVar list >>= newVar
source <- newVar (head list)
pos <- newVar 0
return $ BindingList source list' pos
update :: BindingList v a -> IO ()
update (BindingList source list pos) = do list' <- readVar list
pos' <- readVar pos
readVar source >>= writeVar (list' !! pos')
fromBindingList :: Variable v => BindingList v a -> IO [a]
fromBindingList b = do update b
readVar (list b) >>= mapM readVar
instance Variable v => Variable (BindingList v) where
newVar = warn where warn a = toBindingList [a]
readVar = readVar . source
writeVar = writeVar . source
modifyVar = modifyVar . source
modifyVar' = modifyVar' . source
instance Variable v => Bindable (BindingList v) where
bind = bind . source
length :: Variable v => BindingList v a -> IO Int
length b = do list <- readVar (list b)
return $ P.length list
position :: Variable v => BindingList v a -> IO Int
position b = readVar $ pos b
seek:: Variable v => BindingList v a -> Int -> IO Int
seek b new = do pos' <- readVar $ pos b
if pos' == new then return new else update b >> seek' b new
seek':: BindingList v a -> Int -> IO Int
seek' (BindingList source list pos) new = do list' <- readVar list
readVar (list' !! new) >>= writeVar source
writeVar pos new
return new
seekBy :: Variable v => (Int -> Int) -> BindingList v a -> IO Int
seekBy f bindingList = do pos <- readVar (pos bindingList)
seek bindingList $ f pos
next :: Variable v => BindingList v a -> IO Int
next = seekBy succ
prev :: Variable v => BindingList v a -> IO Int
prev = seekBy pred
remove' :: [a] -> Int -> [a]
remove' list pos = let (xs, _:ys) = splitAt pos list
in xs ++ ys
remove :: BindingList v a -> IO Int
remove b@(BindingList _ list pos) = do list' <- readVar list
pos' <- readVar pos
writeVar list $ remove' list' pos'
seek' b (if pos' == P.length list' 1 then pos' 1 else pos')
insert' :: [a] -> Int -> a -> [a]
insert' list pos x = let (xs, ys) = splitAt pos list
in xs ++ [x] ++ ys
insert :: BindingList v a -> a -> IO Int
insert b@(BindingList _ list pos) x = do update b
list' <- readVar list
pos' <- readVar pos
x' <- newVar x
let pos'' = pos' + 1
writeVar list $ insert' list' pos'' x'
seek' b pos''