talash-0.3.0: Line oriented fast enough text search
Safe HaskellSafe-Inferred
LanguageHaskell2010

Talash.Brick

Description

A simple brick app to search among the candidates from a vector of text and get the selection. By default the app doesn't do anything except return a single selection but more complicated actions can be performed by using the _hooks which allow abitrary IO actions (due to EventM being a MonadIO) in response to input events. The most convenient function to use the brick app are selected and related functions. runApp provides some more flexibility.

Synopsis

Types

data Searcher a Source #

Constructors

forall n.KnownNat n => Searcher 

Fields

data SearchEvent a Source #

Constructors

forall n.KnownNat n => SearchEvent (SearchEventSized n a) 

data SearchEnv n a b Source #

The constant environment in which the search runs.

Constructors

SearchEnv 

Fields

data EventHooks a Source #

Event hooks are almost direct translations of the events from vty i.e. see Event.

Constructors

EventHooks 

Fields

data AppTheme Source #

Constructors

AppTheme 

Fields

data AppSettingsG (n :: Nat) a b t Source #

Constructors

AppSettings 

Fields

data CaseSensitivity #

Constructors

CaseSensitive 
IgnoreCase 

Instances

Instances details
FromJSON CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

ToJSON CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Generic CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Associated Types

type Rep CaseSensitivity :: Type -> Type #

Show CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

NFData CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Methods

rnf :: CaseSensitivity -> () #

Eq CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

Hashable CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

type Rep CaseSensitivity 
Instance details

Defined in Data.Text.CaseSensitivity

type Rep CaseSensitivity = D1 ('MetaData "CaseSensitivity" "Data.Text.CaseSensitivity" "alfred-margaret-2.0.0.0-5xj5mmrDprP1Dn3hNNnaoN" 'False) (C1 ('MetaCons "CaseSensitive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IgnoreCase" 'PrefixI 'False) (U1 :: Type -> Type))

The Brick App and Helpers

searchApp :: KnownNat n => AppSettings n a -> SearchEnv n a (Widget Bool) -> App (Searcher a) (SearchEvent a) Bool Source #

Tha app itself. selected and the related functions are probably more convenient for embedding into a larger program.

defSettings :: KnownNat n => AppSettings n a Source #

Default settings. Uses blue for various highlights and cyan for borders. All the hooks except keyHook which is handleKeyEvent are trivial.

runApp :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> Chunks n -> IO (Searcher a) Source #

Run app with given settings and return the final Searcher state.

runAppFromHandle :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> Handle -> IO (Searcher a) Source #

Run app with a vector that contains lines read from a handle and return the final Searcher state.

selected :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> Chunks n -> IO (Maybe Text) Source #

Run app and return the text of the selection if there is one else Nothing.

selectedFromHandle :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> Handle -> IO (Maybe Text) Source #

Same as selected but reads the vector from the supplied handle.

selectedFromHandleWith :: KnownNat n => (Text -> Text) -> (Vector Text -> Vector Text) -> AppSettings n a -> SearchFunctions a (Widget Bool) -> Handle -> IO (Maybe Text) Source #

Same as selectedFromHandle but allows for transforming the lines read and the final vector with supplied functions. See also readVectorHandleWith.

selectedFromFileNamesSorted :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> Handle -> IO (Maybe Text) Source #

Another variation on selectedFromHandle. See fileNamesSorted for what happens to read vector.

selectedFromFiles :: KnownNat n => AppSettings n a -> SearchFunctions a (Widget Bool) -> [FindInDirs] -> IO (Maybe Text) Source #

Version of selected for file search using a simple implementation of searching file trees from Talash.Files. Better to use either other libraries like unix-recursive or external programs like fd for more complicated tasks.

runSearch :: AppSettings 64 a -> SearchFunctions a (Widget Bool) -> IO () Source #

A version of selected that puts the selected text on the stdout.

makeChunks :: forall n. KnownNat n => Vector Text -> Chunks n Source #

Default program

run :: IO () Source #

Defualt program for the brick app that reads candidates from stdin and prints the selected text to the stdout. Can be called from the executable with talash tui which uses the orderless style. The search style can be set explicitly by calling talash tui fuzzy or talash tui orderless

run' :: [String] -> IO () Source #

The backend for run

Lenses

Searcher

queryEditor :: forall n a. Lens' (SearcherSized n a) (Editor Text Bool) Source #

allMatches :: forall n a b. Lens' (SearchEnv n a b) (IOVector (Vector n Bit)) Source #

matches :: forall n a. Lens' (SearcherSized n a) (GenericList Bool MatchSetG (ScoredMatchSized n)) Source #

numMatches :: forall n a. Lens' (SearcherSized n a) Int Source #

SearchEvent

matchedTop :: forall n a. Lens' (SearchEventSized n a) (MatchSetSized n) Source #

term :: forall n a. Lens' (SearchEventSized n a) Text Source #

SearchEnv

candidates :: forall n a b. Lens' (SearchEnv n a b) (Chunks n) Source #

eventSource :: forall n a. Lens' (SearcherSized n a) (BChan (SearchEvent a)) Source #

SearchFunctions

makeMatcher :: forall a b. Lens' (SearchFunctions a b) (Text -> Matcher a) Source #

match :: forall a b n. KnownNat n => SimpleGetter (SearchFunctions a b) (MatcherSized n a -> Text -> Maybe (MatchFull n)) Source #

display :: forall a b n. KnownNat n => SimpleGetter (SearchFunctions a b) ((Bool -> Text -> b) -> MatcherSized n a -> Text -> Vector n Int -> [b]) Source #

AppTheme

SearchSettings

theme :: forall n a b t t. Lens (AppSettingsG n a b t) (AppSettingsG n a b t) t t Source #

hooks :: forall n a b t a b. Lens (AppSettingsG n a b t) (AppSettingsG n a b t) (ReaderT (SearchEnv n a b) EventHooks (Searcher a)) (ReaderT (SearchEnv n a b) EventHooks (Searcher a)) Source #

Exposed Internals

handleKeyEvent :: KnownNat n => SearchEnv n a c -> Key -> [Modifier] -> EventM Bool (Searcher b) () Source #

Handling of keypresses. The default bindings are Enter exits the app with the current selection. Esc exits without any selection Up , Down , PageUp and PageDown move through the matches. All others keys are used for editing the query. See handleEditorEvent for details.

searcherWidget :: (KnownNat n, KnownNat m) => SearchEnv n a (Widget Bool) -> Text -> SearcherSized m a -> Widget Bool Source #

The brick widget used to display the editor and the search result.

initialSearcher :: SearchEnv n a c -> BChan (SearchEvent a) -> SearcherSized 0 a Source #

The initial state of the searcher. The editor is empty.

readVectorHandleWith Source #

Arguments

:: (Text -> Text)

The function to transform the candidates.

-> (Vector Text -> Vector Text)

The function to apply to the constructed vector before compacting.

-> Handle

The handle to read from

-> IO (Vector Text)