module Futhark.Util
(mapAccumLM,
chunk,
chunks,
dropAt,
takeLast,
dropLast,
mapEither,
maybeNth,
maybeHead,
splitFromEnd,
splitAt3,
splitAt4,
focusNth,
unixEnvironment,
isEnvVarSet,
runProgramWithExitCode,
directoryContents,
roundFloat,
roundDouble,
fromPOSIX,
toPOSIX,
trim,
pmapIO,
zEncodeString
)
where
import Numeric
import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Char
import Data.List
import Data.Either
import Data.Maybe
import System.Environment
import System.IO.Unsafe
import qualified System.Directory.Tree as Dir
import System.Process
import System.Exit
import qualified System.FilePath.Posix as Posix
import qualified System.FilePath as Native
mapAccumLM :: Monad m =>
(acc -> x -> m (acc, y)) -> acc -> [x] -> m (acc, [y])
mapAccumLM _ acc [] = return (acc, [])
mapAccumLM f acc (x:xs) = do
(acc', x') <- f acc x
(acc'', xs') <- mapAccumLM f acc' xs
return (acc'', x':xs')
chunk :: Int -> [a] -> [[a]]
chunk _ [] = []
chunk n xs =
let (bef,aft) = splitAt n xs
in bef : chunk n aft
chunks :: [Int] -> [a] -> [[a]]
chunks [] _ = []
chunks (n:ns) xs =
let (bef,aft) = splitAt n xs
in bef : chunks ns aft
dropAt :: Int -> Int -> [a] -> [a]
dropAt i n xs = take i xs ++ drop (i+n) xs
takeLast :: Int -> [a] -> [a]
takeLast n = reverse . take n . reverse
dropLast :: Int -> [a] -> [a]
dropLast n = reverse . drop n . reverse
mapEither :: (a -> Either b c) -> [a] -> ([b], [c])
mapEither f l = partitionEithers $ map f l
maybeNth :: Integral int => int -> [a] -> Maybe a
maybeNth i l
| i >= 0, v:_ <- genericDrop i l = Just v
| otherwise = Nothing
maybeHead :: [a] -> Maybe a
maybeHead [] = Nothing
maybeHead (x:_) = Just x
splitFromEnd :: Int -> [a] -> ([a], [a])
splitFromEnd i l = splitAt (length l - i) l
splitAt3 :: Int -> Int -> [a] -> ([a], [a], [a])
splitAt3 n m l =
let (xs, l') = splitAt n l
(ys, zs) = splitAt m l'
in (xs, ys, zs)
splitAt4 :: Int -> Int -> Int -> [a] -> ([a], [a], [a], [a])
splitAt4 n m k l =
let (xs, l') = splitAt n l
(ys, l'') = splitAt m l'
(zs, vs) = splitAt k l''
in (xs, ys, zs, vs)
focusNth :: Integral int => int -> [a] -> Maybe ([a], a, [a])
focusNth i xs
| (bef, x:aft) <- genericSplitAt i xs = Just (bef, x, aft)
| otherwise = Nothing
{-# NOINLINE unixEnvironment #-}
unixEnvironment :: [(String,String)]
unixEnvironment = unsafePerformIO getEnvironment
isEnvVarSet :: String -> Bool -> Bool
isEnvVarSet name default_val = fromMaybe default_val $ do
val <- lookup name unixEnvironment
case val of
"0" -> return False
"1" -> return True
_ -> Nothing
runProgramWithExitCode :: FilePath -> [String] -> String
-> IO (Either IOException (ExitCode, String, String))
runProgramWithExitCode exe args inp =
(Right <$> readProcessWithExitCode exe args inp)
`catch` \e -> return (Left e)
directoryContents :: FilePath -> IO [FilePath]
directoryContents dir = do
_ Dir.:/ tree <- Dir.readDirectoryWith return dir
case Dir.failures tree of
Dir.Failed _ err : _ -> throw err
_ -> return $ mapMaybe isFile $ Dir.flattenDir tree
where isFile (Dir.File _ path) = Just path
isFile _ = Nothing
foreign import ccall "nearbyint" c_nearbyint :: Double -> Double
foreign import ccall "nearbyintf" c_nearbyintf :: Float -> Float
roundFloat :: Float -> Float
roundFloat = c_nearbyintf
roundDouble :: Double -> Double
roundDouble = c_nearbyint
toPOSIX :: Native.FilePath -> Posix.FilePath
toPOSIX = Posix.joinPath . Native.splitDirectories
fromPOSIX :: Posix.FilePath -> Native.FilePath
fromPOSIX = Native.joinPath . Posix.splitDirectories
trim :: String -> String
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace
fork :: (a -> IO b) -> a -> IO (MVar b)
fork f x = do cell <- newEmptyMVar
void $ forkIO $ do result <- f x
putMVar cell result
return cell
pmapIO :: (a -> IO b) -> [a] -> IO [b]
pmapIO f elems = go elems []
where
go [] res = return res
go xs res = do
numThreads <- getNumCapabilities
let (e,es) = splitAt numThreads xs
mvars <- mapM (fork f) e
result <- mapM takeMVar mvars
go es (result ++ res)
type UserString = String
type EncodedString = String
zEncodeString :: UserString -> EncodedString
zEncodeString "" = ""
zEncodeString (c:cs) = encodeDigitChar c ++ concatMap encodeChar cs
unencodedChar :: Char -> Bool
unencodedChar 'Z' = False
unencodedChar 'z' = False
unencodedChar '_' = True
unencodedChar c = isAsciiLower c
|| isAsciiUpper c
|| isDigit c
encodeDigitChar :: Char -> EncodedString
encodeDigitChar c | isDigit c = encodeAsUnicodeCharar c
| otherwise = encodeChar c
encodeChar :: Char -> EncodedString
encodeChar c | unencodedChar c = [c]
encodeChar '(' = "ZL"
encodeChar ')' = "ZR"
encodeChar '[' = "ZM"
encodeChar ']' = "ZN"
encodeChar ':' = "ZC"
encodeChar 'Z' = "ZZ"
encodeChar 'z' = "zz"
encodeChar '&' = "za"
encodeChar '|' = "zb"
encodeChar '^' = "zc"
encodeChar '$' = "zd"
encodeChar '=' = "ze"
encodeChar '>' = "zg"
encodeChar '#' = "zh"
encodeChar '.' = "zi"
encodeChar '<' = "zl"
encodeChar '-' = "zm"
encodeChar '!' = "zn"
encodeChar '+' = "zp"
encodeChar '\'' = "zq"
encodeChar '\\' = "zr"
encodeChar '/' = "zs"
encodeChar '*' = "zt"
encodeChar '_' = "zu"
encodeChar '%' = "zv"
encodeChar c = encodeAsUnicodeCharar c
encodeAsUnicodeCharar :: Char -> EncodedString
encodeAsUnicodeCharar c = 'z' : if isDigit (head hex_str) then hex_str
else '0':hex_str
where hex_str = showHex (ord c) "U"