module SMR.Data.Bag where
import Prelude hiding (map)
import qualified Data.List as List
data Bag a
= BagNil
| BagElem a
| BagList [a]
| BagUnion (Bag a) (Bag a)
deriving Show
nil :: Bag a
nil = BagNil
singleton :: a -> Bag a
singleton x
= BagElem x
list :: [a] -> Bag a
list xs
= BagList xs
union :: Bag a -> Bag a -> Bag a
union xs1 xs2
= BagUnion xs1 xs2
toList :: Bag a -> [a]
toList bag
= go [] bag
where
go xs1 BagNil = xs1
go xs1 (BagElem x) = x : xs1
go xs1 (BagList xs2) = go_list xs1 xs2
go xs1 (BagUnion b1 b2) = go (go xs1 b1) b2
go_list _ [] = []
go_list xs1 (x : xs2) = go_list (x : xs1) xs2
map :: (a -> b) -> Bag a -> Bag b
map f bag
= case bag of
BagNil -> BagNil
BagElem x -> BagElem (f x)
BagList xs -> BagList (List.map f xs)
BagUnion b1 b2 -> BagUnion (map f b1) (map f b2)