
I am seeing surprising results from 'inCompact' after 'compact'. It seems there are additional limitations on what can be compacted, with 'compact' not throwing a 'CompactionFailed' exception in some cases, and yet not compacting the value. Is this expected? When the below is compiled and run: {-# LANGUAGE OverloadedStrings #-} module Main (main) where import Data.Compact import qualified Data.ByteString.Short as S import qualified Data.Map.Strict as M fib :: [Int] fib = 0:1:zipWith (+) fib (tail fib) u = if M.lookup 3 m == Just 2 then () else undefined f3 = head $ drop 3 fib m = M.fromList $ zip [0..9] fib main :: IO () main = do test "explicit ()" () test "computed ()" u test "explicit Int" (42 :: Int) test "computed Int" f3 test "empty string" ("" :: String) test "non-empty string" ("some string" :: String) test "empty short bytestring" S.empty test "non-empty short bytestring" (S.toShort "some bytestring") test "explict empty map" (M.empty :: M.Map Int Int) test "computed fib table" m where test :: String -> a -> IO () test msg val = do putStr (msg ++ ": ") c <- compact val inCompact c (getCompact c) >>= print it outputs: explicit (): False computed (): False explicit Int: False computed Int: True empty string: False non-empty string: True empty short bytestring: True non-empty short bytestring: True explict empty map: False computed fib table: True but the documentation promises: getCompact :: Compact a -> a # Retrieve a direct pointer to the value pointed at by a Compact reference. If you have used compactAdd, there may be multiple Compact references into the same compact region. Upholds the property: inCompact c (getCompact c) == True so when 'compact' does not bottom, I'd expect 'True'. -- Viktor.