diff --git a/linear-base.cabal b/linear-base.cabal index f6c641d4..b955280e 100644 --- a/linear-base.cabal +++ b/linear-base.cabal @@ -58,7 +58,9 @@ library Data.Ord.Linear.Internal.Eq Data.Profunctor.Kleisli.Linear Data.Profunctor.Linear + Data.Queue.Mutable.Linear Data.Set.Mutable.Linear + Data.Stack.Mutable.Linear Data.Tuple.Linear Data.Unrestricted.Internal.Consumable Data.Unrestricted.Internal.Dupable diff --git a/src/Data/Deque/Mutable/Linear.hs b/src/Data/Deque/Mutable/Linear.hs index 2a516d45..b0f96a31 100644 --- a/src/Data/Deque/Mutable/Linear.hs +++ b/src/Data/Deque/Mutable/Linear.hs @@ -19,7 +19,6 @@ module Data.Deque.Mutable.Linear , alloc , fromList -- * Querying - , size , length , peekFront , peekBack @@ -86,7 +85,7 @@ nextPtr sz (Ptr p) = (p + 1) `mod` sz -- # Allocation ------------------------------------------------------------------------------- --- | Run a computation of an empty Deque with a given size +-- | Run a computation of an empty Deque with a given initial allocated size alloc :: Int -> (Deque a %1-> Ur b) %1-> Ur b alloc k f = Array.alloc k err $ \arr -> f (Deque 0 0 arr) where err = Prelude.error "Accessing error element of a collection!" diff --git a/src/Data/Queue/Mutable/Linear.hs b/src/Data/Queue/Mutable/Linear.hs new file mode 100644 index 00000000..d963c9a0 --- /dev/null +++ b/src/Data/Queue/Mutable/Linear.hs @@ -0,0 +1,78 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LinearTypes #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- | Mutable linear queues +-- +-- This module provides mutable queues with a pure API. Import thusly: +-- +-- > import qualified Data.Queue.Mutable.Linear as Linear +-- +module Data.Queue.Mutable.Linear + ( + -- * Construction + Queue + , alloc + , fromList + -- * Modification + , push + , pop + , map + -- * Querying + , top + , length + -- * Consumption + , toList + ) +where + +import Data.Deque.Mutable.Linear (Deque) +import qualified Data.Deque.Mutable.Linear as Deque +import qualified Data.Functor.Linear as Data +import Data.Unrestricted.Linear +import Prelude.Linear hiding (length, map) + + +-- # API +------------------------------------------------------------------------------- + +data Queue a where + Queue :: {-# UNPACK #-} !(Deque a) %1-> Queue a + -- We represent a queue as a Deque where we add to the front end + -- and take from the back end + +unqueue :: Queue a %1-> Deque a +unqueue (Queue deq) = deq + +-- | Allocate a queue with a given initial allocated size +alloc :: Int -> (Queue a %1-> Ur b) %1-> Ur b +alloc k f = Deque.alloc k $ \deq -> f (Queue deq) + +-- | Given a list, make a queue where we treat the end of the list +-- as the top of the queue, the first-in-line element +fromList :: [a] -> (Queue a %1-> Ur b) %1-> Ur b +fromList xs f = Deque.fromList xs $ \deq -> f (Queue deq) + +push :: a -> Queue a %1-> Queue a +push x = Queue . Deque.pushFront x . unqueue + +pop :: Queue a %1-> (Ur (Maybe a), Queue a) +pop = Data.fmap Queue . Deque.popBack . unqueue + +map :: (a -> b) -> Queue a %1-> Queue b +map f = Queue . Deque.map f . unqueue + +top :: Queue a %1-> (Ur (Maybe a), Queue a) +top = Data.fmap Queue . Deque.peekBack . unqueue + +length :: Queue a %1-> (Ur Int, Queue a) +length = Data.fmap Queue . Deque.length . unqueue + +-- | Convert to a list where the head of the +-- list is the top of the stack +toList :: Queue a %1-> Ur [a] +toList = Deque.toList . unqueue + +instance Consumable (Queue a) where + consume (Queue deq) = consume deq + diff --git a/src/Data/Stack/Mutable/Linear.hs b/src/Data/Stack/Mutable/Linear.hs new file mode 100644 index 00000000..acb2e618 --- /dev/null +++ b/src/Data/Stack/Mutable/Linear.hs @@ -0,0 +1,78 @@ +{-# LANGUAGE GADTs #-} +{-# LANGUAGE LinearTypes #-} +{-# LANGUAGE NoImplicitPrelude #-} + +-- | Mutable linear stacks +-- +-- This module provides mutable stacks with a pure API. Import thusly: +-- +-- > import qualified Data.Stack.Mutable.Linear as Linear +-- +module Data.Stack.Mutable.Linear + ( + -- * Construction + Stack + , alloc + , fromList + -- * Modification + , push + , pop + , map + -- * Querying + , top + , length + -- * Consumption + , toList + ) +where + +import Data.Deque.Mutable.Linear (Deque) +import qualified Data.Deque.Mutable.Linear as Deque +import qualified Data.Functor.Linear as Data +import Data.Unrestricted.Linear +import Prelude.Linear hiding (length, map) + + +-- # API +------------------------------------------------------------------------------- + +data Stack a where + Stack :: {-# UNPACK #-} !(Deque a) %1-> Stack a + -- We represent a stack as a Deque where we grow and + -- shrink from the **front** end + +unstack :: Stack a %1-> Deque a +unstack (Stack deq) = deq + +-- | Allocate a stack with a given initial allocated size +alloc :: Int -> (Stack a %1-> Ur b) %1-> Ur b +alloc k f = Deque.alloc k $ \deq -> f (Stack deq) + +-- | Given a list, make a stack where we treat the head of the list +-- as the top of the stack +fromList :: [a] -> (Stack a %1-> Ur b) %1-> Ur b +fromList xs f = Deque.fromList xs $ \deq -> f (Stack deq) + +push :: a -> Stack a %1-> Stack a +push x = Stack . Deque.pushFront x . unstack + +pop :: Stack a %1-> (Ur (Maybe a), Stack a) +pop = Data.fmap Stack . Deque.popFront . unstack + +map :: (a -> b) -> Stack a %1-> Stack b +map f = Stack . Deque.map f . unstack + +top :: Stack a %1-> (Ur (Maybe a), Stack a) +top = Data.fmap Stack . Deque.peekFront . unstack + +length :: Stack a %1-> (Ur Int, Stack a) +length = Data.fmap Stack . Deque.length . unstack + +-- | Convert to a list where the head of the +-- list is the top of the stack +toList :: Stack a %1-> Ur [a] +toList = Deque.toList . unstack + +instance Consumable (Stack a) where + consume (Stack deq) = consume deq +