filepather-0.5.5: Functions on System.FilePath
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.FilePath.FilePather.ReadFilePath

Documentation

newtype ReadFilePathT e f a Source #

Constructors

ReadFilePathT (FilePath -> f (Either e a)) 

Instances

Instances details
MFunctor (ReadFilePathT e :: (Type -> Type) -> Type -> TYPE LiftedRep) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

hoist :: forall m n (b :: k). Monad m => (forall a. m a -> n a) -> ReadFilePathT e m b -> ReadFilePathT e n b #

MonadError e f => MonadError e (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

throwError :: e -> ReadFilePathT e f a #

catchError :: ReadFilePathT e f a -> (e -> ReadFilePathT e f a) -> ReadFilePathT e f a #

Monad f => MonadReader FilePath (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

ask :: ReadFilePathT e f FilePath #

local :: (FilePath -> FilePath) -> ReadFilePathT e f a -> ReadFilePathT e f a #

reader :: (FilePath -> a) -> ReadFilePathT e f a #

MonadState FilePath f => MonadState FilePath (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

get :: ReadFilePathT e f FilePath #

put :: FilePath -> ReadFilePathT e f () #

state :: (FilePath -> (a, FilePath)) -> ReadFilePathT e f a #

MonadWriter FilePath f => MonadWriter FilePath (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

writer :: (a, FilePath) -> ReadFilePathT e f a #

tell :: FilePath -> ReadFilePathT e f () #

listen :: ReadFilePathT e f a -> ReadFilePathT e f (a, FilePath) #

pass :: ReadFilePathT e f (a, FilePath -> FilePath) -> ReadFilePathT e f a #

MMonad (ReadFilePathT e) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

embed :: forall (n :: Type -> Type) m b. Monad n => (forall a. m a -> ReadFilePathT e n a) -> ReadFilePathT e m b -> ReadFilePathT e n b #

MonadTrans (ReadFilePathT e) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

lift :: Monad m => m a -> ReadFilePathT e m a #

MonadFail f => MonadFail (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

fail :: String -> ReadFilePathT e f a #

MonadFix f => MonadFix (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

mfix :: (a -> ReadFilePathT e f a) -> ReadFilePathT e f a #

MonadIO f => MonadIO (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

liftIO :: IO a -> ReadFilePathT e f a #

MonadZip f => MonadZip (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

mzip :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f (a, b) #

mzipWith :: (a -> b -> c) -> ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f c #

munzip :: ReadFilePathT e f (a, b) -> (ReadFilePathT e f a, ReadFilePathT e f b) #

Monad f => Applicative (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

pure :: a -> ReadFilePathT e f a #

(<*>) :: ReadFilePathT e f (a -> b) -> ReadFilePathT e f a -> ReadFilePathT e f b #

liftA2 :: (a -> b -> c) -> ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f c #

(*>) :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f b #

(<*) :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f a #

Functor f => Functor (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

fmap :: (a -> b) -> ReadFilePathT e f a -> ReadFilePathT e f b #

(<$) :: a -> ReadFilePathT e f b -> ReadFilePathT e f a #

Monad f => Monad (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

(>>=) :: ReadFilePathT e f a -> (a -> ReadFilePathT e f b) -> ReadFilePathT e f b #

(>>) :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f b #

return :: a -> ReadFilePathT e f a #

MonadCont f => MonadCont (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

callCC :: ((a -> ReadFilePathT e f b) -> ReadFilePathT e f a) -> ReadFilePathT e f a #

Monad f => Alt (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

(<!>) :: ReadFilePathT e f a -> ReadFilePathT e f a -> ReadFilePathT e f a #

some :: Applicative (ReadFilePathT e f) => ReadFilePathT e f a -> ReadFilePathT e f [a] #

many :: Applicative (ReadFilePathT e f) => ReadFilePathT e f a -> ReadFilePathT e f [a] #

Monad f => Apply (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

(<.>) :: ReadFilePathT e f (a -> b) -> ReadFilePathT e f a -> ReadFilePathT e f b #

(.>) :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f b #

(<.) :: ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f a #

liftF2 :: (a -> b -> c) -> ReadFilePathT e f a -> ReadFilePathT e f b -> ReadFilePathT e f c #

Monad f => Bind (ReadFilePathT e f) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

(>>-) :: ReadFilePathT e f a -> (a -> ReadFilePathT e f b) -> ReadFilePathT e f b #

join :: ReadFilePathT e f (ReadFilePathT e f a) -> ReadFilePathT e f a #

(Monad f, Monoid a) => Monoid (ReadFilePathT e f a) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

mempty :: ReadFilePathT e f a #

mappend :: ReadFilePathT e f a -> ReadFilePathT e f a -> ReadFilePathT e f a #

mconcat :: [ReadFilePathT e f a] -> ReadFilePathT e f a #

(Monad f, Semigroup a) => Semigroup (ReadFilePathT e f a) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Methods

(<>) :: ReadFilePathT e f a -> ReadFilePathT e f a -> ReadFilePathT e f a #

sconcat :: NonEmpty (ReadFilePathT e f a) -> ReadFilePathT e f a #

stimes :: Integral b => b -> ReadFilePathT e f a -> ReadFilePathT e f a #

Wrapped (ReadFilePathT e f a) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

Associated Types

type Unwrapped (ReadFilePathT e f a) #

Methods

_Wrapped' :: Iso' (ReadFilePathT e f a) (Unwrapped (ReadFilePathT e f a)) #

ReadFilePathT e f a ~ t => Rewrapped (ReadFilePathT e' f' a') t Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

type Unwrapped (ReadFilePathT e f a) Source # 
Instance details

Defined in System.FilePath.FilePather.ReadFilePath

type Unwrapped (ReadFilePathT e f a) = FilePath -> f (Either e a)