Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Documentation
type GrepState = ModalState GrepOutputLine Source #
data GrepAction Source #
Select (Path Abs File) Int (Maybe Int) | |
Replace (NonEmpty GrepOutputLine) | |
Delete (NonEmpty GrepOutputLine) | |
NoAction |
Instances
Show GrepAction Source # | |
Defined in Proteome.Grep showsPrec :: Int -> GrepAction -> ShowS # show :: GrepAction -> String # showList :: [GrepAction] -> ShowS # | |
Eq GrepAction Source # | |
Defined in Proteome.Grep (==) :: GrepAction -> GrepAction -> Bool # (/=) :: GrepAction -> GrepAction -> Bool # |
yankResult :: Members [Rpc, Resource, Embed IO] r => MenuWidget GrepState r GrepAction Source #
uniqueGrepLines :: Functor (t IO) => IsStream t => t IO (MenuItem GrepOutputLine) -> t IO (MenuItem GrepOutputLine) Source #
grepItems :: Members [Settings !! SettingError, Rpc, Stop GrepError, Log, Embed IO, Final IO] r => Path Abs Dir -> Text -> [Text] -> Sem r (SerialT IO (MenuItem GrepOutputLine)) Source #
actions :: Members [Scratch, Rpc, Rpc !! RpcError, AtomicState Env, Stop ReplaceError, Resource, Embed IO] r => Mappings GrepState r GrepAction Source #
grepAction :: Members [Scratch, Rpc, Rpc !! RpcError, AtomicState Env, Stop ReplaceError, Resource, Embed IO] r => GrepAction -> Sem r () Source #
type GrepErrorStack = [Scratch, Settings, Rpc, Stop ReplaceError, Stop GrepError] Source #
handleErrors :: Members [Settings !! SettingError, Scratch !! RpcError, Rpc !! RpcError, Stop Report] r => InterpretersFor GrepErrorStack r Source #
type GrepStack = [ModalWindowMenus () GrepOutputLine !! RpcError, Settings !! SettingError, Scratch !! RpcError, Rpc !! RpcError, AtomicState Env, Log, Resource, Embed IO, Final IO] Source #
grepWith :: Members GrepStack r => Members GrepErrorStack r => Member (Stop Report) r => [Text] -> Path Abs Dir -> Text -> Sem r () Source #