| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Proteome.Filename
Documentation
Instances
data Modification Source #
Constructors
| Filename (Path Rel File) (Path Rel Dir) NameSpec [Text] | |
| Dir (Path Abs Dir) | |
| File (Path Abs File) | |
| Container Int (Path Rel Dir) | 
Instances
| Show Modification Source # | |
| Defined in Proteome.Filename Methods showsPrec :: Int -> Modification -> ShowS # show :: Modification -> String # showList :: [Modification] -> ShowS # | |
| Eq Modification Source # | |
| Defined in Proteome.Filename | |
dotsInPath :: Text -> Int Source #
absoluteDir :: Text -> Maybe Modification Source #
absoluteFile :: Text -> Maybe Modification Source #
relativeDir :: Path Abs Dir -> Text -> Maybe Modification Source #
relativeFile :: Path Abs Dir -> Text -> Maybe Modification Source #
regularModification :: Members [Stop FilenameError, Embed IO] r => Path Abs Dir -> Text -> Sem r Modification Source #
modification :: Members [Stop FilenameError, Embed IO] r => Bool -> Path Abs Dir -> Text -> Sem r Modification Source #
checkBufferPath :: Members [Rpc, Stop FilenameError, Embed IO] r => Path Abs Dir -> Sem r (Path Abs File) Source #
renameInplace :: Member (Stop FilenameError) r => Bool -> Path Rel File -> BufPath -> Path Rel Dir -> NameSpec -> [Text] -> Sem r (Path Abs File) Source #
replaceDir :: Member (Stop FilenameError) r => Int -> Path Rel Dir -> Path Abs File -> Sem r (Path Abs File) Source #
assemblePath :: Member (Stop FilenameError) r => Bool -> Path Abs File -> Modification -> Sem r (Path Abs File) Source #
ensureDestinationEmpty :: Members [Stop FilenameError, Embed IO] r => Path Abs File -> Sem r () Source #
prepareDestination :: Members [Stop FilenameError, Embed IO] r => Path Abs File -> Sem r () Source #
smartModification :: Members [Stop FilenameError, Rpc !! RpcError, Embed IO] r => Bool -> Text -> Sem r Modification Source #
trashModification :: Members [Stop FilenameError, Rpc, Rpc !! RpcError, PersistPath, Embed IO] r => Sem r Modification Source #
pathsForMod :: Members [Stop FilenameError, Rpc, Rpc !! RpcError, Embed IO] r => Bool -> Modification -> Sem r (Path Abs File, Path Abs File) Source #
relocate :: Members [Stop FilenameError, Rpc, Rpc !! RpcError, Embed IO] r => Bool -> Modification -> (Path Abs File -> Path Abs File -> Sem r ()) -> Sem r () Source #
copyOrFail :: Members [Stop FilenameError, Embed IO] r => Path Abs File -> Path Abs File -> Sem r () Source #
moveFile :: Members [Stop FilenameError, DataLog LogReport, Embed IO] r => Path Abs File -> Path Abs File -> Sem r () Source #
move :: Members [Stop FilenameError, DataLog LogReport, Rpc, Rpc !! RpcError, Embed IO] r => Bool -> Modification -> Sem r () Source #
copy :: Members [Stop FilenameError, Rpc, Rpc !! RpcError, Embed IO] r => Bool -> Modification -> Sem r () Source #