#7400: Strange closure type 17 internal error -------------------------+-------------------------------------------------- Reporter: ropoctl | Owner: Type: bug | Status: new Priority: normal | Component: Runtime System Version: 7.4.2 | Keywords: Os: Linux | Architecture: x86_64 (amd64) Failure: None/Unknown | Blockedby: Blocking: | Related: -------------------------+-------------------------------------------------- resample: internal error: evacuate(static): strange closure type 17 (GHC version 7.4.2 for x86_64_unknown_linux) Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
{{{ module Resample where import Data.List import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import qualified Data.ByteString.Lazy.Char8 as BL import qualified Data.ByteString.Lazy as BB import qualified Data.Vector as V import System.Random.Mersenne import Control.Monad (liftM, replicateM_) readCollapsed :: FilePath -> IO [(Int, B.ByteString)] readCollapsed f = ((map (either error id) . unfoldr parse) . BL.lines) `fmap` BL.readFile f parse :: [BL.ByteString] -> Maybe (Either String (Int, B.ByteString), [BL.ByteString]) parse (c:sq:rest) = Just (Right (read $ BL.unpack c, B.concat $ BL.toChunks sq), rest) parse [] = Nothing parse fs = let showStanza = unlines (map BL.unpack fs) err = Left $ "Resample: illegal number of lines: " ++ showStanza in Just (err, []) uncollapse :: (Int, B.ByteString) -> [B.ByteString] uncollapse (c, sq) = take c $ repeat sq randomPick' mt vec len = liftM (vec V.!) $ liftM ((flip mod) len) (random mt) main :: IO () main = do sqvec <- liftM (V.fromList . Prelude.concatMap uncollapse) $ readCollapsed "/dev/stdin" let seqlen = V.length sqvec mtgen <- newMTGen Nothing replicateM_ 30000000 $ BC.putStrLn =<< randomPick' mtgen sqvec seqlen }}} -- Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/7400> GHC <http://www.haskell.org/ghc/> The Glasgow Haskell Compiler _______________________________________________ Glasgow-haskell-bugs mailing list Glasgow-haskell-bugs@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs