[Haskell-cafe] lazy skip list?

Felipe Lessa felipe.lessa at gmail.com
Thu Aug 19 23:27:29 EDT 2010


Hmmmm....


{-# LANGUAGE GADTs, EmptyDataDecls, KindSignatures #-}

data Z :: *
data S :: * -> *

----------------------------------------------------------------------

data SkipList s a where
    Empty :: SkipList s a
    Cons  :: Element (S s) a -> SkipList (S s) a -> SkipList s a

instance Show a => Show (SkipList s a) where
    showsPrec d Empty =
        showString "Empty"
    showsPrec d (Cons elm xs) =
        showParen (d > 10) $
        showString "Cons " .
        showsPrec 11 elm . (' ':) .
        showsPrec 11 xs

----------------------------------------------------------------------

data Element s a where
    None   :: Element s a
    Branch :: !Int -> a -> Element s a -> Element s a -> Element (S s) a

instance Show a => Show (Element s a) where
    showsPrec d None =
        showString "None"
    showsPrec d (Branch sz x l r) =
        showParen (d > 10) $
        showString "Branch " .
        showsPrec 11 sz . (' ':) .
        showsPrec 11 x  . (' ':) .
        showsPrec 11 l  . (' ':) .
        showsPrec 11 r

sizeE :: Element s a -> Int
sizeE None             = 0
sizeE (Branch n _ _ _) = n

branch :: a -> Element s a -> Element s a -> Element (S s) a
branch x l r = Branch (sizeE l + sizeE r + 1) x l r

----------------------------------------------------------------------

fromList :: ElementFromList s => [a] -> SkipList s a
fromList [] = Empty
fromList xs = let (elm, xs') = elementFromList xs
              in Cons elm (fromList xs')

class ElementFromList s where
    elementFromList :: [a] -> (Element s a, [a])

instance ElementFromList Z where
    elementFromList xs = (None, xs)

instance ElementFromList s => ElementFromList (S s) where
    elementFromList []     = (None, [])
    elementFromList (x:xs) =
        let (elmL, xsL) = elementFromList xs
            (elmR, xsR) = elementFromList xsL
        in (branch x elmL elmR, xsR)

----------------------------------------------------------------------

toList :: SkipList s a -> [a]
toList Empty         = []
toList (Cons elm xs) = go elm (toList xs)
    where
      go :: Element s a -> [a] -> [a]
      go None             rest = rest
      go (Branch _ x l r) rest = x : go l (go r rest)

----------------------------------------------------------------------

class Nth s where
    nth :: Element s a -> Int -> Either Int a

instance Nth Z where
    nth None i = Left i

instance Nth s => Nth (S s) where
    nth None             i             = Left i
    nth (Branch n x l r) i | i == 0    = Right x
                           | i >= n    = Left (i-n)
                           | otherwise = either (nth r) Right $ nth l (i-1)

index :: Nth s => SkipList s a -> Int -> Maybe a
index Empty         _ = Nothing
index (Cons elm xs) i = either (index xs) Just $ nth elm i


-- 
Felipe.


More information about the Haskell-Cafe mailing list