Skip to content

Commit

Permalink
Derive IsList instances to EnumSet and EnumMap
Browse files Browse the repository at this point in the history
  • Loading branch information
0xd34df00d committed Sep 3, 2024
1 parent 782ab25 commit 9f7577d
Show file tree
Hide file tree
Showing 2 changed files with 27 additions and 4 deletions.
16 changes: 14 additions & 2 deletions Data/EnumMap/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,6 +2,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Module : $Header$
Expand Down Expand Up @@ -184,6 +185,7 @@ import Data.Semigroup ( Semigroup )
import Data.Traversable ( Traversable )
import Data.Typeable ( Typeable )
import Data.Aeson ( FromJSON(..), ToJSON(..) )
import qualified GHC.Exts as IL
import Text.Read

-- | Wrapper for 'IntMap' with 'Enum' keys.
Expand All @@ -207,6 +209,16 @@ instance (ToJSON a) => ToJSON (EnumMap k a) where
instance (FromJSON a) => FromJSON (EnumMap k a) where
parseJSON = fmap (EnumMap . I.fromList) . parseJSON

instance (Enum k) => IL.IsList (EnumMap k a) where
type Item (EnumMap k a) = (k, a)

toList = P.map (first toEnum) . I.toList . unWrap
{-# INLINE toList #-}

fromList = EnumMap . I.fromList . P.map (first fromEnum)
{-# INLINE fromList #-}


--
-- Conversion to/from 'IntMap'.
--
Expand Down Expand Up @@ -637,7 +649,7 @@ assocs = P.map (first toEnum) . I.assocs . unWrap
{-# INLINE assocs #-}

toList :: (Enum k) => EnumMap k a -> [(k, a)]
toList = P.map (first toEnum) . I.toList . unWrap
toList = IL.toList
{-# INLINE toList #-}

toAscList :: (Enum k) => EnumMap k a -> [(k, a)]
Expand All @@ -649,7 +661,7 @@ toDescList = P.map (first toEnum) . I.toDescList . unWrap
{-# INLINE toDescList #-}

fromList :: (Enum k) => [(k, a)] -> EnumMap k a
fromList = EnumMap . I.fromList . P.map (first fromEnum)
fromList = IL.fromList
{-# INLINE fromList #-}

fromListWith :: (Enum k) => (a -> a -> a) -> [(k, a)] -> EnumMap k a
Expand Down
15 changes: 13 additions & 2 deletions Data/EnumSet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE TypeFamilies #-}

-- |
-- Module : $Header$
Expand Down Expand Up @@ -113,6 +114,7 @@ import Data.Aeson
( FromJSON(parseJSON), ToJSON(toEncoding, toJSON) )
import Text.Read
import GHC.Generics (Generic)
import qualified GHC.Exts as IL

-- | Wrapper for 'IntSet' with 'Enum' elements.
newtype EnumSet k = EnumSet { unWrap :: IntSet }
Expand Down Expand Up @@ -143,6 +145,15 @@ instance ToJSON (EnumSet a) where
instance (FromJSON a) => FromJSON (EnumSet a) where
parseJSON = fmap (EnumSet . I.fromList) . parseJSON

instance (Enum a) => IL.IsList (EnumSet a) where
type Item (EnumSet a) = a

toList = P.map toEnum . I.toList . unWrap
{-# INLINE toList #-}

fromList = EnumSet . I.fromList . P.map fromEnum
{-# INLINE fromList #-}

--
-- Conversion to/from 'IntSet'.
--
Expand Down Expand Up @@ -316,7 +327,7 @@ elems = P.map toEnum . I.elems . unWrap
{-# INLINE elems #-}

toList :: (Enum k) => EnumSet k -> [k]
toList = P.map toEnum . I.toList . unWrap
toList = IL.toList
{-# INLINE toList #-}

toAscList :: (Enum k) => EnumSet k -> [k]
Expand All @@ -328,7 +339,7 @@ toDescList = P.map toEnum . I.toDescList . unWrap
{-# INLINE toDescList #-}

fromList :: (Enum k) => [k] -> EnumSet k
fromList = EnumSet . I.fromList . P.map fromEnum
fromList = IL.fromList
{-# INLINE fromList #-}

fromAscList :: (Enum k) => [k] -> EnumSet k
Expand Down

0 comments on commit 9f7577d

Please sign in to comment.