Skip to content

Commit 6d7a272

Browse files
committed
restore heap example (#18)
1 parent d83ffdf commit 6d7a272

File tree

3 files changed

+15
-16
lines changed

3 files changed

+15
-16
lines changed

examples/Foreign/Heap.hs

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE FlexibleInstances #-}
2+
{-# LANGUAGE LinearTypes #-}
23
{-# LANGUAGE MultiParamTypeClasses #-}
34
{-# LANGUAGE NoImplicitPrelude #-}
45
{-# LANGUAGE ScopedTypeVariables #-}
@@ -45,11 +46,13 @@ mergeN (Heap k1 a1 h1) (Heap k2 a2 h2) pool =
4546
--- XXX: this is a good example of why we need a working `case` and/or
4647
--- `let`.
4748
testAndRebuild :: Unrestricted k ->. a ->. Box (List (NEHeap k a)) ->. Unrestricted k ->. a ->. Box (List (NEHeap k a)) ->. Pool ->. NEHeap k a
48-
testAndRebuild (Unrestricted k1') a1' h1' (Unrestricted k2') a2' h2' pool' =
49-
if k1' <= k2' then
50-
Heap k1' a1' (Manual.alloc (List.Cons (Heap k2' a2' h2') h1') pool')
51-
else
52-
Heap k2' a2' (Manual.alloc (List.Cons (Heap k1' a1' h1') h2') pool')
49+
testAndRebuild (Unrestricted k1') a1' h1' (Unrestricted k2') a2' h2' =
50+
if k1' <= k2'
51+
then helper k1' a1' k2' a2' h1' h2'
52+
else helper k2' a2' k1' a1' h2' h1'
53+
54+
helper :: k -> a ->. k -> a ->. Box (List (NEHeap k a)) ->. Box (List (NEHeap k a)) ->. Pool ->. NEHeap k a
55+
helper k1'' a1'' k2'' a2'' h1'' h2'' pool'' = Heap k1'' a1'' (Manual.alloc (List.Cons (Heap k2'' a2'' h2'') h1'') pool'')
5356

5457
mergeN' :: forall k a. (Manual.Representable k, Manual.Representable a, Movable k, Ord k) => NEHeap k a ->. Heap k a ->. Pool ->. NEHeap k a
5558
mergeN' h Empty pool = pool `lseq` h

examples/Spec.hs

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -5,11 +5,9 @@
55

66
import Control.Exception
77
import Control.Monad as P (void)
8-
-- TODO: restore (see #18)
9-
-- import qualified Data.List as L
8+
import qualified Data.List as L
109
import Data.Typeable
11-
-- TODO: restore (see #18)
12-
-- import qualified Foreign.Heap as Heap
10+
import qualified Foreign.Heap as Heap
1311
import Foreign.List (List)
1412
import qualified Foreign.List as List
1513
import Foreign.Marshal.Pure (Pool)
@@ -70,8 +68,7 @@ main = hspec P.$ do
7068
)
7169

7270

73-
-- TODO: restore (see #18)
74-
-- describe "Off-heap heaps" $ do
75-
-- describe "sort" $ do
76-
-- it "sorts" $
77-
-- property (\(l :: [(Int, ())]) -> Heap.sort l == (L.reverse $ L.sort l))
71+
describe "Off-heap heaps" P.$ do
72+
describe "sort" P.$ do
73+
it "sorts" P.$
74+
property (\(l :: [(Int, ())]) -> Heap.sort l == (L.reverse P.$ L.sort l))

linear-base.cabal

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,8 +56,7 @@ test-suite examples
5656
main-is: Spec.hs
5757
other-modules:
5858
Foreign.List
59-
-- TODO: restore (see #18)
60-
-- Foreign.Heap
59+
Foreign.Heap
6160
build-depends:
6261
base,
6362
hspec,

0 commit comments

Comments
 (0)