Skip to content

Commit

Permalink
Accepted patch from Daniel Lyons
Browse files Browse the repository at this point in the history
  • Loading branch information
bhickey committed Jul 8, 2010
1 parent 565d55f commit 01e33cf
Show file tree
Hide file tree
Showing 4 changed files with 17 additions and 5 deletions.
5 changes: 4 additions & 1 deletion Data/Heap/Pairing.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE RankNTypes #-}
--
-- Copyright (c) 2010 Brendan Hickey - http://bhickey.net
-- New BSD License (see http://www.opensource.org/licenses/bsd-license.php)
Expand All @@ -8,7 +9,6 @@ module Data.Heap.Pairing
where

import Prelude hiding (head, tail, null)
import qualified Data.List as L

data (Ord a) => PairingHeap a =
EmptyHeap
Expand Down Expand Up @@ -60,7 +60,10 @@ toList = toAscList
fromList :: (Ord a) => [a] -> PairingHeap a
fromList = fromAscList

mergeList :: forall a. (Ord a) => [PairingHeap a] -> PairingHeap a
mergeList [a] = a
mergeList x = mergeList (mergePairs x)

mergePairs :: forall a. (Ord a) => [PairingHeap a] -> [PairingHeap a]
mergePairs (a:b:c) = merge a b : mergePairs c
mergePairs x = x
1 change: 0 additions & 1 deletion Data/Heap/Skew.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ module Data.Heap.Skew
where

import Prelude hiding (head, tail, null)
import qualified Data.List as L

data (Ord a) => SkewHeap a =
SkewLeaf
Expand Down
8 changes: 6 additions & 2 deletions Data/Tree/AVL.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,13 +8,17 @@ module Data.Tree.AVL
where

import Prelude hiding (head, tail, (!!), lookup, null)
import Data.Maybe


data AVLTree k v =
Leaf
| AVLTree !k !v !Int !Int !(AVLTree k v) !(AVLTree k v) deriving (Ord, Eq, Show)


instance Functor (AVLTree k) where
fmap _ Leaf = Leaf
fmap f (AVLTree k v lh rh l r) = AVLTree k (f v) lh rh (fmap f l) (fmap f r)


-- | /O(1)/. 'singleton' constructs a singleton AVL tree
singleton :: (Ord k) => k -> v -> AVLTree k v
singleton k v = AVLTree k v 1 1 Leaf Leaf
Expand Down
8 changes: 7 additions & 1 deletion Data/Tree/Splay.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,6 +13,12 @@ data (Ord k) => SplayTree k v =
Leaf
| SplayTree k v Int (SplayTree k v) (SplayTree k v) deriving (Ord, Eq)


instance (Ord k) => Functor (SplayTree k) where
fmap _ Leaf = Leaf
fmap f (SplayTree k v h l r) = SplayTree k (f v) h (fmap f l) (fmap f r)


-- | /O(1)/. 'singleton' constructs a splay tree containing one element.
singleton :: (Ord k) => (k,v) -> SplayTree k v
singleton (k,v) = SplayTree k v 0 Leaf Leaf
Expand Down Expand Up @@ -83,7 +89,7 @@ zig _ Leaf = error "tree corruption"
zig (SplayTree k1 v1 _ l1 r1) (SplayTree k v d _ r) =
SplayTree k1 v1 d l1 (SplayTree k v (d - size l1 - 1) r1 r)

-- | /O(1)/. zig rotates its second argument up
-- | /O(1)/. zag rotates its second argument up
zag :: (Ord k) => SplayTree k v -> SplayTree k v -> SplayTree k v
zag Leaf _ = error "tree corruption"
zag _ Leaf = error "tree corruption"
Expand Down

0 comments on commit 01e33cf

Please sign in to comment.