In the following program, the function "test1" results in huge memory usage, but substituting "test2", which does essentially the same thing, does not.  GHC 7.10.1, AMD64.  Is there a different implementation of replicateM that avoids the space leak?

module Main where {
import Control.Monad;

numbers :: [Int];
numbers=[1..200];

-- has a space leak
test1 :: [[Int]];
test1 = replicateM 4 numbers;

-- no space leak
test2 :: [[Int]];
test2 = do {
x1 <- numbers;
x2 <- numbers;
x3 <- numbers;
x4 <- numbers;
return [x1,x2,x3,x4];
};

main :: IO();
main = print $ length $ test1;

}

Thanks,
--ken