Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

Represent a list of Enums bitwise as an Int

In order to save user-account permissions externally (e.g. in DB), I want to represent a list of elements of a enumeration that have a derived Enum instance as an Int.
Every bit of the number is seen as a flag (or Boolean) denoting if the i-th element is present in the list.
Putting it in different words - every power of 2 represents one element and the sum of such powers an unique list of elements.

Example:

data Permissions = IsAllowedToLogin   -- 1
                 | IsModerator        -- 2
                 | IsAdmin            -- 4
                 deriving (Bounded, Enum, Eq, Show) 

enumsToInt [IsAllowedToLogin, IsAdmin] == 1 + 4 == 5

intToEnums 3 == intToEnums (1 + 2) == [IsAllowedToLogin, IsModerator]

The function converting such a list into an Int is quite easy to write:

enumsToInt :: (Enum a, Eq a) => [a] -> Int
enumsToInt = foldr (\p acc -> acc + 2 ^ fromEnum p) 0 . nub

Note that the accepted answer contains a much more effective implementation.

What really troubles me is the reversing function. I can imagine it should have this type:

intToEnums :: (Bounded a, Enum a) => Int -> [a]
intToEnums = undefined               -- What I'm asking about

How should I approach this problem?

like image 815
Jakub Avatar asked Apr 09 '13 19:04

Jakub


3 Answers

Following is a complete solution. It should perform better as it's implementation is based on bitwise rather than arithmetic operations, which is a much more effective approach. The solution also does its best to generalize things.

{-# LANGUAGE DefaultSignatures #-}
import Data.Bits
import Control.Monad

data Permission = IsAllowedToLogin   -- 1
                | IsModerator        -- 2
                | IsAdmin            -- 4
                deriving (Bounded, Enum, Eq, Show) 

class ToBitMask a where 
  toBitMask :: a -> Int
  -- | Using a DefaultSignatures extension to declare a default signature with
  -- an `Enum` constraint without affecting the constraints of the class itself.
  default toBitMask :: Enum a => a -> Int
  toBitMask = shiftL 1 . fromEnum

instance ToBitMask Permission

instance ( ToBitMask a ) => ToBitMask [a] where 
  toBitMask = foldr (.|.) 0 . map toBitMask

-- | Not making this a typeclass, since it already generalizes over all 
-- imaginable instances with help of `MonadPlus`.
fromBitMask :: 
  ( MonadPlus m, Enum a, Bounded a, ToBitMask a ) => 
    Int -> m a
fromBitMask bm = msum $ map asInBM $ enumFrom minBound where 
  asInBM a = if isInBitMask bm a then return a else mzero

isInBitMask :: ( ToBitMask a ) => Int -> a -> Bool
isInBitMask bm a = let aBM = toBitMask a in aBM == aBM .&. bm

Running it with the following

main = do
  print (fromBitMask 0 :: [Permission])
  print (fromBitMask 1 :: [Permission])
  print (fromBitMask 2 :: [Permission])
  print (fromBitMask 3 :: [Permission])
  print (fromBitMask 4 :: [Permission])
  print (fromBitMask 5 :: [Permission])
  print (fromBitMask 6 :: [Permission])
  print (fromBitMask 7 :: [Permission])

  print (fromBitMask 0 :: Maybe Permission)
  print (fromBitMask 1 :: Maybe Permission)
  print (fromBitMask 2 :: Maybe Permission)
  print (fromBitMask 4 :: Maybe Permission)

outputs

[]
[IsAllowedToLogin]
[IsModerator]
[IsAllowedToLogin,IsModerator]
[IsAdmin]
[IsAllowedToLogin,IsAdmin]
[IsModerator,IsAdmin]
[IsAllowedToLogin,IsModerator,IsAdmin]
Nothing
Just IsAllowedToLogin
Just IsModerator
Just IsAdmin
like image 151
Nikita Volkov Avatar answered Oct 18 '22 01:10

Nikita Volkov


I'm sure there's something on hackage that does this already, but it's simple enough to hand-roll your own using the Data.Bits module.

You can simplify enumsToInt to just something like foldl' (.|.) . map (bit . fromEnum), i.e., convert to integer indices and then to single bits, then fold with bitwise OR. If nothing else, this saves you from worrying about removing duplicates.

For intToEnums there's nothing incredibly convenient, but for a quick solution you can do something like filter (testBit foo . fromEnum) [minBound .. maxBound]. This of course only works for Bounded types and presumes that the enum doesn't have more values than the external type has bits and that fromEnum uses consecutive integers starting from 0, but it sounds like you're starting with all that as a premise here anyway.

like image 31
C. A. McCann Avatar answered Oct 17 '22 23:10

C. A. McCann


EnumSet is probably exactly what you want. It even has an intToEnums function (though it appears to only work consistently with T Integer a of the types I have tried - in particular, T Int Char gives unexpected results) and would not be expected to recreate duplicate entries after serializing/deserializing (given that its a set), while a list may carry that expectation.

like image 25
ScootyPuff Avatar answered Oct 18 '22 00:10

ScootyPuff