Created
December 28, 2014 23:56
-
-
Save gallais/b172a81291ae68da987c to your computer and use it in GitHub Desktop.
Powersets using masks
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-# LANGUAGE ScopedTypeVariables #-} | |
module PowerSet where | |
import Data.Bits | |
import GHC.Word | |
-- Here we want to define the powerset of a list xs "in one go" | |
-- using the masks corresponding to the binary representations | |
-- of the numbers between 0 and 2 ^ length xs - 1. | |
-- Here are a couple of examples (remember: numbers are read right | |
-- to left but lists are read left to right!..) | |
-- 0 is 000000, it associates [] to the list [1, 2, 3, 4, 5, 6] | |
-- 4 is 000100, it associates [3] to the list [1, 2, 3, 4, 5, 6] | |
-- 11 is 001011, it associates [1,2,4] to the list [1, 2, 3, 4, 5, 6] | |
-- In order to avoid picking a particular representation from | |
-- the get go for these masks, we define a new type `PowerSet a b` | |
-- with two type parameters `a` and `b` which packages a list | |
-- of lists of type [[a]]. | |
-- `b` is never mentioned here; it is a phantom type which will | |
-- let us be parametric over the choice of masks representation | |
-- until the call site where we may pick whatever is most | |
-- appropriate. | |
newtype PowerSet a b = PowerSet { runPowerSet :: [[a]] } | |
-- Now we can define the powerset function itself. We add type | |
-- class constraints describing what `b` should be like. | |
-- * It should be `Num`-like, indeed 0 will be one such number | |
-- * It should be `Enum`erable given that we are planning to | |
-- go through all possible masks between 0 and 2 ^ length xs - 1 | |
-- * It should be made of `Bits` given that we want to be able | |
-- to test whether the n-th bit is set or not. | |
-- Because we mention `b` in the body of the function, we need | |
-- the language extension `ScopedTypeVariables` to write the | |
-- following type annotation. Hence the pragma at the beginning | |
-- of this file. | |
powerset :: forall a b. (Num b, Enum b, Bits b) => [a] -> PowerSet a b | |
powerset xs = PowerSet $ | |
-- Now we are looking at the meat of the program. We start by zipping | |
-- xs together with the infinite list [0..] thus getting back the list | |
-- of elements together with their position in xs. | |
let xsWithPos = zip xs [0..] in | |
-- we then, for each mask, filter the elements whose bit is set | |
-- and forget about their position in the original list by | |
-- `map`ping `fst` on the result. | |
fmap (\ mask-> fmap fst $ filter (testBit mask . snd) xsWithPos) | |
([0..2^length xs-1] :: [b]) | |
-- Great. We can run examples and pick various types for the masks: | |
main :: IO () | |
main = do | |
-- using Arbitrary precision Integers | |
print $ runPowerSet $ (powerset [1,2,4,5,6,7] :: PowerSet Int Integer) | |
-- moving down to machine words | |
print $ runPowerSet $ (powerset [1,2,4,5,6,7] :: PowerSet Int Word) | |
-- you know what? we don't even need that much! | |
print $ runPowerSet $ (powerset [1,2,4,5,6,7] :: PowerSet Int Word8) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment