path-tagged-0.1.0.0: A wrapper around the @path@ library, tagged with semantic name.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Path.Tagged

Synopsis

Types

newtype PathTo entity pk t Source #

Constructors

PathTo 

Fields

Instances

Instances details
(Typeable t, Typeable (Untag b)) => Lift (PathTo e b t :: Type) Source # 
Instance details

Defined in Path.Tagged

Methods

lift :: Quote m => PathTo e b t -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => PathTo e b t -> Code m (PathTo e b t) #

FromJSON (PathTo k2 (Abs :: Base k1) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSON (PathTo k2 (Abs :: Base k1) File) Source # 
Instance details

Defined in Path.Tagged

FromJSON (PathTo k2 (RelTo b) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSON (PathTo k2 (RelTo b) File) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (Abs :: Base k1) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (Abs :: Base k1) File) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (RelTo b) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (RelTo b) File) Source # 
Instance details

Defined in Path.Tagged

ToJSON (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

toJSON :: PathTo entity pk t -> Value #

toEncoding :: PathTo entity pk t -> Encoding #

toJSONList :: [PathTo entity pk t] -> Value #

toEncodingList :: [PathTo entity pk t] -> Encoding #

omitField :: PathTo entity pk t -> Bool #

Generic (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Associated Types

type Rep (PathTo entity pk t) :: Type -> Type #

Methods

from :: PathTo entity pk t -> Rep (PathTo entity pk t) x #

to :: Rep (PathTo entity pk t) x -> PathTo entity pk t #

Show (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

showsPrec :: Int -> PathTo entity pk t -> ShowS #

show :: PathTo entity pk t -> String #

showList :: [PathTo entity pk t] -> ShowS #

NFData (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

rnf :: PathTo entity pk t -> () #

Eq (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

(==) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

(/=) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

Ord (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

compare :: PathTo entity pk t -> PathTo entity pk t -> Ordering #

(<) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

(<=) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

(>) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

(>=) :: PathTo entity pk t -> PathTo entity pk t -> Bool #

max :: PathTo entity pk t -> PathTo entity pk t -> PathTo entity pk t #

min :: PathTo entity pk t -> PathTo entity pk t -> PathTo entity pk t #

Hashable (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

Methods

hashWithSalt :: Int -> PathTo entity pk t -> Int #

hash :: PathTo entity pk t -> Int #

AnyPathTo (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b Dir) Source #

type AbsPath (PathTo e b Dir) Source #

type RelPathTo' k e (PathTo e b Dir) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeAbsolute :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b Dir)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b Dir -> m (RelPathTo e0 (PathTo e b Dir)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b Dir -> m (RelPathTo' (PathTag (PathTo e b Dir)) Cwd (PathTo e b Dir)) Source #

AnyPathTo (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b File) Source #

type AbsPath (PathTo e b File) Source #

type RelPathTo' k e (PathTo e b File) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeAbsolute :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b File)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b File -> m (RelPathTo e0 (PathTo e b File)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b File -> m (RelPathTo' (PathTag (PathTo e b File)) Cwd (PathTo e b File)) Source #

type RelPathTo' k (e' :: k) (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (PathTo e b Dir) = PathTo e (RelTo e') Dir
type RelPathTo' k (e' :: k) (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (PathTo e b File) = PathTo e (RelTo e') File
type Rep (PathTo entity pk t) Source # 
Instance details

Defined in Path.Tagged

type Rep (PathTo entity pk t) = D1 ('MetaData "PathTo" "Path.Tagged" "path-tagged-0.1.0.0-FFPUlr6bBoZ95OWscTAxp" 'True) (C1 ('MetaCons "PathTo" 'PrefixI 'True) (S1 ('MetaSel ('Just "untagPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Path (Untag pk) t))))
type AbsPath (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (PathTo e b Dir) = PathTo e (Abs :: Base k) Dir
type AbsPath (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (PathTo e b File) = PathTo e (Abs :: Base k) File
type PathTag (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (PathTo e b Dir) = k
type PathTag (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (PathTo e b File) = k

type family ToSubpath a where ... Source #

Equations

ToSubpath 'Abs = 'Abs 
ToSubpath ('RelTo e) = 'RelTo (Entry e) 

retagPath :: PathTo p b t -> PathTo p' (Retagged b) t Source #

data Base k Source #

Constructors

RelTo k 
Abs 

type family Untag pk where ... Source #

Equations

Untag ('RelTo _) = Rel 
Untag 'Abs = Abs 

type Abs = 'Abs Source #

data File #

A file path.

Instances

Instances details
Data File 
Instance details

Defined in Path.Posix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File #

toConstr :: File -> Constr #

dataTypeOf :: File -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c File) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) #

gmapT :: (forall b. Data b => b -> b) -> File -> File #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQ :: (forall d. Data d => d -> u) -> File -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

FromJSON (SomeBase File) 
Instance details

Defined in Path.Posix

AnyPath (SomeBase File)

Since: path-io-1.8.0

Instance details

Defined in Path.IO

Associated Types

type AbsPath (SomeBase File) #

type RelPath (SomeBase File) #

FromJSON (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs File) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel File) 
Instance details

Defined in Path.Posix

AnyPath (Path b File) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b File) #

type RelPath (Path b File) #

FromJSON (PathTo k2 (Abs :: Base k1) File) Source # 
Instance details

Defined in Path.Tagged

FromJSON (PathTo k2 (RelTo b) File) Source # 
Instance details

Defined in Path.Tagged

FromJSON (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (Abs :: Base k1) File) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (RelTo b) File) Source # 
Instance details

Defined in Path.Tagged

AnyPathTo (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b File) Source #

type AbsPath (PathTo e b File) Source #

type RelPathTo' k e (PathTo e b File) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeAbsolute :: MonadIO m => PathTo e b File -> m (AbsPath (PathTo e b File)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b File)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b File -> m (RelPathTo e0 (PathTo e b File)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b File -> m (RelPathTo' (PathTag (PathTo e b File)) Cwd (PathTo e b File)) Source #

AnyPathTo (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b File) Source #

type AbsPath (SomeBase e b File) Source #

type RelPathTo' k e (SomeBase e b File) Source #

type RelPathTo' k (e' :: k) (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (PathTo e b File) = PathTo e (RelTo e') File
type RelPathTo' k (e' :: k) (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (SomeBase e b File) = PathTo e (RelTo e') File
type AbsPath (SomeBase File) 
Instance details

Defined in Path.IO

type RelPath (SomeBase File) 
Instance details

Defined in Path.IO

type AbsPath (Path b File) 
Instance details

Defined in Path.IO

type RelPath (Path b File) 
Instance details

Defined in Path.IO

type AbsPath (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (PathTo e b File) = PathTo e (Abs :: Base k) File
type AbsPath (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (SomeBase e b File) = PathTo e (Abs :: Base k) File
type PathTag (PathTo e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (PathTo e b File) = k
type PathTag (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (SomeBase e b File) = k

data Dir #

A directory path.

Instances

Instances details
Data Dir 
Instance details

Defined in Path.Posix

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dir -> c Dir #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Dir #

toConstr :: Dir -> Constr #

dataTypeOf :: Dir -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Dir) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Dir) #

gmapT :: (forall b. Data b => b -> b) -> Dir -> Dir #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dir -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dir -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dir -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dir -> m Dir #

FromJSON (SomeBase Dir) 
Instance details

Defined in Path.Posix

AnyPath (SomeBase Dir)

Since: path-io-1.8.0

Instance details

Defined in Path.IO

Associated Types

type AbsPath (SomeBase Dir) #

type RelPath (SomeBase Dir) #

FromJSON (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSON (Path Rel Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Abs Dir) 
Instance details

Defined in Path.Posix

FromJSONKey (Path Rel Dir) 
Instance details

Defined in Path.Posix

AnyPath (Path b Dir) 
Instance details

Defined in Path.IO

Associated Types

type AbsPath (Path b Dir) #

type RelPath (Path b Dir) #

FromJSON (PathTo k2 (Abs :: Base k1) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSON (PathTo k2 (RelTo b) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSON (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (Abs :: Base k1) Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSONKey (PathTo k2 (RelTo b) Dir) Source # 
Instance details

Defined in Path.Tagged

AnyPathTo (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (PathTo e b Dir) Source #

type AbsPath (PathTo e b Dir) Source #

type RelPathTo' k e (PathTo e b Dir) Source #

Methods

canonicalizePath :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeAbsolute :: MonadIO m => PathTo e b Dir -> m (AbsPath (PathTo e b Dir)) Source #

makeRelative :: forall m (e0 :: PathTag (PathTo e b Dir)). MonadThrow m => PathTo e0 Abs Dir -> PathTo e b Dir -> m (RelPathTo e0 (PathTo e b Dir)) Source #

makeRelativeToCurrentDir :: MonadIO m => PathTo e b Dir -> m (RelPathTo' (PathTag (PathTo e b Dir)) Cwd (PathTo e b Dir)) Source #

AnyPathTo (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b Dir) Source #

type AbsPath (SomeBase e b Dir) Source #

type RelPathTo' k e (SomeBase e b Dir) Source #

type RelPathTo' k (e' :: k) (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (PathTo e b Dir) = PathTo e (RelTo e') Dir
type RelPathTo' k (e' :: k) (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (SomeBase e b Dir) = PathTo e (RelTo e') Dir
type AbsPath (SomeBase Dir) 
Instance details

Defined in Path.IO

type RelPath (SomeBase Dir) 
Instance details

Defined in Path.IO

type AbsPath (Path b Dir) 
Instance details

Defined in Path.IO

type AbsPath (Path b Dir) = Path Abs Dir
type RelPath (Path b Dir) 
Instance details

Defined in Path.IO

type RelPath (Path b Dir) = Path Rel Dir
type AbsPath (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (PathTo e b Dir) = PathTo e (Abs :: Base k) Dir
type AbsPath (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (SomeBase e b Dir) = PathTo e (Abs :: Base k) Dir
type PathTag (PathTo e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (PathTo e b Dir) = k
type PathTag (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (SomeBase e b Dir) = k

Special Entity Tags

type family Unknown where ... Source #

Unknown base directory

data Subpath k Source #

Constructors

Entry k 
Parent (Subpath k) 

type family EntryOf k where ... Source #

Equations

EntryOf ('Entry e) = e 
EntryOf p = TypeError ('Text "Concrete entry expected, but got: " ':<>: 'ShowType p) 

type ParentOf e = 'Parent ('Entry e) Source #

data SomeBase e b t Source #

Constructors

IsAbs (PathTo e Abs t) 
IsRel (PathTo e (RelTo b) t) 

Instances

Instances details
FromJSON (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged

FromJSON (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged

ToJSON (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

toJSON :: SomeBase e b t -> Value #

toEncoding :: SomeBase e b t -> Encoding #

toJSONList :: [SomeBase e b t] -> Value #

toEncodingList :: [SomeBase e b t] -> Encoding #

omitField :: SomeBase e b t -> Bool #

Generic (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Associated Types

type Rep (SomeBase e b t) :: Type -> Type #

Methods

from :: SomeBase e b t -> Rep (SomeBase e b t) x #

to :: Rep (SomeBase e b t) x -> SomeBase e b t #

Show (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

showsPrec :: Int -> SomeBase e b t -> ShowS #

show :: SomeBase e b t -> String #

showList :: [SomeBase e b t] -> ShowS #

NFData (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

rnf :: SomeBase e b t -> () #

Eq (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

(==) :: SomeBase e b t -> SomeBase e b t -> Bool #

(/=) :: SomeBase e b t -> SomeBase e b t -> Bool #

Ord (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

compare :: SomeBase e b t -> SomeBase e b t -> Ordering #

(<) :: SomeBase e b t -> SomeBase e b t -> Bool #

(<=) :: SomeBase e b t -> SomeBase e b t -> Bool #

(>) :: SomeBase e b t -> SomeBase e b t -> Bool #

(>=) :: SomeBase e b t -> SomeBase e b t -> Bool #

max :: SomeBase e b t -> SomeBase e b t -> SomeBase e b t #

min :: SomeBase e b t -> SomeBase e b t -> SomeBase e b t #

Hashable (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

Methods

hashWithSalt :: Int -> SomeBase e b t -> Int #

hash :: SomeBase e b t -> Int #

AnyPathTo (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b Dir) Source #

type AbsPath (SomeBase e b Dir) Source #

type RelPathTo' k e (SomeBase e b Dir) Source #

AnyPathTo (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

Associated Types

type PathTag (SomeBase e b File) Source #

type AbsPath (SomeBase e b File) Source #

type RelPathTo' k e (SomeBase e b File) Source #

type RelPathTo' k (e' :: k) (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (SomeBase e b Dir) = PathTo e (RelTo e') Dir
type RelPathTo' k (e' :: k) (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type RelPathTo' k (e' :: k) (SomeBase e b File) = PathTo e (RelTo e') File
type Rep (SomeBase e b t) Source # 
Instance details

Defined in Path.Tagged

type Rep (SomeBase e b t) = D1 ('MetaData "SomeBase" "Path.Tagged" "path-tagged-0.1.0.0-FFPUlr6bBoZ95OWscTAxp" 'False) (C1 ('MetaCons "IsAbs" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PathTo e (Abs :: Base k) t))) :+: C1 ('MetaCons "IsRel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PathTo e (RelTo b) t))))
type AbsPath (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (SomeBase e b Dir) = PathTo e (Abs :: Base k) Dir
type AbsPath (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type AbsPath (SomeBase e b File) = PathTo e (Abs :: Base k) File
type PathTag (SomeBase e b Dir) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (SomeBase e b Dir) = k
type PathTag (SomeBase e b File) Source # 
Instance details

Defined in Path.Tagged.IO

type PathTag (SomeBase e b File) = k

Exceptions

QuasiQuotes

Operations

(</>) :: PathTo parent b Dir -> PathTo child (RelTo parent) t -> PathTo child b t infixr 5 Source #

stripProperPrefix :: MonadThrow m => PathTo p b Dir -> PathTo l b t -> m (PathTo l (RelTo p) t) Source #

replaceProperPrefix :: MonadThrow m => PathTo parent b Dir -> PathTo parent' b' Dir -> PathTo child b t -> m (PathTo child b' t) Source #

replaceProperPrefix' :: MonadThrow m => PathTo parent b Dir -> PathTo parent b' Dir -> PathTo child b t -> m (PathTo child b' t) Source #

addExtension :: forall e' m e b. MonadThrow m => String -> PathTo e b File -> m (PathTo e' b File) Source #

splitExtension :: forall e' m e b. MonadThrow m => PathTo e b File -> m (PathTo e' b File, String) Source #

replaceExtension :: forall e' m e b. MonadThrow m => String -> PathTo e b File -> m (PathTo e' b File) Source #

mapSomeBase :: (forall c. PathTo e c t -> PathTo e' c t') -> SomeBase e b t -> SomeBase e' b t' Source #

prjSomeBase :: (forall c. PathTo e c t -> a) -> SomeBase e b t -> a Source #

Parsing

parseAbsDir :: forall e m. MonadThrow m => FilePath -> m (PathTo e Abs Dir) Source #

parseRelDir :: forall e b m. MonadThrow m => FilePath -> m (PathTo e (RelTo b) Dir) Source #

parseAbsFile :: forall e m. MonadThrow m => FilePath -> m (PathTo e Abs File) Source #

parseRelFile :: forall e b m. MonadThrow m => FilePath -> m (PathTo e (RelTo b) File) Source #

Conversion

TemplateHaskell constructors

Typed constructors