Safe Haskell | None |
---|---|
Language | Haskell2010 |
TextZipper
is designed to be help manipulate the contents of a text input field. It keeps track of the logical lines of text (i.e., lines separated by user-entered newlines) and the current cursor position. Several functions are defined in this module to navigate and edit the TextZipper from the cursor position.
TextZipper
s can be converted into DisplayLines
, which describe how the contents of the zipper will be displayed when wrapped to fit within a container of a certain width. It also provides some convenience facilities for converting interactions with the rendered DisplayLines back into manipulations of the underlying TextZipper.
Synopsis
- data TextZipper = TextZipper {}
- mapZipper :: (Char -> Char) -> TextZipper -> TextZipper
- left :: TextZipper -> TextZipper
- leftN :: Int -> TextZipper -> TextZipper
- right :: TextZipper -> TextZipper
- rightN :: Int -> TextZipper -> TextZipper
- up :: TextZipper -> TextZipper
- down :: TextZipper -> TextZipper
- pageUp :: Int -> TextZipper -> TextZipper
- pageDown :: Int -> TextZipper -> TextZipper
- home :: TextZipper -> TextZipper
- end :: TextZipper -> TextZipper
- top :: TextZipper -> TextZipper
- insertChar :: Char -> TextZipper -> TextZipper
- insert :: Text -> TextZipper -> TextZipper
- deleteLeft :: TextZipper -> TextZipper
- deleteRight :: TextZipper -> TextZipper
- deleteLeftWord :: TextZipper -> TextZipper
- tab :: Int -> TextZipper -> TextZipper
- value :: TextZipper -> Text
- empty :: TextZipper
- fromText :: Text -> TextZipper
- data Span tag = Span tag Text
- data TextAlignment
- type OffsetMapWithAlignment = Map Int (Int, Int)
- data WrappedLine = WrappedLine {}
- data DisplayLines tag = DisplayLines {}
- splitAtWidth :: Int -> Text -> (Text, Text)
- characterIndexFromWidth :: Int -> Text -> Int
- takeWidth :: Int -> Text -> Text
- dropWidth :: Int -> Text -> Text
- charWidth :: Char -> Int
- spansWidth :: [Span tag] -> Int
- spansLength :: [Span tag] -> Int
- textWidth :: Text -> Int
- widthI :: Stream Char -> Int
- charIndexAt :: Int -> Stream Char -> Int
- wordsWithWhitespace :: Text -> [Text]
- splitWordsAtDisplayWidth :: Int -> [Text] -> [(Text, Bool)]
- alignmentOffset :: TextAlignment -> Int -> Text -> Int
- wrapWithOffsetAndAlignment :: TextAlignment -> Int -> Int -> Text -> [WrappedLine]
- eolSpacesToLogicalLines :: [[WrappedLine]] -> [[(Text, Int)]]
- offsetMapWithAlignmentInternal :: [[WrappedLine]] -> OffsetMapWithAlignment
- offsetMapWithAlignment :: [[(Text, Int)]] -> OffsetMapWithAlignment
- displayLinesWithAlignment :: TextAlignment -> Int -> tag -> tag -> TextZipper -> DisplayLines tag
- goToDisplayLinePosition :: Int -> Int -> DisplayLines tag -> TextZipper -> TextZipper
- displayLines :: Int -> tag -> tag -> TextZipper -> DisplayLines tag
- wrapWithOffset :: Int -> Int -> Text -> [Text]
Documentation
data TextZipper Source #
A zipper of the logical text input contents (the "document"). The lines before the line containing the cursor are stored in reverse order. The cursor is logically between the "before" and "after" text. A "logical" line of input is a line of input up until a user-entered newline character (as compared to a "display" line, which is wrapped to fit within a given viewport width).
Instances
Eq TextZipper Source # | |
Defined in Data.Text.Zipper (==) :: TextZipper -> TextZipper -> Bool # (/=) :: TextZipper -> TextZipper -> Bool # | |
Show TextZipper Source # | |
Defined in Data.Text.Zipper showsPrec :: Int -> TextZipper -> ShowS # show :: TextZipper -> String # showList :: [TextZipper] -> ShowS # | |
IsString TextZipper Source # | |
Defined in Data.Text.Zipper fromString :: String -> TextZipper # |
mapZipper :: (Char -> Char) -> TextZipper -> TextZipper Source #
Map a replacement function over the characters in a TextZipper
left :: TextZipper -> TextZipper Source #
Move the cursor left one character, if possible
leftN :: Int -> TextZipper -> TextZipper Source #
Move the cursor left by the given number of characters, or, if the document isn't long enough, to the beginning of the document
right :: TextZipper -> TextZipper Source #
Move the cursor right one character, if possible
rightN :: Int -> TextZipper -> TextZipper Source #
Move the character right by the given number of characters, or, if the document isn't long enough, to the end of the document
up :: TextZipper -> TextZipper Source #
Move the cursor up one logical line, if possible
down :: TextZipper -> TextZipper Source #
Move the cursor down one logical line, if possible
pageUp :: Int -> TextZipper -> TextZipper Source #
Move the cursor up by the given number of lines
pageDown :: Int -> TextZipper -> TextZipper Source #
Move the cursor down by the given number of lines
home :: TextZipper -> TextZipper Source #
Move the cursor to the beginning of the current logical line
end :: TextZipper -> TextZipper Source #
Move the cursor to the end of the current logical line
top :: TextZipper -> TextZipper Source #
Move the cursor to the top of the document
insertChar :: Char -> TextZipper -> TextZipper Source #
Insert a character at the current cursor position
insert :: Text -> TextZipper -> TextZipper Source #
Insert text at the current cursor position
deleteLeft :: TextZipper -> TextZipper Source #
Delete the character to the left of the cursor
deleteRight :: TextZipper -> TextZipper Source #
Delete the character under/to the right of the cursor
deleteLeftWord :: TextZipper -> TextZipper Source #
Delete a word to the left of the cursor. Deletes all whitespace until it finds a non-whitespace character, and then deletes contiguous non-whitespace characters.
tab :: Int -> TextZipper -> TextZipper Source #
Insert up to n spaces to get to the next logical column that is a multiple of n
value :: TextZipper -> Text Source #
The plain text contents of the zipper
empty :: TextZipper Source #
The empty zipper
fromText :: Text -> TextZipper Source #
Constructs a zipper with the given contents. The cursor is placed after the contents.
A span of text tagged with some metadata that makes up part of a display line.
data TextAlignment Source #
Text alignment type
Instances
Eq TextAlignment Source # | |
Defined in Data.Text.Zipper (==) :: TextAlignment -> TextAlignment -> Bool # (/=) :: TextAlignment -> TextAlignment -> Bool # | |
Show TextAlignment Source # | |
Defined in Data.Text.Zipper showsPrec :: Int -> TextAlignment -> ShowS # show :: TextAlignment -> String # showList :: [TextAlignment] -> ShowS # |
type OffsetMapWithAlignment = Map Int (Int, Int) Source #
A map from the index (row) of display line to (fst,snd) fst: leading empty spaces from left (may be negative) to adjust for alignment snd: the text offset from the beginning of the document to the first character of the display line
data WrappedLine Source #
Helper type representing a single visual line that may be part of a wrapped logical line
WrappedLine | |
|
Instances
Eq WrappedLine Source # | |
Defined in Data.Text.Zipper (==) :: WrappedLine -> WrappedLine -> Bool # (/=) :: WrappedLine -> WrappedLine -> Bool # | |
Show WrappedLine Source # | |
Defined in Data.Text.Zipper showsPrec :: Int -> WrappedLine -> ShowS # show :: WrappedLine -> String # showList :: [WrappedLine] -> ShowS # |
data DisplayLines tag Source #
Information about the document as it is displayed (i.e., post-wrapping)
DisplayLines | |
|
Instances
Eq tag => Eq (DisplayLines tag) Source # | |
Defined in Data.Text.Zipper (==) :: DisplayLines tag -> DisplayLines tag -> Bool # (/=) :: DisplayLines tag -> DisplayLines tag -> Bool # | |
Show tag => Show (DisplayLines tag) Source # | |
Defined in Data.Text.Zipper showsPrec :: Int -> DisplayLines tag -> ShowS # show :: DisplayLines tag -> String # showList :: [DisplayLines tag] -> ShowS # |
characterIndexFromWidth :: Int -> Text -> Int Source #
Convert a physical width index to a character index. For example, the physical index 3 of the string "ᄀabc" corresponds to the character index 2, because the first character has a width of 2.
takeWidth :: Int -> Text -> Text Source #
Takes the given number of columns of characters. For example
takeWidth 3 "ᄀabc" == "ᄀa"
because the first character has a width of 2 (see charWidth
for more on that).
This function will not take a character if its width exceeds the width it seeks to take.
dropWidth :: Int -> Text -> Text Source #
Drops the given number of columns of characters. For example
dropWidth 2 "ᄀabc" == "abc"
because the first character has a width of 2 (see charWidth
for more on that).
This function will not drop a character if its width exceeds the width it seeks to drop.
charWidth :: Char -> Int Source #
Get the display width of a Char
. "Full width" and "wide" characters
take two columns and everything else takes a single column. See
https://www.unicode.org/reports/tr11/ for more information
This is implemented using wcwidth from Vty such that it matches what will
be displayed on the terminal. Note that this method can change depending
on how vty is configed. Please see vty documentation for details.
spansWidth :: [Span tag] -> Int Source #
Get the width of the text in a set of Span
s, taking into account unicode character widths
spansLength :: [Span tag] -> Int Source #
Get the length (number of characters) of the text in a set of Span
s
textWidth :: Text -> Int Source #
Compute the width of some Text
, taking into account fullwidth
unicode forms.
widthI :: Stream Char -> Int Source #
Compute the width of a stream of characters, taking into account fullwidth unicode forms.
charIndexAt :: Int -> Stream Char -> Int Source #
Compute the logical index position of a stream of characters from a visual position taking into account fullwidth unicode forms.
wordsWithWhitespace :: Text -> [Text] Source #
Same as T.words except whitespace characters are included at end (i.e. ["line1 ", ...])
Char
s representing white space.
splitWordsAtDisplayWidth :: Int -> [Text] -> [(Text, Bool)] Source #
Split words into logical lines, True
in the tuple indicates line ends with a whitespace character that got deleted
alignmentOffset :: TextAlignment -> Int -> Text -> Int Source #
Calculate the offset that will result in rendered text being aligned left, right, or center
wrapWithOffsetAndAlignment Source #
:: TextAlignment | |
-> Int | Maximum width |
-> Int | Offset for first line |
-> Text | Text to be wrapped |
-> [WrappedLine] |
Wraps a logical line of text to fit within the given width. The first wrapped line is offset by the number of columns provided. Subsequent wrapped lines are not.
eolSpacesToLogicalLines :: [[WrappedLine]] -> [[(Text, Int)]] Source #
converts deleted eol spaces into logical lines
offsetMapWithAlignment Source #
:: [[(Text, Int)]] | The outer list represents logical lines, inner list represents wrapped lines |
-> OffsetMapWithAlignment |
displayLinesWithAlignment Source #
:: TextAlignment | |
-> Int | Width, used for wrapping |
-> tag | Metadata for normal characters |
-> tag | Metadata for the cursor |
-> TextZipper | The text input contents and cursor state |
-> DisplayLines tag |
Given a width and a TextZipper
, produce a list of display lines
(i.e., lines of wrapped text) with special attributes applied to
certain segments (e.g., the cursor). Additionally, produce the current
y-coordinate of the cursor and a mapping from display line number to text
offset
goToDisplayLinePosition :: Int -> Int -> DisplayLines tag -> TextZipper -> TextZipper Source #
Move the cursor of the given TextZipper
to the logical position indicated
by the given display line coordinates, using the provided DisplayLinesWithAlignment
information. If the x coordinate is beyond the end of a line, the cursor is
moved to the end of the line.
:: Int | Width, used for wrapping |
-> tag | Metadata for normal characters |
-> tag | Metadata for the cursor |
-> TextZipper | The text input contents and cursor state |
-> DisplayLines tag |
Given a width and a TextZipper
, produce a list of display lines
(i.e., lines of wrapped text) with special attributes applied to
certain segments (e.g., the cursor). Additionally, produce the current
y-coordinate of the cursor and a mapping from display line number to text
offset