Skip to content

Commit

Permalink
implement instance Foldable EphemeralQueue
Browse files Browse the repository at this point in the history
  • Loading branch information
mitchellwrosen committed Jan 13, 2024
1 parent ee4f5e6 commit bf30ad5
Show file tree
Hide file tree
Showing 2 changed files with 25 additions and 10 deletions.
4 changes: 0 additions & 4 deletions src/Queue.hs
Original file line number Diff line number Diff line change
Expand Up @@ -93,10 +93,6 @@ instance Foldable Queue where
Empty -> mempty
Front x xs -> f x <> go xs

elem :: (Eq a) => a -> Queue a -> Bool
elem x (Q xs ys _) =
List.elem x xs || List.elem x ys

null :: Queue a -> Bool
null =
isEmpty
Expand Down
31 changes: 25 additions & 6 deletions src/Queue/Ephemeral.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,7 @@ module Queue.Ephemeral
where

import Data.Foldable qualified as Foldable
import Data.List qualified as List
import Data.Traversable qualified as Traversable
import Prelude hiding (foldMap, length, map, span, traverse)

Expand All @@ -69,10 +70,26 @@ data EphemeralQueue a
= Q [a] [a]
deriving stock (Eq, Functor)

-- TODO
instance Foldable EphemeralQueue where
foldMap :: (a -> m) -> EphemeralQueue a -> m
foldMap = undefined
foldMap :: (Monoid m) => (a -> m) -> EphemeralQueue a -> m
foldMap f =
go
where
go = \case
Empty -> mempty
Front x xs -> f x <> go xs

elem :: (Eq a) => a -> EphemeralQueue a -> Bool
elem x (Q xs ys) =
List.elem x xs || List.elem x ys

null :: EphemeralQueue a -> Bool
null =
isEmpty

toList :: EphemeralQueue a -> [a]
toList =
Queue.Ephemeral.toList

instance Monoid (EphemeralQueue a) where
mempty :: EphemeralQueue a
Expand All @@ -82,16 +99,18 @@ instance Monoid (EphemeralQueue a) where
-- | \(\mathcal{O}(n)\), where \(n\) is the size of the second argument.
instance Semigroup (EphemeralQueue a) where
(<>) :: EphemeralQueue a -> EphemeralQueue a -> EphemeralQueue a
Q as bs <> Q cs ds = Q as (ds ++ reverse cs ++ bs)
Q as bs <> Q cs ds =
Q as (ds ++ reverse cs ++ bs)

instance (Show a) => Show (EphemeralQueue a) where
show :: EphemeralQueue a -> String
show = show . toList
show =
show . Queue.Ephemeral.toList

instance Traversable EphemeralQueue where
traverse :: (Applicative f) => (a -> f b) -> EphemeralQueue a -> f (EphemeralQueue b)
traverse =
traverse
Queue.Ephemeral.traverse

------------------------------------------------------------------------------------------------------------------------
-- Patterns
Expand Down

0 comments on commit bf30ad5

Please sign in to comment.