chatty-0.7.0.1: Some monad transformers and typeclasses for abstraction of global dependencies.

Safe HaskellSafe
LanguageHaskell2010

System.Chatty.Filesystem

Documentation

data FSExec a Source #

Constructors

FSSucc a 
NoPermission 
NotFound 

data File m Source #

Constructors

File 

Fields

newtype Path Source #

Constructors

MultiPath [PathSpec] 

Instances

Eq Path Source # 

Methods

(==) :: Path -> Path -> Bool #

(/=) :: Path -> Path -> Bool #

Ord Path Source # 

Methods

compare :: Path -> Path -> Ordering #

(<) :: Path -> Path -> Bool #

(<=) :: Path -> Path -> Bool #

(>) :: Path -> Path -> Bool #

(>=) :: Path -> Path -> Bool #

max :: Path -> Path -> Path #

min :: Path -> Path -> Path #

Show Path Source # 

Methods

showsPrec :: Int -> Path -> ShowS #

show :: Path -> String #

showList :: [Path] -> ShowS #

type FileA m = Atom (File m) Source #

data Mountpoint m Source #

Constructors

Mount 

Fields

class Monad m => ChFilesystem m where Source #

Minimal complete definition

fopen, fpwd, fcd

Methods

fopen :: Path -> m (FSExec (FileA m)) Source #

fpwd :: m Path Source #

fcd :: Path -> m () Source #

Instances

class Monad m => CanLoad m n where Source #

Minimal complete definition

fload

Methods

fload :: FileA n -> m (FSExec ()) Source #

class Monad m => CanSave m n where Source #

Minimal complete definition

fsave

Methods

fsave :: FileA n -> m (FSExec ()) Source #

class Monad m => CanMount m n where Source #

Minimal complete definition

fmount

Methods

fmount :: Mountpoint n -> m () Source #

Instances

Monad m => CanMount (NullFsT m) (NullFsT m) Source # 

Methods

fmount :: Mountpoint (NullFsT m) -> NullFsT m () Source #

data FilePrinterT m a Source #

Constructors

FilePrinter 

Fields

Instances

newtype NullFsT m a Source #

Constructors

NullFs 

Fields

Instances

MonadTrans NullFsT Source # 

Methods

lift :: Monad m => m a -> NullFsT m a #

Monad m => Monad (NullFsT m) Source # 

Methods

(>>=) :: NullFsT m a -> (a -> NullFsT m b) -> NullFsT m b #

(>>) :: NullFsT m a -> NullFsT m b -> NullFsT m b #

return :: a -> NullFsT m a #

fail :: String -> NullFsT m a #

Functor f => Functor (NullFsT f) Source # 

Methods

fmap :: (a -> b) -> NullFsT f a -> NullFsT f b #

(<$) :: a -> NullFsT f b -> NullFsT f a #

(Functor m, Monad m) => Applicative (NullFsT m) Source # 

Methods

pure :: a -> NullFsT m a #

(<*>) :: NullFsT m (a -> b) -> NullFsT m a -> NullFsT m b #

(*>) :: NullFsT m a -> NullFsT m b -> NullFsT m b #

(<*) :: NullFsT m a -> NullFsT m b -> NullFsT m a #

MonadIO m => MonadIO (NullFsT m) Source # 

Methods

liftIO :: IO a -> NullFsT m a #

Monad m => ChFilesystem (NullFsT m) Source # 
Monad m => CanMount (NullFsT m) (NullFsT m) Source # 

Methods

fmount :: Mountpoint (NullFsT m) -> NullFsT m () Source #

mount :: (CanMount m m, ChAtoms m, ChFilesystem m) => m (Mountpoint m) -> Path -> m () Source #

withNullFs :: ChAtoms m => NullFsT m a -> m a Source #

withExpandoFs :: (ChAtoms m, ChAtoms (NullFsT m)) => NullFsT m a -> m a Source #