-- This file is part of htalkat -- Copyright (C) 2021 Martin Bays -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of version 3 of the GNU General Public License as -- published by the Free Software Foundation, or any later version. -- -- You should have received a copy of the GNU General Public License -- along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE Safe #-} module Mundanities where import Control.Applicative (Alternative, empty) import Control.Monad.Catch (MonadMask, handle) import Control.Monad.IO.Class (MonadIO, liftIO) import System.Directory import System.FilePath -- |returns true iff path is contained within the directory dir isSubPath :: FilePath -> FilePath -> IO Bool isSubPath dir path = isRelative . makeRelative dir <$> canonicalizePath path ignoreIOErr :: (MonadIO m, MonadMask m, Monoid a) => m a -> m a ignoreIOErr = handle ((\_ -> return mempty) :: (Monad m, Monoid a) => IOError -> m a) warnIOErr :: (MonadIO m, MonadMask m, Monoid a) => m a -> m a warnIOErr = handle ((\e -> liftIO (print e) >> return mempty) :: (MonadIO m, Monoid a) => IOError -> m a) ignoreIOErrAlt :: (MonadIO m, MonadMask m, Alternative f) => m (f a) -> m (f a) ignoreIOErrAlt = handle ((\_ -> return empty) :: (Monad m, Alternative f) => IOError -> m (f a)) warnIOErrAlt :: (MonadIO m, MonadMask m, Alternative f) => m (f a) -> m (f a) warnIOErrAlt = handle ((\e -> liftIO (print e) >> return empty) :: (MonadIO m, Alternative f) => IOError -> m (f a))