Skip to content

Commit

Permalink
Create pointed set (#31)
Browse files Browse the repository at this point in the history
* Define PointedSet type class

* Add PointedSet to cabal file

* Fix quantification of PointedSet module name

* Define a Bag as a PointedSet
  • Loading branch information
MatBon01 authored Apr 6, 2023
1 parent 177617b commit b6348ee
Show file tree
Hide file tree
Showing 4 changed files with 26 additions and 2 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -22,10 +22,10 @@ extra-source-files:
README.md

library
exposed-modules: Data.Bag
exposed-modules: Data.Bag, Data.PointedSet, Data.CMonoid

-- Modules included in this library but not exported.
other-modules: Data.CMonoid
-- other-modules:

-- LANGUAGE extensions used by modules in this package.
-- other-extensions:
Expand Down
9 changes: 9 additions & 0 deletions src/Data/Bag.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
{-# LANGUAGE InstanceSigs #-}
module Data.Bag where

import Data.List
import Data.CMonoid
import qualified Data.PointedSet as Pointed

newtype Bag a = Bag {elements :: [a]}
deriving (Show)
Expand Down Expand Up @@ -34,6 +36,13 @@ instance Monoid (Bag a) where

instance CMonoid (Bag a)

instance Pointed.PointedSet (Bag a) where
null = empty
isNull :: Bag a -> Bool
-- Implement isNull with pattern matching to not require Eq a
isNull (Bag []) = True
isNull _ = False

empty :: Bag a
empty = Bag []

Expand Down
5 changes: 5 additions & 0 deletions src/Data/PointedSet.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
module Data.PointedSet where

class PointedSet a where
null :: a
isNull :: a -> Bool
10 changes: 10 additions & 0 deletions test/Data/BagSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@ module Data.BagSpec (spec) where

import Test.Hspec
import qualified Data.Bag as Bag
import qualified Data.PointedSet as Pointed

import Control.Applicative

Expand Down Expand Up @@ -66,6 +67,15 @@ spec = do
describe "Data.Bag CMonoid" $ do
it "has a commutative operator <>" $ do
(b1 <> b2) `shouldBe` (b2 <> b1)
describe "Data.Bag Pointed Set" $ do
it "has empty as its null" $ do
(Pointed.null :: Bag.Bag Int) `shouldBe` (Bag.empty :: Bag.Bag Int)
it "has mempty as its null" $ do
(Pointed.null :: Bag.Bag Char) `shouldBe` (mempty :: Bag.Bag Char)
it "correctly identifies null" $ do
Pointed.isNull (Bag.empty :: Bag.Bag Int) `shouldBe` True
it "does not identify a non-empty Bag as null" $ do
Pointed.isNull (Bag.Bag [1, 2, 4]) `shouldBe` False
where
b1 = Bag.Bag ['a', 'b', 'c']
b2 = Bag.Bag ['b', 'c', 'd']
Expand Down

0 comments on commit b6348ee

Please sign in to comment.