within-0.2.0.1: A value within another path.

LicenseMIT
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Within

Description

The Within type, an EnvT comonad specialised to `Path b Dir`.

Synopsis

Documentation

newtype WithinT b w a Source #

The Within Type, newtype wrapper around EnvT specialised to a `Path b Dir` environment.

Constructors

WithinT (EnvT (Path b Dir) w a) 
Instances
PathLike Rel t a => PathLike b t (Within b a) Source # 
Instance details

Defined in Within

Methods

toPath :: Within b a -> Path b t #

FileLike Rel a => FileLike b (Within b a) Source # 
Instance details

Defined in Within

Methods

toFile :: Within b a -> Path b File #

DirLike Rel a => DirLike b (Within b a) Source # 
Instance details

Defined in Within

Methods

toDir :: Within b a -> Path b Dir #

ComonadTrans (WithinT b) Source # 
Instance details

Defined in Within

Methods

lower :: Comonad w => WithinT b w a -> w a #

Eq t => Eq (Within b t) Source # 
Instance details

Defined in Within

Methods

(==) :: Within b t -> Within b t -> Bool #

(/=) :: Within b t -> Within b t -> Bool #

Functor w => Functor (WithinT b w) Source # 
Instance details

Defined in Within

Methods

fmap :: (a -> b0) -> WithinT b w a -> WithinT b w b0 #

(<$) :: a -> WithinT b w b0 -> WithinT b w a #

Ord t => Ord (Within b t) Source # 
Instance details

Defined in Within

Methods

compare :: Within b t -> Within b t -> Ordering #

(<) :: Within b t -> Within b t -> Bool #

(<=) :: Within b t -> Within b t -> Bool #

(>) :: Within b t -> Within b t -> Bool #

(>=) :: Within b t -> Within b t -> Bool #

max :: Within b t -> Within b t -> Within b t #

min :: Within b t -> Within b t -> Within b t #

Show t => Show (Within b t) Source # 
Instance details

Defined in Within

Methods

showsPrec :: Int -> Within b t -> ShowS #

show :: Within b t -> String #

showList :: [Within b t] -> ShowS #

Foldable w => Foldable (WithinT b w) Source # 
Instance details

Defined in Within

Methods

fold :: Monoid m => WithinT b w m -> m #

foldMap :: Monoid m => (a -> m) -> WithinT b w a -> m #

foldr :: (a -> b0 -> b0) -> b0 -> WithinT b w a -> b0 #

foldr' :: (a -> b0 -> b0) -> b0 -> WithinT b w a -> b0 #

foldl :: (b0 -> a -> b0) -> b0 -> WithinT b w a -> b0 #

foldl' :: (b0 -> a -> b0) -> b0 -> WithinT b w a -> b0 #

foldr1 :: (a -> a -> a) -> WithinT b w a -> a #

foldl1 :: (a -> a -> a) -> WithinT b w a -> a #

toList :: WithinT b w a -> [a] #

null :: WithinT b w a -> Bool #

length :: WithinT b w a -> Int #

elem :: Eq a => a -> WithinT b w a -> Bool #

maximum :: Ord a => WithinT b w a -> a #

minimum :: Ord a => WithinT b w a -> a #

sum :: Num a => WithinT b w a -> a #

product :: Num a => WithinT b w a -> a #

Traversable w => Traversable (WithinT b w) Source # 
Instance details

Defined in Within

Methods

traverse :: Applicative f => (a -> f b0) -> WithinT b w a -> f (WithinT b w b0) #

sequenceA :: Applicative f => WithinT b w (f a) -> f (WithinT b w a) #

mapM :: Monad m => (a -> m b0) -> WithinT b w a -> m (WithinT b w b0) #

sequence :: Monad m => WithinT b w (m a) -> m (WithinT b w a) #

Hashable t => Hashable (Within b t) Source # 
Instance details

Defined in Within

Methods

hashWithSalt :: Int -> Within b t -> Int #

hash :: Within b t -> Int #

Comonad w => Comonad (WithinT b w) Source # 
Instance details

Defined in Within

Methods

extract :: WithinT b w a -> a #

duplicate :: WithinT b w a -> WithinT b w (WithinT b w a) #

extend :: (WithinT b w a -> b0) -> WithinT b w a -> WithinT b w b0 #

Comonad w => ComonadEnv (Path b Dir) (WithinT b w) Source # 
Instance details

Defined in Within

Methods

ask :: WithinT b w a -> Path b Dir #

Generic (WithinT b w a) Source # 
Instance details

Defined in Within

Associated Types

type Rep (WithinT b w a) :: Type -> Type #

Methods

from :: WithinT b w a -> Rep (WithinT b w a) x #

to :: Rep (WithinT b w a) x -> WithinT b w a #

type Rep (WithinT b w a) Source # 
Instance details

Defined in Within

type Rep (WithinT b w a) = D1 (MetaData "WithinT" "Within" "within-0.2.0.1-Aqh9WzzDEJELdMBljEJj8h" True) (C1 (MetaCons "WithinT" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (EnvT (Path b Dir) w a))))

type Within b a = WithinT b Identity a Source #

localDir :: (Path b Dir -> Path c Dir) -> WithinT b w a -> WithinT c w a Source #

Change the parent directory of a Within value.

localDirM :: Monad m => (Path b Dir -> m (Path c Dir)) -> WithinT b w a -> m (WithinT c w a) Source #

Change the parent directory of a Within value, monadic verison.

asWithin :: MonadThrow m => Path a t -> Path a Dir -> m (Within a (Path Rel t)) Source #

Treat a Path as if it lies within another directory and returns a Within value. Used infix like

>>> $(mkRelFile "foo/a.txt") `asWithin` $(mkRelDir "foo")

within :: a -> Path b Dir -> Within b a Source #

Put a value inside a directory.

>>> $(mkRelFile "a.txt") `within` $(mkRelDir "foo")

fromWithin :: PathLike Rel t a => Within b a -> Path b t Source #

Turns a Within containing a PathLike into a single Path.

blinkLocalDir :: Path b Dir -> WithinT a w t -> WithinT b w t Source #

Switch the outer part of a Within value to a new directory, synonym for localDir . const

blinkAndMap :: Functor w => Path b Dir -> (s -> t) -> WithinT a w s -> WithinT b w t Source #

Switch the outer part of a Within value to a new directory and map the inner at the same time.

blinkAndMapM :: (Monad m, Traversable w) => Path b Dir -> (s -> m t) -> WithinT a w s -> m (WithinT b w t) Source #

Switch the outer part of a Within value to a new directory and mapM the inner at the same time.

localDirAndMapM :: (Monad m, Traversable w) => (Path b Dir -> m (Path c Dir)) -> (s -> m t) -> WithinT b w s -> m (WithinT c w t) Source #

mapM the outer and inner part of a Within value at the same time.