{-| Module  : WeakSets
Description : Homogeneous sets are sets which can contain only one type of values. They are more flexible than Data.Set because they do not require the objects contained to be orderable.
Copyright   : Guillaume Sabbagh 2022
License     : LGPL-3.0-or-later
Maintainer  : guillaumesabbagh@protonmail.com
Stability   : experimental
Portability : portable

Homogeneous sets are sets which can contain only one type of values.

They are more flexible than Data.Set because they do not require the objects contained to be orderable.

The datatype only assumes its components are equatable, it is therefore slower than the Data.Set datatype.

We use this datatype because most of the datatypes we care about are not orderable.

Inline functions related to homogeneous sets are written between pipes @|@.

Function names should not collide with Prelude but may collide with Data.Set.
-}

module Data.WeakSets.HomogeneousSet
(
    -- * Set datatype and smart constructor

    Set, -- abstract type, the smart constructor is `set`

    set, -- the smart constructor for `Set`

    -- * Set related functions

    setToList,
    isIncludedIn,
    cardinal,
    isIn,
    (|&|),
    (|||),
    (|*|),
    (|+|),
    (|-|),
    (|^|),
    powerSet,
    filterSet,
    nubSetBy,
    -- * Functions to work with `Maybe`

    setToMaybe,
    maybeToSet,
    catMaybesToSet,
    mapMaybeToSet,
)
where
    import              Data.List               (intercalate, nub, nubBy, intersect, union, (\\), subsequences)
    import              Data.Maybe
    
    -- | A homogeneous set is a list of values.

    --

    -- The only differences are that we don't want duplicate elements and we don't need the order of the list elements.

    --

    -- To force these constraints, the `Set` constructor is abstract and is not exported. The only way to construct a set is to use the smart constructor `set` which ensures the previous conditions.

    data Set a = Set [a]
    
    -- | /O(1)/. The smart constructor of sets. This is the only way of instantiating a `Set`.

    --

    -- If several elements are equal, they are kept until the user wants a list back.

    set :: [a] -> Set a
    set :: forall a. [a] -> Set a
set [a]
xs = [a] -> Set a
forall a. [a] -> Set a
Set [a]
xs
    
    instance (Show a) => Show (Set a) where
        show :: Set a -> String
show (Set [a]
xs) = String
"(set "String -> ShowS
forall a. [a] -> [a] -> [a]
++[a] -> String
forall a. Show a => a -> String
show [a]
xsString -> ShowS
forall a. [a] -> [a] -> [a]
++String
")"
    
    -- | /O(n^2)/. Return a boolean indicating if a `Set` is included in another one.

    isIncludedIn :: (Eq a) => Set a -> Set a -> Bool
    (Set []) isIncludedIn :: forall a. Eq a => Set a -> Set a -> Bool
`isIncludedIn` Set a
_ = Bool
True
    (Set (a
x:[a]
xs)) `isIncludedIn` (Set [a]
ys)
        | a
x a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [a]
ys = ([a] -> Set a
forall a. [a] -> Set a
Set [a]
xs) Set a -> Set a -> Bool
forall a. Eq a => Set a -> Set a -> Bool
`isIncludedIn` ([a] -> Set a
forall a. [a] -> Set a
Set [a]
ys)
        | Bool
otherwise = Bool
False
    
    instance (Eq a) => Eq (Set a) where
        Set a
x == :: Set a -> Set a -> Bool
== Set a
y = Set a
x Set a -> Set a -> Bool
forall a. Eq a => Set a -> Set a -> Bool
`isIncludedIn` Set a
y Bool -> Bool -> Bool
&& Set a
y Set a -> Set a -> Bool
forall a. Eq a => Set a -> Set a -> Bool
`isIncludedIn` Set a
x
        
    instance Semigroup (Set a) where
        (Set [a]
xs) <> :: Set a -> Set a -> Set a
<> (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> [a] -> [a]
forall a. Semigroup a => a -> a -> a
<> [a]
ys
        
    instance Monoid (Set a) where
        mempty :: Set a
mempty = [a] -> Set a
forall a. [a] -> Set a
Set []
    
    instance Foldable Set where
        foldr :: forall a b. (a -> b -> b) -> b -> Set a -> b
foldr a -> b -> b
f b
d (Set [a]
xs) = (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr a -> b -> b
f b
d [a]
xs

    instance Functor Set where
        fmap :: forall a b. (a -> b) -> Set a -> Set b
fmap a -> b
f (Set [a]
xs) = [b] -> Set b
forall a. [a] -> Set a
Set ([b] -> Set b) -> [b] -> Set b
forall a b. (a -> b) -> a -> b
$ a -> b
f (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a]
xs
    
    instance Applicative Set where
        pure :: forall a. a -> Set a
pure a
x = [a] -> Set a
forall a. [a] -> Set a
Set [a
x]
        <*> :: forall a b. Set (a -> b) -> Set a -> Set b
(<*>) (Set [a -> b]
fs) (Set [a]
xs) = [b] -> Set b
forall a. [a] -> Set a
Set ([b] -> Set b) -> [b] -> Set b
forall a b. (a -> b) -> a -> b
$ [a -> b]
fs [a -> b] -> [a] -> [b]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [a]
xs

    instance Monad Set where
        >>= :: forall a b. Set a -> (a -> Set b) -> Set b
(>>=) (Set [a]
xs) a -> Set b
f = [b] -> Set b
forall a. [a] -> Set a
Set ([b] -> Set b) -> [b] -> Set b
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (Set b -> [b]
forall a. Set a -> [a]
unsafeSetToList(Set b -> [b]) -> (a -> Set b) -> a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.a -> Set b
f)
    
    -- | /O(n)/. Transform a `Set` back into a list, the list returned does not have duplicate elements, the order of the original list holds.

    setToList :: (Eq a) => Set a -> [a]
    setToList :: forall a. Eq a => Set a -> [a]
setToList (Set [a]
xs) = [a] -> [a]
forall a. Eq a => [a] -> [a]
nub [a]
xs
    
    -- | /O(1)/. Gives the underlying list of a set without removing duplicates, this function is not exported.

    unsafeSetToList :: Set a -> [a]
    unsafeSetToList :: forall a. Set a -> [a]
unsafeSetToList (Set [a]
xs) = [a]
xs
    
    -- | /O(n)/. Size of a set.

    cardinal :: (Eq a) => Set a -> Int
    cardinal :: forall a. Eq a => Set a -> Int
cardinal = [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length([a] -> Int) -> (Set a -> [a]) -> Set a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Set a -> [a]
forall a. Eq a => Set a -> [a]
setToList
    
    -- | /O(n)/. Return wether an element is in a set.

    isIn :: (Eq a) => a -> Set a -> Bool
    isIn :: forall a. Eq a => a -> Set a -> Bool
isIn a
x = (a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
elem a
x)([a] -> Bool) -> (Set a -> [a]) -> Set a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Set a -> [a]
forall a. Set a -> [a]
unsafeSetToList
    
    -- | /O(n*m)/. Return the intersection of two sets.

    (|&|) :: (Eq a) => Set a -> Set a -> Set a
    |&| :: forall a. Eq a => Set a -> Set a -> Set a
(|&|) (Set [a]
xs) (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
`intersect` [a]
ys
    
    -- | /O(n)/. Return the union of two sets.

    (|||) ::  Set a -> Set a -> Set a
    ||| :: forall a. Set a -> Set a -> Set a
(|||) (Set [a]
xs) (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> [a] -> [a]
forall a. [a] -> [a] -> [a]
++ [a]
ys
    
    -- | /O(n*m)/. Return the cartesian product of two sets.

    (|*|) ::  Set a -> Set b -> Set (a,b)
    |*| :: forall a b. Set a -> Set b -> Set (a, b)
(|*|) (Set [a]
xs) (Set [b]
ys) = [(a, b)] -> Set (a, b)
forall a. [a] -> Set a
Set ([(a, b)] -> Set (a, b)) -> [(a, b)] -> Set (a, b)
forall a b. (a -> b) -> a -> b
$ [(a
x,b
y) | a
x <- [a]
xs, b
y <- [b]
ys]
    
    -- | /O(n)/. Return the disjoint union of two sets.

    (|+|) :: Set a -> Set b -> Set (Either a b)
    |+| :: forall a b. Set a -> Set b -> Set (Either a b)
(|+|) (Set [a]
xs) (Set [b]
ys) = [Either a b] -> Set (Either a b)
forall a. [a] -> Set a
Set ([Either a b] -> Set (Either a b))
-> [Either a b] -> Set (Either a b)
forall a b. (a -> b) -> a -> b
$ [a -> Either a b
forall a b. a -> Either a b
Left a
x | a
x <- [a]
xs] [Either a b] -> [Either a b] -> [Either a b]
forall a. [a] -> [a] -> [a]
++ [b -> Either a b
forall a b. b -> Either a b
Right b
y | b
y <- [b]
ys]
    
    -- | Returns the cartesian product of a set with itself n times.

    (|^|) :: (Num a, Eq a) => Set a -> a -> Set [a]
    |^| :: forall a. (Num a, Eq a) => Set a -> a -> Set [a]
(|^|) Set a
_ a
0 = [[a]] -> Set [a]
forall a. [a] -> Set a
Set [[]]
    (|^|) Set a
s a
n = (:) (a -> [a] -> [a]) -> Set a -> Set ([a] -> [a])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Set a
s Set ([a] -> [a]) -> Set [a] -> Set [a]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Set a
s Set a -> a -> Set [a]
forall a. (Num a, Eq a) => Set a -> a -> Set [a]
|^| (a
na -> a -> a
forall a. Num a => a -> a -> a
-a
1))
    
    -- | /O(n*m)/. Return the difference of two sets.

    (|-|) :: (Eq a) => Set a -> Set a -> Set a
    |-| :: forall a. Eq a => Set a -> Set a -> Set a
(|-|) (Set [a]
xs) (Set [a]
ys) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ [a]
xs [a] -> [a] -> [a]
forall a. Eq a => [a] -> [a] -> [a]
\\ [a]
ys
    
    -- | Return the set of all subsets of a given set.

    powerSet :: Set a -> Set (Set a)
    powerSet :: forall a. Set a -> Set (Set a)
powerSet (Set [a]
xs) = [Set a] -> Set (Set a)
forall a. [a] -> Set a
Set ([Set a] -> Set (Set a)) -> [Set a] -> Set (Set a)
forall a b. (a -> b) -> a -> b
$ [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [[a]] -> [Set a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [a] -> [[a]]
forall a. [a] -> [[a]]
subsequences [a]
xs
    
    -- | /O(n)/. Filter a set according to a condition.

    filterSet :: (a -> Bool) -> Set a -> Set a
    filterSet :: forall a. (a -> Bool) -> Set a -> Set a
filterSet a -> Bool
f (Set [a]
xs) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ (a -> Bool) -> [a] -> [a]
forall a. (a -> Bool) -> [a] -> [a]
filter a -> Bool
f [a]
xs
    
    -- | /O(1)/. Set version of listToMaybe.

    setToMaybe :: Set a -> Maybe a
    setToMaybe :: forall a. Set a -> Maybe a
setToMaybe = [a] -> Maybe a
forall a. [a] -> Maybe a
listToMaybe([a] -> Maybe a) -> (Set a -> [a]) -> Set a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Set a -> [a]
forall a. Set a -> [a]
unsafeSetToList
    
    -- | /O(1)/. Set version of maybeToList.

    maybeToSet :: Maybe a -> Set a
    maybeToSet :: forall a. Maybe a -> Set a
maybeToSet Maybe a
x = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ Maybe a -> [a]
forall a. Maybe a -> [a]
maybeToList Maybe a
x
    
    -- | /O(n)/. Set version of catMaybes.

    catMaybesToSet :: Set (Maybe a) -> Set a
    catMaybesToSet :: forall a. Set (Maybe a) -> Set a
catMaybesToSet = [a] -> Set a
forall a. [a] -> Set a
set([a] -> Set a) -> (Set (Maybe a) -> [a]) -> Set (Maybe a) -> Set a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.[Maybe a] -> [a]
forall a. [Maybe a] -> [a]
catMaybes([Maybe a] -> [a])
-> (Set (Maybe a) -> [Maybe a]) -> Set (Maybe a) -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Set (Maybe a) -> [Maybe a]
forall a. Set a -> [a]
unsafeSetToList
    
    -- | /O(n)/. Set version of mapMaybe.

    mapMaybeToSet :: (a -> Maybe b) -> Set a -> Set b
    mapMaybeToSet :: forall a b. (a -> Maybe b) -> Set a -> Set b
mapMaybeToSet a -> Maybe b
f = [b] -> Set b
forall a. [a] -> Set a
set([b] -> Set b) -> (Set a -> [b]) -> Set a -> Set b
forall b c a. (b -> c) -> (a -> b) -> a -> c
.((a -> Maybe b) -> [a] -> [b]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe a -> Maybe b
f)([a] -> [b]) -> (Set a -> [a]) -> Set a -> [b]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Set a -> [a]
forall a. Set a -> [a]
unsafeSetToList

    -- | /O(n)/. Remove duplicates in the set using your own equality function.

    nubSetBy :: (a -> a -> Bool) -> Set a -> Set a
    nubSetBy :: forall a. (a -> a -> Bool) -> Set a -> Set a
nubSetBy a -> a -> Bool
f (Set [a]
xs) = [a] -> Set a
forall a. [a] -> Set a
Set ([a] -> Set a) -> [a] -> Set a
forall a b. (a -> b) -> a -> b
$ (a -> a -> Bool) -> [a] -> [a]
forall a. (a -> a -> Bool) -> [a] -> [a]
nubBy a -> a -> Bool
f [a]
xs