module Database.PostgreSQL.PQTypes.Utils.NubList
( NubList
, toNubList
, fromNubList
, overNubList
) where
import Prelude
import Data.Monoid (Monoid(..))
import Data.Typeable
import qualified Text.Read as R
import qualified Data.Set as Set
import qualified Data.Semigroup as SG
newtype NubList a =
NubList { fromNubList :: [a] }
deriving (Eq, Typeable)
toNubList :: Ord a => [a] -> NubList a
toNubList list = NubList $ (ordNubBy id) list
overNubList :: Ord a => ([a] -> [a]) -> NubList a -> NubList a
overNubList f (NubList list) = toNubList . f $ list
instance Ord a => SG.Semigroup (NubList a) where
(NubList xs) <> (NubList ys) = NubList $ xs `listUnion` ys
where
listUnion :: (Ord a) => [a] -> [a] -> [a]
listUnion a b = a
++ ordNubBy id (filter (`Set.notMember` (Set.fromList a)) b)
instance Ord a => Monoid (NubList a) where
mempty = NubList []
mappend = (SG.<>)
instance Show a => Show (NubList a) where
show (NubList list) = show list
instance (Ord a, Read a) => Read (NubList a) where
readPrec = readNubList toNubList
readNubList :: (Read a) => ([a] -> l a) -> R.ReadPrec (l a)
readNubList toList = R.parens . R.prec 10 $ fmap toList R.readPrec
ordNubBy :: Ord b => (a -> b) -> [a] -> [a]
ordNubBy f l = go Set.empty l
where
go !_ [] = []
go !s (x:xs)
| y `Set.member` s = go s xs
| otherwise = let !s' = Set.insert y s
in x : go s' xs
where
y = f x