Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Matterhorn.Types.EditState
Synopsis
- data EditMode
- data AttachmentData = AttachmentData {}
- data AutocompletionType
- data CompletionSource
- data SpecialMention
- specialMentionName :: SpecialMention -> Text
- isSpecialMention :: Text -> Bool
- data EditState n = EditState {
- _esEditor :: Editor Text n
- _esEditMode :: EditMode
- _esEphemeral :: EphemeralEditState
- _esMisspellings :: Set Text
- _esAutocomplete :: Maybe (AutocompleteState n)
- _esResetEditMode :: EditMode
- _esAutocompletePending :: Maybe Text
- _esAttachmentList :: List n AttachmentData
- _esFileBrowser :: Maybe (FileBrowser n)
- _esJustCompleted :: Bool
- _esShowReplyPrompt :: Bool
- _esSpellCheckTimerReset :: Maybe (IO ())
- _esChannelId :: ChannelId
- _esTeamId :: Maybe TeamId
- _esTarget :: EditorTarget
- newEditState :: n -> n -> EditorTarget -> Maybe TeamId -> ChannelId -> EditMode -> Bool -> Maybe (IO ()) -> EditState n
- unsafeEsFileBrowser :: Lens' (EditState n) (FileBrowser n)
- esAttachmentList :: forall n. Lens' (EditState n) (List n AttachmentData)
- esFileBrowser :: forall n. Lens' (EditState n) (Maybe (FileBrowser n))
- esMisspellings :: forall n. Lens' (EditState n) (Set Text)
- esEditMode :: forall n. Lens' (EditState n) EditMode
- esEphemeral :: forall n. Lens' (EditState n) EphemeralEditState
- esEditor :: forall n. Lens' (EditState n) (Editor Text n)
- esAutocomplete :: forall n. Lens' (EditState n) (Maybe (AutocompleteState n))
- esAutocompletePending :: forall n. Lens' (EditState n) (Maybe Text)
- esResetEditMode :: forall n. Lens' (EditState n) EditMode
- esJustCompleted :: forall n. Lens' (EditState n) Bool
- esShowReplyPrompt :: forall n. Lens' (EditState n) Bool
- esSpellCheckTimerReset :: forall n. Lens' (EditState n) (Maybe (IO ()))
- esTeamId :: forall n. Lens' (EditState n) (Maybe TeamId)
- esChannelId :: forall n. Lens' (EditState n) ChannelId
- esTarget :: forall n. Lens' (EditState n) EditorTarget
- data EditorTarget
- data EphemeralEditState = EphemeralEditState {}
- defaultEphemeralEditState :: EphemeralEditState
- eesMultiline :: Lens' EphemeralEditState Bool
- eesInputHistoryPosition :: Lens' EphemeralEditState (Maybe Int)
- eesLastInput :: Lens' EphemeralEditState (Text, EditMode)
- eesTypingUsers :: Lens' EphemeralEditState TypingUsers
- addEphemeralStateTypingUser :: UserId -> UTCTime -> EphemeralEditState -> EphemeralEditState
- data AutocompleteState n = AutocompleteState {}
- acPreviousSearchString :: forall n. Lens' (AutocompleteState n) Text
- acCompletionList :: forall n n. Lens (AutocompleteState n) (AutocompleteState n) (List n AutocompleteAlternative) (List n AutocompleteAlternative)
- acCachedResponses :: forall n. Lens' (AutocompleteState n) (HashMap Text [AutocompleteAlternative])
- acType :: forall n. Lens' (AutocompleteState n) AutocompletionType
- data AutocompleteAlternative
- autocompleteAlternativeReplacement :: AutocompleteAlternative -> Text
- autocompleteAlternativeText :: AutocompleteAlternative -> Text
Documentation
The input state associated with the message editor.
Constructors
NewPost | The input is for a new post. |
Editing Post MessageType | The input is ultimately to replace the body of an existing post of the specified type. |
Replying Message Post | The input is to be used as a new post in reply to the specified post. |
data AttachmentData Source #
An attachment.
Constructors
AttachmentData | |
Fields |
Instances
Show AttachmentData Source # | |
Defined in Matterhorn.Types.EditState Methods showsPrec :: Int -> AttachmentData -> ShowS # show :: AttachmentData -> String # showList :: [AttachmentData] -> ShowS # | |
Eq AttachmentData Source # | |
Defined in Matterhorn.Types.EditState Methods (==) :: AttachmentData -> AttachmentData -> Bool # (/=) :: AttachmentData -> AttachmentData -> Bool # |
data AutocompletionType Source #
The type of data that the autocompletion logic supports. We use this to track the kind of completion underway in case the type of completion needs to change.
Constructors
ACUsers | |
ACChannels | |
ACCodeBlockLanguage | |
ACEmoji | |
ACCommands |
Instances
Show AutocompletionType Source # | |
Defined in Matterhorn.Types.EditState Methods showsPrec :: Int -> AutocompletionType -> ShowS # show :: AutocompletionType -> String # showList :: [AutocompletionType] -> ShowS # | |
Eq AutocompletionType Source # | |
Defined in Matterhorn.Types.EditState Methods (==) :: AutocompletionType -> AutocompletionType -> Bool # (/=) :: AutocompletionType -> AutocompletionType -> Bool # |
data CompletionSource Source #
The source of an autocompletion alternative.
Instances
Show CompletionSource Source # | |
Defined in Matterhorn.Types.EditState Methods showsPrec :: Int -> CompletionSource -> ShowS # show :: CompletionSource -> String # showList :: [CompletionSource] -> ShowS # | |
Eq CompletionSource Source # | |
Defined in Matterhorn.Types.EditState Methods (==) :: CompletionSource -> CompletionSource -> Bool # (/=) :: CompletionSource -> CompletionSource -> Bool # |
data SpecialMention Source #
A "special" mention that does not map to a specific user, but is an alias that the server uses to notify users.
Constructors
MentionAll | @all: notify everyone in the channel. |
MentionChannel | @channel: notify everyone in the channel. |
isSpecialMention :: Text -> Bool Source #
The EditState
value contains the editor widget itself as well as
history and metadata we need for editing-related operations.
Constructors
EditState | |
Fields
|
newEditState :: n -> n -> EditorTarget -> Maybe TeamId -> ChannelId -> EditMode -> Bool -> Maybe (IO ()) -> EditState n Source #
unsafeEsFileBrowser :: Lens' (EditState n) (FileBrowser n) Source #
esAttachmentList :: forall n. Lens' (EditState n) (List n AttachmentData) Source #
esFileBrowser :: forall n. Lens' (EditState n) (Maybe (FileBrowser n)) Source #
esEphemeral :: forall n. Lens' (EditState n) EphemeralEditState Source #
esAutocomplete :: forall n. Lens' (EditState n) (Maybe (AutocompleteState n)) Source #
data EditorTarget Source #
Constructors
EditorForThread TeamId | |
EditorForChannel ChannelId |
Instances
Show EditorTarget Source # | |
Defined in Matterhorn.Types.EditState Methods showsPrec :: Int -> EditorTarget -> ShowS # show :: EditorTarget -> String # showList :: [EditorTarget] -> ShowS # | |
Eq EditorTarget Source # | |
Defined in Matterhorn.Types.EditState |
data EphemeralEditState Source #
Constructors
EphemeralEditState | |
Fields
|
addEphemeralStateTypingUser :: UserId -> UTCTime -> EphemeralEditState -> EphemeralEditState Source #
Add user to the list of users in this state who are currently typing.
data AutocompleteState n Source #
Constructors
AutocompleteState | |
Fields
|
acPreviousSearchString :: forall n. Lens' (AutocompleteState n) Text Source #
acCompletionList :: forall n n. Lens (AutocompleteState n) (AutocompleteState n) (List n AutocompleteAlternative) (List n AutocompleteAlternative) Source #
acCachedResponses :: forall n. Lens' (AutocompleteState n) (HashMap Text [AutocompleteAlternative]) Source #
acType :: forall n. Lens' (AutocompleteState n) AutocompletionType Source #
data AutocompleteAlternative Source #
Constructors
UserCompletion User Bool Text | User, plus whether the user is in the channel that triggered the autocomplete and any prefix (e.g. the preceeding portion of a user list) that should be retained when subtituting this autocompletion. |
SpecialMention SpecialMention | A special mention. |
ChannelCompletion Bool Channel | Channel, plus whether the user is a member of the channel |
SyntaxCompletion Text | Name of a skylighting syntax definition |
CommandCompletion CompletionSource Text Text Text | Source, name of a slash command, argspec, and description |
EmojiCompletion Text | The text of an emoji completion |
autocompleteAlternativeReplacement :: AutocompleteAlternative -> Text Source #
Returns the actual text that should replace the current autocompletion word.
autocompleteAlternativeText :: AutocompleteAlternative -> Text Source #
This returns the potential auto-completion final portion that might be used to match and therefore complete the current entry. Note that this is just the final completion portion; it differs from autocompleteAlternativeReplacement in that it does not include any sigils or prefixes; this value is often used to filter text for the results that will match the auto-completion.