I want to partition the integer n=180 with terms >=5
I.e.  n=15 => [[5,5,5],[8,7],[9,6],[10,5],[15]]
The function part does this. memopart does it with memoization a lot faster.
mempart works fine on my machine until n=120. For n=130 I get 'out of memory'. For other reasons I work on Win64 with ghc32.
To save memory I replaced Int with Word8. I also replaced [Word8] with B.ByteString (memopartB). But no luck. I still get 'out of memory' for n=130.
I run the program with: part +RTS -M4294967295  (429... is according to ghc the max memory I can use)
Any ideas how to solve this? 
What is the most memory efficient replacement for a list?
module Main (
   main,part,memopart   
)
where
import Data.Int 
import System.Time
import qualified Data.ByteString.Lazy as B
import Data.Word
import Data.List (intercalate)
part :: Int -> [[Int]]
part 0 = [[]]
part n = [x:y | x <- [5..n], y <- part (n-x),  [x] >= take 1 y]
partB :: Word8 -> [B.ByteString]
partB 0 = [B.empty]
partB n = [B.cons x y | x <- [5..n], y <- partB (n-x), B.singleton x >= y]
memopart a = memo !! a  where
    memo = [[]] : [[x:y | x <- [5..n], y <- memo !! (n-x), [x] >= take 1 y] | n <- [5..]]
memopartB :: Int -> [B.ByteString]    
memopartB a = memo !! a  where             
                  memo :: [[B.ByteString]]
                  memo = [B.empty] : [[B.cons x y | x <- [5 :: Word8 .. n :: Word8], y <- memo !! minusWord8 n x, B.singleton x >= y] | n <- [5 :: Word8 ..]]
                  minusWord8 :: Word8 -> Word8 -> Int
                  minusWord8 c d = (fromIntegral c :: Int) - (fromIntegral d:: Int)
    
main = do
         startTime <- getClockTime
         -- print $ length $ memopart 50
         putStrLn $ showPartBRes $ memopartB 120
         stopTime  <- getClockTime
         putStrLn ("Time: " ++ timeDiffToString (diffClockTimes stopTime startTime))
         
showPartBRes :: [B.ByteString] -> String
showPartBRes res = intercalate ", " $ map showB  res
                   where showB :: B.ByteString -> String
                         showB arr = '[' : intercalate "," (B.foldr (\w acc -> show w : acc) [] arr) ++ "]"