module Utils where import Prelude hiding (catch) import Control.Exception (catch, IOException) import Control.Monad (forM) import System.Directory (getDirectoryContents, doesFileExist, doesDirectoryExist) import System.FilePath (()) import Data.Vec (NearZero(nearZero)) import Numeric.QD (QuadDouble) import Fractal.RUFF.Types.Complex (Complex((:+))) safeRead :: Read a => String -> Maybe a safeRead s = case reads s of [(a, "")] -> Just a _ -> Nothing catchIO :: IO a -> (IOException -> IO a) -> IO a catchIO = catch getFilesRecursive :: FilePath -> IO [([FilePath], FilePath)] getFilesRecursive d = (do fs0 <- getDirectoryContents d let fs = filter (`notElem` [".", ".."]) fs0 ffs <- forM fs $ \f -> do let df = d f fe <- doesFileExist df fd <- doesDirectoryExist df case (fe, fd) of (True, False) -> return [([], f)] (False, True) -> map (\(ds, f') -> (f:ds, f')) `fmap` getFilesRecursive df _ -> return [] return (concat ffs)) `catchIO` (\_ -> return []) safeLast :: [a] -> Maybe a safeLast [] = Nothing safeLast [x] = Just x safeLast (_:xs) = safeLast xs instance NearZero QuadDouble where nearZero x = not (abs x > (1e-60)) instance (NearZero a) => NearZero (Complex a) where nearZero (r :+ i) = nearZero r && nearZero i