{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-tabs #-}
module Utility.Misc where
import System.IO
import Control.Monad
import Foreign
import Data.Char
import Data.List
import System.Exit
#ifndef mingw32_HOST_OS
import System.Posix.Process (getAnyProcessStatus)
import Utility.Exception
#endif
import Control.Applicative
import Prelude
hGetContentsStrict :: Handle -> IO String
hGetContentsStrict = hGetContents >=> \s -> length s `seq` return s
readFileStrict :: FilePath -> IO String
readFileStrict = readFile >=> \s -> length s `seq` return s
separate :: (a -> Bool) -> [a] -> ([a], [a])
separate c l = unbreak $ break c l
  where
	unbreak r@(a, b)
		| null b = r
		| otherwise = (a, tail b)
firstLine :: String -> String
firstLine = takeWhile (/= '\n')
segment :: (a -> Bool) -> [a] -> [[a]]
segment p l = map reverse $ go [] [] l
  where
	go c r [] = reverse $ c:r
	go c r (i:is)
		| p i = go [] (c:r) is
		| otherwise = go (i:c) r is
prop_segment_regressionTest :: Bool
prop_segment_regressionTest = all id
	
	[ segment (== "--") [] == [[]]
	
	, segment (== "--") ["--", "foo", "bar"] == [[],["foo","bar"]]
	]
segmentDelim :: (a -> Bool) -> [a] -> [[a]]
segmentDelim p l = map reverse $ go [] [] l
  where
	go c r [] = reverse $ c:r
	go c r (i:is)
		| p i = go [] ([i]:c:r) is
		| otherwise = go (i:c) r is
massReplace :: [(String, String)] -> String -> String
massReplace vs = go [] vs
  where
	go acc _ [] = concat $ reverse acc
	go acc [] (c:cs) = go ([c]:acc) vs cs
	go acc ((val, replacement):rest) s
		| val `isPrefixOf` s =
			go (replacement:acc) vs (drop (length val) s)
		| otherwise = go acc rest s
hGetSomeString :: Handle -> Int -> IO String
hGetSomeString h sz = do
	fp <- mallocForeignPtrBytes sz
	len <- withForeignPtr fp $ \buf -> hGetBufSome h buf sz
	map (chr . fromIntegral) <$> withForeignPtr fp (peekbytes len)
  where
	peekbytes :: Int -> Ptr Word8 -> IO [Word8]
	peekbytes len buf = mapM (peekElemOff buf) [0..pred len]
reapZombies :: IO ()
#ifndef mingw32_HOST_OS
reapZombies =
	
	catchDefaultIO Nothing (getAnyProcessStatus False True)
		>>= maybe (return ()) (const reapZombies)
#else
reapZombies = return ()
#endif
exitBool :: Bool -> IO a
exitBool False = exitFailure
exitBool True = exitSuccess