[Haskell-cafe] algorithm-for-finding-numerical-permutation-given-lexicographic-index

mukesh tiwari mukeshtiwari.iiitm at gmail.com
Wed Apr 10 07:54:17 CEST 2013


Hi Lone
Just coded quickly so still there is lot of chance for improvement.

{-# LANGUAGE MultiWayIf #-}
import Data.List
import Data.Word
import Data.Bits

builtin_ctz_hask :: Word32 -> Word32
builtin_ctz_hask x
             | x == 0 =  32
             | otherwise = n' - ( ( .&. ) x' 1 ) where
               ( n' , x' ) = foldl' computeBit (  1 , x ) [ ( 0xFFFF , 16 )
, ( 0xFF , 8 ) , ( 0xF , 4 ) , ( 0x3 , 2 ) ]
               computeBit :: ( Word32 , Word32 ) ->
                             ( Word32 , Word32 ) -> ( Word32 , Word32 )
               computeBit ( nt , xt ) ( yt , cnt ) =
                            if | (.&.) xt yt  == 0  -> ( nt + cnt , xt
`shiftR` ( fromIntegral cnt ) )
                               | otherwise -> ( nt , xt )



bitPermutation :: Word32  -> Word32
bitPermutation v = w where
               t :: Word32
               t = (.|.) v ( v - 1 )
               t' :: Word32
               t' = complement t
               w :: Word32
               w = ( .|. ) ( t + 1 ) ( ( (.&.) t' ( -t' ) - 1 ) `shiftR` (
fromIntegral ( 1 + builtin_ctz_hask v  ) ) )

allPermutation :: Word32 -> [ Word32 ]
allPermutation n = iterate bitPermutation n

wordtoBin :: Word32 -> [ Word32 ]
wordtoBin 0 = [ 0 ]
wordtoBin n
        | mod n 2 == 1 = wordtoBin ( div n 2 ) ++ [ 1 ]
        | otherwise = wordtoBin ( div n 2 ) ++ [ 0 ]

Here is the output.
*Main> map ( concat . map show . wordtoBin ) . take 10 . allPermutation $ 19
["010011","010101","010110","011001","011010","011100","0100011","0100101","0100110","0101001"]

Mukesh



On Wed, Apr 10, 2013 at 3:47 AM, Lone Wolf <amslonewolf at gmail.com> wrote:

> How could I use Data.Bits to implement the below C code in Haskell?
>
> http://www-graphics.stanford.edu/~seander/bithacks.html#NextBitPermutation
>
> Compute the lexicographically next bit permutation
>
> Suppose we have a pattern of N bits set to 1 in an integer and we want the
> next permutation of N 1 bits in a lexicographical sense. For example, if N
> is 3 and the bit pattern is 00010011, the next patterns would be 00010101
> , 00010110, 00011001, 00011010, 00011100, 00100011, and so forth. The
> following is a fast way to compute the next permutation.
>
> unsigned int v; // current permutation of bits
> unsigned int w; // next permutation of bits
>
> unsigned int t = v | (v - 1); // t gets v's least significant 0 bits set
> to 1
> // Next set to 1 the most significant bit to change,
> // set to 0 the least significant ones, and add the necessary 1 bits.
> w = (t + 1) | (((~t & -~t) - 1) >> (__builtin_ctz(v) + 1));
>
> The __builtin_ctz(v) GNU C compiler intrinsic for x86 CPUs returns the
> number of trailing zeros. If you are using Microsoft compilers for x86, the
> intrinsic is _BitScanForward. These both emit absf instruction, but
> equivalents may be available for other architectures. If not, then consider
> using one of the methods for counting the consecutive zero bits mentioned
> earlier. Here is another version that tends to be slower because of its
> division operator, but it does not require counting the trailing zeros.
>
> unsigned int t = (v | (v - 1)) + 1;
> w = t | ((((t & -t) / (v & -v)) >> 1) - 1);
>
> Thanks to Dario Sneidermanis of Argentina, who provided this on November
> 28, 2009.
>
>
> On Wed, Apr 3, 2013 at 12:44 PM, Tom Davie <tom.davie at gmail.com> wrote:
>
>> permutationIndex :: Int → [Int] → [Int]
>> permutationIndex [] = []
>> permutationIndex xs =
>>   let len = length xs
>>       max = fac len
>>       divisor = max / len
>>       i = index / divisor
>>       el = xs !! i
>>    in permutationIndex (index - divisor * i) (filter (!= el) xs)
>>
>> Of course, this is not very efficient, because you're using lists, and
>> attempting to index into them and measure their lengths.  Perhaps a
>> different data structure is in order.
>>
>> Thanks
>>
>> Tom Davie
>>
>> On 3 Apr 2013, at 17:38, Lone Wolf <amslonewolf at gmail.com> wrote:
>>
>>
>>> http://stackoverflow.com/questions/8940470/algorithm-for-finding-numerical-permutation-given-lexicographic-index
>>>
>>> How would you rewrite this into Haskell?  The code snippet is in Scala.
>>>
>>> /**
>>>     example: index:=15, list:=(1, 2, 3, 4)
>>> */
>>> def permutationIndex (index: Int, list: List [Int]) : List [Int] =
>>>   if (list.isEmpty) list else {
>>>     val len = list.size     // len = 4
>>>     val max = fac (len)     // max = 24
>>>     val divisor = max / len // divisor = 6
>>>     val i = index / divisor // i = 2
>>>     val el = list (i)
>>>     el :: permutationIndex (index - divisor * i, list.filter (_ != el)) }
>>>
>>>
>>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
>>
>>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130410/436f1706/attachment.htm>


More information about the Haskell-Cafe mailing list