{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE BangPatterns #-}
module Distribution.Utils.Generic (
withFileContents,
writeFileAtomic,
fromUTF8BS,
fromUTF8LBS,
toUTF8BS,
toUTF8LBS,
validateUTF8,
readUTF8File,
withUTF8FileContents,
writeUTF8File,
ignoreBOM,
normaliseLineEndings,
dropWhileEndLE,
takeWhileEndLE,
equating,
comparing,
isInfixOf,
intercalate,
lowercase,
isAscii,
isAsciiAlpha,
isAsciiAlphaNum,
listUnion,
listUnionRight,
ordNub,
ordNubBy,
ordNubRight,
safeTail,
unintersperse,
wrapText,
wrapLine,
unfoldrM,
spanMaybe,
breakMaybe,
isAbsoluteOnAnyPlatform,
isRelativeOnAnyPlatform,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Utils.String
import Data.Bits ((.&.), (.|.), shiftL)
import Data.List
( isInfixOf )
import Data.Ord
( comparing )
import qualified Data.ByteString.Lazy as BS
import qualified Data.Set as Set
import qualified Data.ByteString as SBS
import System.Directory
( removeFile, renameFile )
import System.FilePath
( (<.>), splitFileName )
import System.IO
( withFile, withBinaryFile
, openBinaryTempFileWithDefaultPermissions
, IOMode(ReadMode), hGetContents, hClose )
import qualified Control.Exception as Exception
wrapText :: String -> String
wrapText = unlines
. map (intercalate "\n"
. map unwords
. wrapLine 79
. words)
. lines
wrapLine :: Int -> [String] -> [[String]]
wrapLine width = wrap 0 []
where wrap :: Int -> [String] -> [String] -> [[String]]
wrap 0 [] (w:ws)
| length w + 1 > width
= wrap (length w) [w] ws
wrap col line (w:ws)
| col + length w + 1 > width
= reverse line : wrap 0 [] (w:ws)
wrap col line (w:ws)
= let col' = col + length w + 1
in wrap col' (w:line) ws
wrap _ [] [] = []
wrap _ line [] = [reverse line]
withFileContents :: FilePath -> (String -> NoCallStackIO a) -> NoCallStackIO a
withFileContents name action =
withFile name ReadMode
(\hnd -> hGetContents hnd >>= action)
writeFileAtomic :: FilePath -> BS.ByteString -> NoCallStackIO ()
writeFileAtomic targetPath content = do
let (targetDir, targetFile) = splitFileName targetPath
Exception.bracketOnError
(openBinaryTempFileWithDefaultPermissions targetDir $ targetFile <.> "tmp")
(\(tmpPath, handle) -> hClose handle >> removeFile tmpPath)
(\(tmpPath, handle) -> do
BS.hPut handle content
hClose handle
renameFile tmpPath targetPath)
fromUTF8BS :: SBS.ByteString -> String
fromUTF8BS = decodeStringUtf8 . SBS.unpack
fromUTF8LBS :: BS.ByteString -> String
fromUTF8LBS = decodeStringUtf8 . BS.unpack
toUTF8BS :: String -> SBS.ByteString
toUTF8BS = SBS.pack . encodeStringUtf8
toUTF8LBS :: String -> BS.ByteString
toUTF8LBS = BS.pack . encodeStringUtf8
validateUTF8 :: SBS.ByteString -> Maybe Int
validateUTF8 = go 0 where
go off bs = case SBS.uncons bs of
Nothing -> Nothing
Just (c, bs')
| c <= 0x7F -> go (off + 1) bs'
| c <= 0xBF -> Just off
| c <= 0xDF -> twoBytes off c bs'
| c <= 0xEF -> moreBytes off 3 0x800 bs' (fromIntegral $ c .&. 0xF)
| c <= 0xF7 -> moreBytes off 4 0x10000 bs' (fromIntegral $ c .&. 0x7)
| c <= 0xFB -> moreBytes off 5 0x200000 bs' (fromIntegral $ c .&. 0x3)
| c <= 0xFD -> moreBytes off 6 0x4000000 bs' (fromIntegral $ c .&. 0x1)
| otherwise -> Just off
twoBytes off c0 bs = case SBS.uncons bs of
Nothing -> Just off
Just (c1, bs')
| c1 .&. 0xC0 == 0x80 ->
if d >= (0x80 :: Int)
then go (off + 2) bs'
else Just off
| otherwise -> Just off
where
d = (fromIntegral (c0 .&. 0x1F) `shiftL` 6) .|. fromIntegral (c1 .&. 0x3F)
moreBytes :: Int -> Int -> Int -> SBS.ByteString -> Int -> Maybe Int
moreBytes off 1 overlong cs' acc
| overlong <= acc, acc <= 0x10FFFF, acc < 0xD800 || 0xDFFF < acc
= go (off + 1) cs'
| otherwise
= Just off
moreBytes off byteCount overlong bs acc = case SBS.uncons bs of
Just (cn, bs') | cn .&. 0xC0 == 0x80 ->
moreBytes (off + 1) (byteCount-1) overlong bs' ((acc `shiftL` 6) .|. fromIntegral cn .&. 0x3F)
_ -> Just off
ignoreBOM :: String -> String
ignoreBOM ('\xFEFF':string) = string
ignoreBOM string = string
readUTF8File :: FilePath -> NoCallStackIO String
readUTF8File f = (ignoreBOM . fromUTF8LBS) <$> BS.readFile f
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO a
withUTF8FileContents name action =
withBinaryFile name ReadMode
(\hnd -> BS.hGetContents hnd >>= action . ignoreBOM . fromUTF8LBS)
writeUTF8File :: FilePath -> String -> NoCallStackIO ()
writeUTF8File path = writeFileAtomic path . BS.pack . encodeStringUtf8
normaliseLineEndings :: String -> String
normaliseLineEndings [] = []
normaliseLineEndings ('\r':'\n':s) = '\n' : normaliseLineEndings s
normaliseLineEndings ('\r':s) = '\n' : normaliseLineEndings s
normaliseLineEndings ( c :s) = c : normaliseLineEndings s
dropWhileEndLE :: (a -> Bool) -> [a] -> [a]
dropWhileEndLE p = foldr (\x r -> if null r && p x then [] else x:r) []
takeWhileEndLE :: (a -> Bool) -> [a] -> [a]
takeWhileEndLE p = fst . foldr go ([], False)
where
go x (rest, done)
| not done && p x = (x:rest, False)
| otherwise = (rest, True)
ordNub :: Ord a => [a] -> [a]
ordNub = ordNubBy id
ordNubBy :: Ord b => (a -> b) -> [a] -> [a]
ordNubBy f l = go Set.empty l
where
go !_ [] = []
go !s (x:xs)
| y `Set.member` s = go s xs
| otherwise = let !s' = Set.insert y s
in x : go s' xs
where
y = f x
listUnion :: (Ord a) => [a] -> [a] -> [a]
listUnion a b = a ++ ordNub (filter (`Set.notMember` aSet) b)
where
aSet = Set.fromList a
ordNubRight :: (Ord a) => [a] -> [a]
ordNubRight = fst . foldr go ([], Set.empty)
where
go x p@(l, s) = if x `Set.member` s then p
else (x:l, Set.insert x s)
listUnionRight :: (Ord a) => [a] -> [a] -> [a]
listUnionRight a b = ordNubRight (filter (`Set.notMember` bSet) a) ++ b
where
bSet = Set.fromList b
safeTail :: [a] -> [a]
safeTail [] = []
safeTail (_:xs) = xs
equating :: Eq a => (b -> a) -> b -> b -> Bool
equating p x y = p x == p y
lowercase :: String -> String
lowercase = map toLower
isAscii :: Char -> Bool
isAscii c = fromEnum c < 0x80
isAsciiAlpha :: Char -> Bool
isAsciiAlpha c = ('a' <= c && c <= 'z')
|| ('A' <= c && c <= 'Z')
isAsciiAlphaNum :: Char -> Bool
isAsciiAlphaNum c = isAscii c && isAlphaNum c
unintersperse :: Char -> String -> [String]
unintersperse mark = unfoldr unintersperse1 where
unintersperse1 str
| null str = Nothing
| otherwise =
let (this, rest) = break (== mark) str in
Just (this, safeTail rest)
breakMaybe :: (a -> Maybe b) -> [a] -> ([a], Maybe (b, [a]))
breakMaybe f = go id where
go !acc [] = (acc [], Nothing)
go !acc (x:xs) = case f x of
Nothing -> go (acc . (x:)) xs
Just b -> (acc [], Just (b, xs))
spanMaybe :: (a -> Maybe b) -> [a] -> ([b],[a])
spanMaybe _ xs@[] = ([], xs)
spanMaybe p xs@(x:xs') = case p x of
Just y -> let (ys, zs) = spanMaybe p xs' in (y : ys, zs)
Nothing -> ([], xs)
unfoldrM :: Monad m => (b -> m (Maybe (a, b))) -> b -> m [a]
unfoldrM f = go where
go b = do
m <- f b
case m of
Nothing -> return []
Just (a, b') -> liftM (a :) (go b')
isAbsoluteOnAnyPlatform :: FilePath -> Bool
isAbsoluteOnAnyPlatform (drive:':':'\\':_) = isAlpha drive
isAbsoluteOnAnyPlatform ('\\':'\\':_) = True
isAbsoluteOnAnyPlatform ('/':_) = True
isAbsoluteOnAnyPlatform _ = False
isRelativeOnAnyPlatform :: FilePath -> Bool
isRelativeOnAnyPlatform = not . isAbsoluteOnAnyPlatform