Henning Thielemann schrieb:
> On Mon, 21 May 2007, Steffen Mazanek wrote:
> 
>> is there an efficient algorithm that takes two positive numbers n and m and
>> that computes all lists l of numbers 0<x<=n such that sum l = m?
>>
>> For instance
>> alg 5 1 = [[1]]
>> alg 5 2 = [[1,1],[2]]
>> alg 5 3 = [[1,1,1],[1,2],[2,1],[3]]
>> ...
> 
> http://darcs.haskell.org/htam/src/Combinatorics/Partitions.hs
> 
> alg  =  flip partitionsDec

*Combinatorics.Partitions> partitionsDec 5 3
[[3],[2,1],[1,1,1]]

so [1,2] is missing. And for these partitions I've also the attached module.

*Partition> parts 3
[3,2 1,1 1 1]

Christian
module Partition where

{- | a strictly increasing list of pairs where the second components are
the frequencies -}
newtype Part = Part [(Int, Int)] deriving (Eq, Ord)

instance Show Part where
    show (Part l) = showIntList $ partToList $ reverse l 

showIntList :: [Int] -> String
showIntList = unwords . map show

partToList :: [(Int, Int)] -> [Int]
partToList = concatMap ( \ (v, f) -> replicate f v)

infixr 5 >:
(>:) :: (Int, Int) -> [(Int, Int)] -> [(Int, Int)]
p@(_, c) >: l = if c == 0 then l else p : l

extendPart :: [(Int, Int)] -> [[(Int, Int)]]
extendPart l = case l of
    [] -> []
    (v, c) : r -> 
        if v == 1 then 
            case r of 
              [] -> [l]
              (v2, c2) : s -> 
                  let i = v2 - 1
                      (di, mi) = divMod (c + v2) i 
                  in l : extendPart (
                        (if mi == 0 then id else ((mi, 1) :))
                         $ (i, di) : (v2, c2 - 1) >: s)
        else l : extendPart (
                  (if v == 2 then [(1, 2)]
                   else [(1, 1), (v - 1, 1)]) ++ (v, c - 1) >: r)

parts :: Int -> [Part]
parts n = if n < 0 then [] else if n == 0 then [Part []] else 
               map Part $ extendPart [(n, 1)]
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to