{-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE GeneralisedNewtypeDeriving #-} module Data.EnumSet.Wrapper (EnumSet (..)) where import Control.DeepSeq (NFData) import Data.Data (Data) import Data.EnumOrd (EnumOrd (..)) import Data.IntSet (IntSet) import qualified Data.IntSet as IntSet import Data.Set (Set) import qualified Data.Set as Set import GHC.Exts (IsList) import Text.Read (Read (..)) newtype EnumSet k = EnumSet {unEnumSet :: IntSet} deriving ( Monoid, Semigroup, Data, IsList, Eq, Ord, NFData ) toSet :: Enum k => EnumSet k -> Set (EnumOrd k) toSet = Set.fromList . fmap (EnumOrd . toEnum) . IntSet.toList . unEnumSet fromSet :: Enum k => Set (EnumOrd k) -> EnumSet k fromSet = EnumSet . IntSet.fromList . fmap (fromEnum . unEnumOrd) . Set.toList instance (Enum k, Show k) => Show (EnumSet k) where showsPrec p = showsPrec p . toSet instance (Enum k, Read k) => Read (EnumSet k) where readPrec = fromSet <$> readPrec