Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data FileAction
- editFile :: MenuWidget FilesState r FileAction
- matchingDirs :: Member (Embed IO) r => [Path Abs Dir] -> Path Rel Dir -> Sem r [Path Abs Dir]
- dirsWithPrefix :: Member (Embed IO) r => Text -> Path Abs Dir -> Sem r [Path Rel Dir]
- matchingPaths :: Member (Embed IO) r => [Path Abs Dir] -> Text -> Sem r (Text, [Path Rel Dir])
- commonPrefix :: [Text] -> Maybe Text
- tabComplete :: Member (Embed IO) r => [Path Abs Dir] -> Text -> Sem r (Maybe Text)
- tabUpdatePrompt :: PromptMode -> Text -> Prompt
- tab :: Member (Embed IO) r => [Path Abs Dir] -> MenuWidget FilesState r FileAction
- createAndEditFile :: Members [Rpc, Stop FilesError, Embed IO] r => Path Abs File -> Sem r ()
- existingSubdirCount :: Member (Embed IO) r => [Text] -> Path Abs Dir -> Sem r Int
- createFile :: Member (Reader Prompt) r => Members [Stop FilesError, Embed IO] r => NonEmpty (Path Abs Dir) -> Sem r (Maybe (MenuAction FileAction))
- cycleSegment :: MenuWidget FilesState r FileAction
- actions :: Members [Stop FilesError, Embed IO] r => NonEmpty (Path Abs Dir) -> Mappings FilesState r FileAction
- parsePath :: Path Abs Dir -> Text -> Maybe (Path Abs Dir)
- readRegex :: Member (Stop FilesError) r => Text -> Text -> Sem r Regex
- readRegexs :: Members [Settings, Stop FilesError] r => Setting [Text] -> Sem r [Regex]
- filesConfig :: Members [Rpc, Settings, Stop FilesError] r => Sem r FilesConfig
- fileAction :: Members [Rpc, Stop FilesError, Stop Report, Embed IO] r => FileAction -> Sem r ()
- type FilesStack = [WindowMenus () FilesState !! RpcError, Log, Async, Embed IO]
- filesMenu :: Members FilesStack r => Members [Stop FilesError, Stop Report, Settings, Rpc] r => Path Abs Dir -> [Text] -> Sem r ()
- proFiles :: Members FilesStack r => Members [Rpc !! RpcError, Settings !! SettingError] r => ArgList -> Handler r ()
Documentation
data FileAction Source #
Instances
Show FileAction Source # | |
Defined in Proteome.Files showsPrec :: Int -> FileAction -> ShowS # show :: FileAction -> String # showList :: [FileAction] -> ShowS # | |
Eq FileAction Source # | |
Defined in Proteome.Files (==) :: FileAction -> FileAction -> Bool # (/=) :: FileAction -> FileAction -> Bool # |
matchingDirs :: Member (Embed IO) r => [Path Abs Dir] -> Path Rel Dir -> Sem r [Path Abs Dir] Source #
matchingPaths :: Member (Embed IO) r => [Path Abs Dir] -> Text -> Sem r (Text, [Path Rel Dir]) Source #
Search all dirs in bases
for relative paths starting with text
.
First, split the last path segment (after /) off and collect the subdirectories of bases
that start with the
remainder. If there is no / in the text, parsing the remainder fails with Nothing
and the bases
themselves are
used.
Then, search the resulting dirs for subdirs starting with the last segment.
Return the remainder and the relative subdir paths.
tabUpdatePrompt :: PromptMode -> Text -> Prompt Source #
tab :: Member (Embed IO) r => [Path Abs Dir] -> MenuWidget FilesState r FileAction Source #
createAndEditFile :: Members [Rpc, Stop FilesError, Embed IO] r => Path Abs File -> Sem r () Source #
createFile :: Member (Reader Prompt) r => Members [Stop FilesError, Embed IO] r => NonEmpty (Path Abs Dir) -> Sem r (Maybe (MenuAction FileAction)) Source #
actions :: Members [Stop FilesError, Embed IO] r => NonEmpty (Path Abs Dir) -> Mappings FilesState r FileAction Source #
filesConfig :: Members [Rpc, Settings, Stop FilesError] r => Sem r FilesConfig Source #
fileAction :: Members [Rpc, Stop FilesError, Stop Report, Embed IO] r => FileAction -> Sem r () Source #
type FilesStack = [WindowMenus () FilesState !! RpcError, Log, Async, Embed IO] Source #