Skip to content

Commit 992f963

Browse files
committed
Adding stacks and queues
1 parent 7439f28 commit 992f963

File tree

4 files changed

+159
-2
lines changed

4 files changed

+159
-2
lines changed

linear-base.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,9 @@ library
5858
Data.Ord.Linear.Internal.Eq
5959
Data.Profunctor.Kleisli.Linear
6060
Data.Profunctor.Linear
61+
Data.Queue.Mutable.Linear
6162
Data.Set.Mutable.Linear
63+
Data.Stack.Mutable.Linear
6264
Data.Tuple.Linear
6365
Data.Unrestricted.Internal.Consumable
6466
Data.Unrestricted.Internal.Dupable

src/Data/Deque/Mutable/Linear.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@ module Data.Deque.Mutable.Linear
1919
, alloc
2020
, fromList
2121
-- * Querying
22-
, size
2322
, length
2423
, peekFront
2524
, peekBack
@@ -86,7 +85,7 @@ nextPtr sz (Ptr p) = (p + 1) `mod` sz
8685
-- # Allocation
8786
-------------------------------------------------------------------------------
8887

89-
-- | Run a computation of an empty Deque with a given size
88+
-- | Run a computation of an empty Deque with a given initial allocated size
9089
alloc :: Int -> (Deque a %1-> Ur b) %1-> Ur b
9190
alloc k f = Array.alloc k err $ \arr -> f (Deque 0 0 arr) where
9291
err = Prelude.error "Accessing error element of a collection!"

src/Data/Queue/Mutable/Linear.hs

Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
{-# LANGUAGE GADTs #-}
2+
{-# LANGUAGE LinearTypes #-}
3+
{-# LANGUAGE NoImplicitPrelude #-}
4+
5+
-- | Mutable linear queues
6+
--
7+
-- This module provides mutable queues with a pure API. Import thusly:
8+
--
9+
-- > import qualified Data.Queue.Mutable.Linear as Linear
10+
--
11+
module Data.Queue.Mutable.Linear
12+
(
13+
-- * Construction
14+
Queue
15+
, alloc
16+
, fromList
17+
-- * Modification
18+
, push
19+
, pop
20+
, map
21+
-- * Querying
22+
, top
23+
, length
24+
-- * Consumption
25+
, toList
26+
)
27+
where
28+
29+
import Data.Deque.Mutable.Linear (Deque)
30+
import qualified Data.Deque.Mutable.Linear as Deque
31+
import qualified Data.Functor.Linear as Data
32+
import Data.Unrestricted.Linear
33+
import Prelude.Linear hiding (length, map)
34+
35+
36+
-- # API
37+
-------------------------------------------------------------------------------
38+
39+
data Queue a where
40+
Queue :: {-# UNPACK #-} !(Deque a) %1-> Queue a
41+
-- We represent a queue as a Deque where we add to the front end
42+
-- and take from the back end
43+
44+
unqueue :: Queue a %1-> Deque a
45+
unqueue (Queue deq) = deq
46+
47+
-- | Allocate a queue with a given initial allocated size
48+
alloc :: Int -> (Queue a %1-> Ur b) %1-> Ur b
49+
alloc k f = Deque.alloc k $ \deq -> f (Queue deq)
50+
51+
-- | Given a list, make a queue where we treat the end of the list
52+
-- as the top of the queue, the first-in-line element
53+
fromList :: [a] -> (Queue a %1-> Ur b) %1-> Ur b
54+
fromList xs f = Deque.fromList xs $ \deq -> f (Queue deq)
55+
56+
push :: a -> Queue a %1-> Queue a
57+
push x = Queue . Deque.pushFront x . unqueue
58+
59+
pop :: Queue a %1-> (Ur (Maybe a), Queue a)
60+
pop = Data.fmap Queue . Deque.popBack . unqueue
61+
62+
map :: (a -> b) -> Queue a %1-> Queue b
63+
map f = Queue . Deque.map f . unqueue
64+
65+
top :: Queue a %1-> (Ur (Maybe a), Queue a)
66+
top = Data.fmap Queue . Deque.peekBack . unqueue
67+
68+
length :: Queue a %1-> (Ur Int, Queue a)
69+
length = Data.fmap Queue . Deque.length . unqueue
70+
71+
-- | Convert to a list where the head of the
72+
-- list is the top of the stack
73+
toList :: Queue a %1-> Ur [a]
74+
toList = Deque.toList . unqueue
75+
76+
instance Consumable (Queue a) where
77+
consume (Queue deq) = consume deq
78+

src/Data/Stack/Mutable/Linear.hs

Lines changed: 78 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,78 @@
1+
{-# LANGUAGE GADTs #-}
2+
{-# LANGUAGE LinearTypes #-}
3+
{-# LANGUAGE NoImplicitPrelude #-}
4+
5+
-- | Mutable linear stacks
6+
--
7+
-- This module provides mutable stacks with a pure API. Import thusly:
8+
--
9+
-- > import qualified Data.Stack.Mutable.Linear as Linear
10+
--
11+
module Data.Stack.Mutable.Linear
12+
(
13+
-- * Construction
14+
Stack
15+
, alloc
16+
, fromList
17+
-- * Modification
18+
, push
19+
, pop
20+
, map
21+
-- * Querying
22+
, top
23+
, length
24+
-- * Consumption
25+
, toList
26+
)
27+
where
28+
29+
import Data.Deque.Mutable.Linear (Deque)
30+
import qualified Data.Deque.Mutable.Linear as Deque
31+
import qualified Data.Functor.Linear as Data
32+
import Data.Unrestricted.Linear
33+
import Prelude.Linear hiding (length, map)
34+
35+
36+
-- # API
37+
-------------------------------------------------------------------------------
38+
39+
data Stack a where
40+
Stack :: {-# UNPACK #-} !(Deque a) %1-> Stack a
41+
-- We represent a stack as a Deque where we grow and
42+
-- shrink from the **front** end
43+
44+
unstack :: Stack a %1-> Deque a
45+
unstack (Stack deq) = deq
46+
47+
-- | Allocate a stack with a given initial allocated size
48+
alloc :: Int -> (Stack a %1-> Ur b) %1-> Ur b
49+
alloc k f = Deque.alloc k $ \deq -> f (Stack deq)
50+
51+
-- | Given a list, make a stack where we treat the head of the list
52+
-- as the top of the stack
53+
fromList :: [a] -> (Stack a %1-> Ur b) %1-> Ur b
54+
fromList xs f = Deque.fromList xs $ \deq -> f (Stack deq)
55+
56+
push :: a -> Stack a %1-> Stack a
57+
push x = Stack . Deque.pushFront x . unstack
58+
59+
pop :: Stack a %1-> (Ur (Maybe a), Stack a)
60+
pop = Data.fmap Stack . Deque.popFront . unstack
61+
62+
map :: (a -> b) -> Stack a %1-> Stack b
63+
map f = Stack . Deque.map f . unstack
64+
65+
top :: Stack a %1-> (Ur (Maybe a), Stack a)
66+
top = Data.fmap Stack . Deque.peekFront . unstack
67+
68+
length :: Stack a %1-> (Ur Int, Stack a)
69+
length = Data.fmap Stack . Deque.length . unstack
70+
71+
-- | Convert to a list where the head of the
72+
-- list is the top of the stack
73+
toList :: Stack a %1-> Ur [a]
74+
toList = Deque.toList . unstack
75+
76+
instance Consumable (Stack a) where
77+
consume (Stack deq) = consume deq
78+

0 commit comments

Comments
 (0)