{- misc utility functions
 -
 - Copyright 2010-2011 Joey Hess <id@joeyh.name>
 -
 - License: BSD-2-clause
 -}

{-# 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
import Control.Applicative
import Prelude

{- A version of hgetContents that is not lazy. Ensures file is 
 - all read before it gets closed. -}
hGetContentsStrict :: Handle -> IO String
hGetContentsStrict :: Handle -> IO String
hGetContentsStrict = Handle -> IO String
hGetContents forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \String
s -> forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s seq :: forall a b. a -> b -> b
`seq` forall (m :: * -> *) a. Monad m => a -> m a
return String
s

{- A version of readFile that is not lazy. -}
readFileStrict :: FilePath -> IO String
readFileStrict :: String -> IO String
readFileStrict = String -> IO String
readFile forall (m :: * -> *) a b c.
Monad m =>
(a -> m b) -> (b -> m c) -> a -> m c
>=> \String
s -> forall (t :: * -> *) a. Foldable t => t a -> Int
length String
s seq :: forall a b. a -> b -> b
`seq` forall (m :: * -> *) a. Monad m => a -> m a
return String
s

{- Like break, but the item matching the condition is not included
 - in the second result list.
 -
 - separate (== ':') "foo:bar" = ("foo", "bar")
 - separate (== ':') "foobar" = ("foobar", "")
 -}
separate :: (a -> Bool) -> [a] -> ([a], [a])
separate :: forall a. (a -> Bool) -> [a] -> ([a], [a])
separate a -> Bool
c [a]
l = forall {a} {a}. (a, [a]) -> (a, [a])
unbreak forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> ([a], [a])
break a -> Bool
c [a]
l
  where
	unbreak :: (a, [a]) -> (a, [a])
unbreak r :: (a, [a])
r@(a
a, [a]
b)
		| forall (t :: * -> *) a. Foldable t => t a -> Bool
null [a]
b = (a, [a])
r
		| Bool
otherwise = (a
a, forall a. [a] -> [a]
tail [a]
b)

{- Breaks out the first line. -}
firstLine :: String -> String
firstLine :: String -> String
firstLine = forall a. (a -> Bool) -> [a] -> [a]
takeWhile (forall a. Eq a => a -> a -> Bool
/= Char
'\n')

{- Splits a list into segments that are delimited by items matching
 - a predicate. (The delimiters are not included in the segments.)
 - Segments may be empty. -}
segment :: (a -> Bool) -> [a] -> [[a]]
segment :: forall a. (a -> Bool) -> [a] -> [[a]]
segment a -> Bool
p [a]
l = forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ [a] -> [[a]] -> [a] -> [[a]]
go [] [] [a]
l
  where
	go :: [a] -> [[a]] -> [a] -> [[a]]
go [a]
c [[a]]
r [] = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ [a]
cforall a. a -> [a] -> [a]
:[[a]]
r
	go [a]
c [[a]]
r (a
i:[a]
is)
		| a -> Bool
p a
i = [a] -> [[a]] -> [a] -> [[a]]
go [] ([a]
cforall a. a -> [a] -> [a]
:[[a]]
r) [a]
is
		| Bool
otherwise = [a] -> [[a]] -> [a] -> [[a]]
go (a
iforall a. a -> [a] -> [a]
:[a]
c) [[a]]
r [a]
is

prop_segment_regressionTest :: Bool
prop_segment_regressionTest :: Bool
prop_segment_regressionTest = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all forall a. a -> a
id
	-- Even an empty list is a segment.
	[ forall a. (a -> Bool) -> [a] -> [[a]]
segment (forall a. Eq a => a -> a -> Bool
== String
"--") [] forall a. Eq a => a -> a -> Bool
== [[]]
	-- There are two segements in this list, even though the first is empty.
	, forall a. (a -> Bool) -> [a] -> [[a]]
segment (forall a. Eq a => a -> a -> Bool
== String
"--") [String
"--", String
"foo", String
"bar"] forall a. Eq a => a -> a -> Bool
== [[],[String
"foo",String
"bar"]]
	]

{- Includes the delimiters as segments of their own. -}
segmentDelim :: (a -> Bool) -> [a] -> [[a]]
segmentDelim :: forall a. (a -> Bool) -> [a] -> [[a]]
segmentDelim a -> Bool
p [a]
l = forall a b. (a -> b) -> [a] -> [b]
map forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ [a] -> [[a]] -> [a] -> [[a]]
go [] [] [a]
l
  where
	go :: [a] -> [[a]] -> [a] -> [[a]]
go [a]
c [[a]]
r [] = forall a. [a] -> [a]
reverse forall a b. (a -> b) -> a -> b
$ [a]
cforall a. a -> [a] -> [a]
:[[a]]
r
	go [a]
c [[a]]
r (a
i:[a]
is)
		| a -> Bool
p a
i = [a] -> [[a]] -> [a] -> [[a]]
go [] ([a
i]forall a. a -> [a] -> [a]
:[a]
cforall a. a -> [a] -> [a]
:[[a]]
r) [a]
is
		| Bool
otherwise = [a] -> [[a]] -> [a] -> [[a]]
go (a
iforall a. a -> [a] -> [a]
:[a]
c) [[a]]
r [a]
is

{- Replaces multiple values in a string.
 -
 - Takes care to skip over just-replaced values, so that they are not
 - mangled. For example, massReplace [("foo", "new foo")] does not
 - replace the "new foo" with "new new foo".
 -}
massReplace :: [(String, String)] -> String -> String
massReplace :: [(String, String)] -> String -> String
massReplace [(String, String)]
vs = [String] -> [(String, String)] -> String -> String
go [] [(String, String)]
vs
  where

	go :: [String] -> [(String, String)] -> String -> String
go [String]
acc [(String, String)]
_ [] = forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat forall a b. (a -> b) -> a -> b
$ forall a. [a] -> [a]
reverse [String]
acc
	go [String]
acc [] (Char
c:String
cs) = [String] -> [(String, String)] -> String -> String
go ([Char
c]forall a. a -> [a] -> [a]
:[String]
acc) [(String, String)]
vs String
cs
	go [String]
acc ((String
val, String
replacement):[(String, String)]
rest) String
s
		| String
val forall a. Eq a => [a] -> [a] -> Bool
`isPrefixOf` String
s =
			[String] -> [(String, String)] -> String -> String
go (String
replacementforall a. a -> [a] -> [a]
:[String]
acc) [(String, String)]
vs (forall a. Int -> [a] -> [a]
drop (forall (t :: * -> *) a. Foldable t => t a -> Int
length String
val) String
s)
		| Bool
otherwise = [String] -> [(String, String)] -> String -> String
go [String]
acc [(String, String)]
rest String
s

{- Wrapper around hGetBufSome that returns a String.
 -
 - The null string is returned on eof, otherwise returns whatever
 - data is currently available to read from the handle, or waits for
 - data to be written to it if none is currently available.
 - 
 - Note on encodings: The normal encoding of the Handle is ignored;
 - each byte is converted to a Char. Not unicode clean!
 -}
hGetSomeString :: Handle -> Int -> IO String
hGetSomeString :: Handle -> Int -> IO String
hGetSomeString Handle
h Int
sz = do
	ForeignPtr Word8
fp <- forall a. Int -> IO (ForeignPtr a)
mallocForeignPtrBytes Int
sz
	Int
len <- forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
buf -> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufSome Handle
h Ptr Word8
buf Int
sz
	forall a b. (a -> b) -> [a] -> [b]
map (Int -> Char
chr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp (Int -> Ptr Word8 -> IO [Word8]
peekbytes Int
len)
  where
	peekbytes :: Int -> Ptr Word8 -> IO [Word8]
	peekbytes :: Int -> Ptr Word8 -> IO [Word8]
peekbytes Int
len Ptr Word8
buf = forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
buf) [Int
0..forall a. Enum a => a -> a
pred Int
len]

exitBool :: Bool -> IO a
exitBool :: forall a. Bool -> IO a
exitBool Bool
False = forall a. IO a
exitFailure
exitBool Bool
True = forall a. IO a
exitSuccess