{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
module Matterhorn.Events.ManageAttachments
  ( onEventAttachmentList
  , onEventBrowseFile
  , attachmentListKeybindings
  , attachmentBrowseKeyHandlers
  , attachmentBrowseKeybindings
  , attachmentListKeyHandlers
  )
where

import           Prelude ()
import           Matterhorn.Prelude

import qualified Brick.Widgets.FileBrowser as FB
import qualified Brick.Widgets.List as L
import qualified Data.Text as T
import qualified Data.Vector as Vector
import qualified Graphics.Vty as V
import           Lens.Micro.Platform ( (?=), (%=), to, Lens', (.=) )

import           Matterhorn.Types
import           Matterhorn.Types.KeyEvents
import           Matterhorn.Events.Keybindings
import           Matterhorn.State.Attachments
import           Matterhorn.State.Common


onEventAttachmentList :: Lens' ChatState (MessageInterface Name i)
                      -> V.Event
                      -> MH Bool
onEventAttachmentList :: Lens' ChatState (MessageInterface Name i) -> Event -> MH Bool
onEventAttachmentList Lens' ChatState (MessageInterface Name i)
which =
    [Event -> MH Bool] -> Event -> MH Bool
handleEventWith [ (KeyConfig -> KeyHandlerMap) -> Event -> MH Bool
handleKeyboardEvent (Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
forall i.
Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
attachmentListKeybindings Lens' ChatState (MessageInterface Name i)
which)
                    , \Event
e -> Lens' ChatState (GenericList Name Vector AttachmentData)
-> (Event
    -> GenericList Name Vector AttachmentData
    -> EventM Name (GenericList Name Vector AttachmentData))
-> Event
-> MH ()
forall b e.
Lens' ChatState b -> (e -> b -> EventM Name b) -> e -> MH ()
mhHandleEventLensed ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> EditState Name -> f (EditState Name))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> f (GenericList Name Vector AttachmentData))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList) Event
-> GenericList Name Vector AttachmentData
-> EventM Name (GenericList Name Vector AttachmentData)
forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
Event -> GenericList n t e -> EventM n (GenericList n t e)
L.handleListEvent Event
e MH () -> MH Bool -> MH Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> MH Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
                    ]

attachmentListKeybindings :: Lens' ChatState (MessageInterface Name i)
                          -> KeyConfig
                          -> KeyHandlerMap
attachmentListKeybindings :: Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
attachmentListKeybindings Lens' ChatState (MessageInterface Name i)
which = [KeyEventHandler] -> KeyConfig -> KeyHandlerMap
mkKeybindings (Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
forall i.
Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
attachmentListKeyHandlers Lens' ChatState (MessageInterface Name i)
which)

attachmentListKeyHandlers :: Lens' ChatState (MessageInterface Name i)
                          -> [KeyEventHandler]
attachmentListKeyHandlers :: Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
attachmentListKeyHandlers Lens' ChatState (MessageInterface Name i)
which =
    [ KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
CancelEvent Text
"Close attachment list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          (MessageInterface Name i -> Identity (MessageInterface Name i))
-> ChatState -> Identity ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> Identity (MessageInterface Name i))
 -> ChatState -> Identity ChatState)
-> ((MessageInterfaceMode -> Identity MessageInterfaceMode)
    -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> (MessageInterfaceMode -> Identity MessageInterfaceMode)
-> ChatState
-> Identity ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(MessageInterfaceMode -> Identity MessageInterfaceMode)
-> MessageInterface Name i -> Identity (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) MessageInterfaceMode
miMode ((MessageInterfaceMode -> Identity MessageInterfaceMode)
 -> ChatState -> Identity ChatState)
-> MessageInterfaceMode -> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= MessageInterfaceMode
Compose
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
SelectUpEvent Text
"Move cursor up" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          Lens' ChatState (GenericList Name Vector AttachmentData)
-> (Event
    -> GenericList Name Vector AttachmentData
    -> EventM Name (GenericList Name Vector AttachmentData))
-> Event
-> MH ()
forall b e.
Lens' ChatState b -> (e -> b -> EventM Name b) -> e -> MH ()
mhHandleEventLensed ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> EditState Name -> f (EditState Name))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> f (GenericList Name Vector AttachmentData))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList) Event
-> GenericList Name Vector AttachmentData
-> EventM Name (GenericList Name Vector AttachmentData)
forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
Event -> GenericList n t e -> EventM n (GenericList n t e)
L.handleListEvent (Key -> [Modifier] -> Event
V.EvKey Key
V.KUp [])
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
SelectDownEvent Text
"Move cursor down" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          Lens' ChatState (GenericList Name Vector AttachmentData)
-> (Event
    -> GenericList Name Vector AttachmentData
    -> EventM Name (GenericList Name Vector AttachmentData))
-> Event
-> MH ()
forall b e.
Lens' ChatState b -> (e -> b -> EventM Name b) -> e -> MH ()
mhHandleEventLensed ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((GenericList Name Vector AttachmentData
     -> f (GenericList Name Vector AttachmentData))
    -> EditState Name -> f (EditState Name))
-> (GenericList Name Vector AttachmentData
    -> f (GenericList Name Vector AttachmentData))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> f (GenericList Name Vector AttachmentData))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList) Event
-> GenericList Name Vector AttachmentData
-> EventM Name (GenericList Name Vector AttachmentData)
forall (t :: * -> *) n e.
(Foldable t, Splittable t, Ord n) =>
Event -> GenericList n t e -> EventM n (GenericList n t e)
L.handleListEvent (Key -> [Modifier] -> Event
V.EvKey Key
V.KDown [])
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
AttachmentListAddEvent Text
"Add a new attachment to the attachment list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentFileBrowser Lens' ChatState (MessageInterface Name i)
which
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
AttachmentOpenEvent Text
"Open the selected attachment using the URL open command" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedAttachment Lens' ChatState (MessageInterface Name i)
which
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
AttachmentListDeleteEvent Text
"Delete the selected attachment from the attachment list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
          Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
deleteSelectedAttachment Lens' ChatState (MessageInterface Name i)
which
    ]

attachmentBrowseKeybindings :: Lens' ChatState (MessageInterface Name i)
                            -> KeyConfig
                            -> KeyHandlerMap
attachmentBrowseKeybindings :: Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
attachmentBrowseKeybindings Lens' ChatState (MessageInterface Name i)
which =
    [KeyEventHandler] -> KeyConfig -> KeyHandlerMap
mkKeybindings (Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
forall i.
Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
attachmentBrowseKeyHandlers Lens' ChatState (MessageInterface Name i)
which)

attachmentBrowseKeyHandlers :: Lens' ChatState (MessageInterface Name i)
                            -> [KeyEventHandler]
attachmentBrowseKeyHandlers :: Lens' ChatState (MessageInterface Name i) -> [KeyEventHandler]
attachmentBrowseKeyHandlers Lens' ChatState (MessageInterface Name i)
which =
    [ KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
CancelEvent Text
"Cancel attachment file browse" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
cancelAttachmentBrowse Lens' ChatState (MessageInterface Name i)
which
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
AttachmentOpenEvent Text
"Open the selected file using the URL open command" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedBrowserEntry Lens' ChatState (MessageInterface Name i)
which
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserBeginSearchEvent Text
"Begin search for name in list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserBeginSearch
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserSelectEnterEvent Text
"Select file or enter directory" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$ do
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserSelectEnter
      Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which (Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
tryAddAttachment Lens' ChatState (MessageInterface Name i)
which ([FileInfo] -> MH ())
-> (FileBrowser Name -> [FileInfo]) -> FileBrowser Name -> MH ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileBrowser Name -> [FileInfo]
forall n. FileBrowser n -> [FileInfo]
FB.fileBrowserSelection)
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserSelectCurrentEvent Text
"Select file" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserSelectCurrent
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListPageUpEvent Text
"Move cursor one page up" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListPageUp
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListPageDownEvent Text
"Move cursor one page down" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListPageDown
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListHalfPageUpEvent Text
"Move cursor one-half page up" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListHalfPageUp
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListHalfPageDownEvent Text
"Move cursor one-half page down" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListHalfPageDown
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListTopEvent Text
"Move cursor to top of list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListTop
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListBottomEvent Text
"Move cursor to bottom of list" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListBottom
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListNextEvent Text
"Move cursor down" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListNext
    , KeyEvent -> Text -> MH () -> KeyEventHandler
mkKb KeyEvent
FileBrowserListPrevEvent Text
"Move cursor up" (MH () -> KeyEventHandler) -> MH () -> KeyEventHandler
forall a b. (a -> b) -> a -> b
$
      Lens' ChatState (FileBrowser Name)
-> (FileBrowser Name -> EventM Name (FileBrowser Name)) -> MH ()
forall b. Lens' ChatState b -> (b -> EventM Name b) -> MH ()
mhHandleEventLensed' ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (FileBrowser Name -> f (FileBrowser Name))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((FileBrowser Name -> f (FileBrowser Name))
    -> EditState Name -> f (EditState Name))
-> (FileBrowser Name -> f (FileBrowser Name))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(FileBrowser Name -> f (FileBrowser Name))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (FileBrowser n)
unsafeEsFileBrowser)
        FileBrowser Name -> EventM Name (FileBrowser Name)
forall n. Ord n => FileBrowser n -> EventM n (FileBrowser n)
FB.actionFileBrowserListPrev
    ]

withFileBrowser :: Lens' ChatState (MessageInterface Name i)
                -> ((FB.FileBrowser Name) -> MH ())
                -> MH ()
withFileBrowser :: Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which FileBrowser Name -> MH ()
f = do
    Getting
  (Maybe (FileBrowser Name)) ChatState (Maybe (FileBrowser Name))
-> MH (Maybe (FileBrowser Name))
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Maybe (FileBrowser Name)) (MessageInterface Name i))
-> ChatState -> Const (Maybe (FileBrowser Name)) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Maybe (FileBrowser Name)) (MessageInterface Name i))
 -> ChatState -> Const (Maybe (FileBrowser Name)) ChatState)
-> ((Maybe (FileBrowser Name)
     -> Const (Maybe (FileBrowser Name)) (Maybe (FileBrowser Name)))
    -> MessageInterface Name i
    -> Const (Maybe (FileBrowser Name)) (MessageInterface Name i))
-> Getting
     (Maybe (FileBrowser Name)) ChatState (Maybe (FileBrowser Name))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name
 -> Const (Maybe (FileBrowser Name)) (EditState Name))
-> MessageInterface Name i
-> Const (Maybe (FileBrowser Name)) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name
  -> Const (Maybe (FileBrowser Name)) (EditState Name))
 -> MessageInterface Name i
 -> Const (Maybe (FileBrowser Name)) (MessageInterface Name i))
-> ((Maybe (FileBrowser Name)
     -> Const (Maybe (FileBrowser Name)) (Maybe (FileBrowser Name)))
    -> EditState Name
    -> Const (Maybe (FileBrowser Name)) (EditState Name))
-> (Maybe (FileBrowser Name)
    -> Const (Maybe (FileBrowser Name)) (Maybe (FileBrowser Name)))
-> MessageInterface Name i
-> Const (Maybe (FileBrowser Name)) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe (FileBrowser Name)
 -> Const (Maybe (FileBrowser Name)) (Maybe (FileBrowser Name)))
-> EditState Name
-> Const (Maybe (FileBrowser Name)) (EditState Name)
forall n. Lens' (EditState n) (Maybe (FileBrowser n))
esFileBrowser) MH (Maybe (FileBrowser Name))
-> (Maybe (FileBrowser Name) -> MH ()) -> MH ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
        Maybe (FileBrowser Name)
Nothing -> do
            -- The widget has not been created yet.  This should
            -- normally not occur, because the ManageAttachments
            -- events should not fire when there is no FileBrowser
            -- Widget active to cause Brick to generate these events.
            -- This could therefore be implemented as an `error "BUG:
            -- ..."` handler, but the more benign approach is to
            -- simply create an available FileBrowser at this stage.
            ChannelId
cId <- Getting ChannelId ChatState ChannelId -> MH ChannelId
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const ChannelId (MessageInterface Name i))
-> ChatState -> Const ChannelId ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const ChannelId (MessageInterface Name i))
 -> ChatState -> Const ChannelId ChatState)
-> ((ChannelId -> Const ChannelId ChannelId)
    -> MessageInterface Name i
    -> Const ChannelId (MessageInterface Name i))
-> Getting ChannelId ChatState ChannelId
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Const ChannelId (EditState Name))
-> MessageInterface Name i
-> Const ChannelId (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Const ChannelId (EditState Name))
 -> MessageInterface Name i
 -> Const ChannelId (MessageInterface Name i))
-> ((ChannelId -> Const ChannelId ChannelId)
    -> EditState Name -> Const ChannelId (EditState Name))
-> (ChannelId -> Const ChannelId ChannelId)
-> MessageInterface Name i
-> Const ChannelId (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(ChannelId -> Const ChannelId ChannelId)
-> EditState Name -> Const ChannelId (EditState Name)
forall n. Lens' (EditState n) ChannelId
esChannelId)
            FileBrowser Name
new_b <- IO (FileBrowser Name) -> MH (FileBrowser Name)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (FileBrowser Name) -> MH (FileBrowser Name))
-> IO (FileBrowser Name) -> MH (FileBrowser Name)
forall a b. (a -> b) -> a -> b
$ (FileInfo -> Bool)
-> Name -> Maybe FilePath -> IO (FileBrowser Name)
forall n.
(FileInfo -> Bool) -> n -> Maybe FilePath -> IO (FileBrowser n)
FB.newFileBrowser FileInfo -> Bool
FB.selectNonDirectories (ChannelId -> Name
AttachmentFileBrowser ChannelId
cId) Maybe FilePath
forall a. Maybe a
Nothing
            (MessageInterface Name i -> Identity (MessageInterface Name i))
-> ChatState -> Identity ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> Identity (MessageInterface Name i))
 -> ChatState -> Identity ChatState)
-> ((Maybe (FileBrowser Name)
     -> Identity (Maybe (FileBrowser Name)))
    -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> (Maybe (FileBrowser Name)
    -> Identity (Maybe (FileBrowser Name)))
-> ChatState
-> Identity ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Identity (EditState Name))
-> MessageInterface Name i -> Identity (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Identity (EditState Name))
 -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> ((Maybe (FileBrowser Name)
     -> Identity (Maybe (FileBrowser Name)))
    -> EditState Name -> Identity (EditState Name))
-> (Maybe (FileBrowser Name)
    -> Identity (Maybe (FileBrowser Name)))
-> MessageInterface Name i
-> Identity (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe (FileBrowser Name) -> Identity (Maybe (FileBrowser Name)))
-> EditState Name -> Identity (EditState Name)
forall n. Lens' (EditState n) (Maybe (FileBrowser n))
esFileBrowser ((Maybe (FileBrowser Name) -> Identity (Maybe (FileBrowser Name)))
 -> ChatState -> Identity ChatState)
-> FileBrowser Name -> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a (Maybe b) -> b -> m ()
?= FileBrowser Name
new_b
            FileBrowser Name -> MH ()
f FileBrowser Name
new_b
        Just FileBrowser Name
b -> FileBrowser Name -> MH ()
f FileBrowser Name
b

openSelectedAttachment :: Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedAttachment :: Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedAttachment Lens' ChatState (MessageInterface Name i)
which = do
    Maybe (Int, AttachmentData)
cur <- Getting
  (Maybe (Int, AttachmentData))
  ChatState
  (Maybe (Int, AttachmentData))
-> MH (Maybe (Int, AttachmentData))
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> ChatState -> Const (Maybe (Int, AttachmentData)) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
 -> ChatState -> Const (Maybe (Int, AttachmentData)) ChatState)
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> MessageInterface Name i
    -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> Getting
     (Maybe (Int, AttachmentData))
     ChatState
     (Maybe (Int, AttachmentData))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name
 -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> MessageInterface Name i
-> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name
  -> Const (Maybe (Int, AttachmentData)) (EditState Name))
 -> MessageInterface Name i
 -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> EditState Name
    -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> (Maybe (Int, AttachmentData)
    -> Const
         (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
-> MessageInterface Name i
-> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Const
      (Maybe (Int, AttachmentData))
      (GenericList Name Vector AttachmentData))
-> EditState Name
-> Const (Maybe (Int, AttachmentData)) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((GenericList Name Vector AttachmentData
  -> Const
       (Maybe (Int, AttachmentData))
       (GenericList Name Vector AttachmentData))
 -> EditState Name
 -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> GenericList Name Vector AttachmentData
    -> Const
         (Maybe (Int, AttachmentData))
         (GenericList Name Vector AttachmentData))
-> (Maybe (Int, AttachmentData)
    -> Const
         (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
-> EditState Name
-> Const (Maybe (Int, AttachmentData)) (EditState Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Maybe (Int, AttachmentData))
-> SimpleGetter
     (GenericList Name Vector AttachmentData)
     (Maybe (Int, AttachmentData))
forall s a. (s -> a) -> SimpleGetter s a
to GenericList Name Vector AttachmentData
-> Maybe (Int, AttachmentData)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement)
    case Maybe (Int, AttachmentData)
cur of
        Maybe (Int, AttachmentData)
Nothing -> () -> MH ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just (Int
_, AttachmentData
entry) -> MH () -> MH ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MH () -> MH ()) -> MH () -> MH ()
forall a b. (a -> b) -> a -> b
$ FilePath -> MH ()
openFilePath (FileInfo -> FilePath
FB.fileInfoFilePath (FileInfo -> FilePath) -> FileInfo -> FilePath
forall a b. (a -> b) -> a -> b
$
                                                AttachmentData -> FileInfo
attachmentDataFileInfo AttachmentData
entry)

openSelectedBrowserEntry :: Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedBrowserEntry :: Lens' ChatState (MessageInterface Name i) -> MH ()
openSelectedBrowserEntry Lens' ChatState (MessageInterface Name i)
which = Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which ((FileBrowser Name -> MH ()) -> MH ())
-> (FileBrowser Name -> MH ()) -> MH ()
forall a b. (a -> b) -> a -> b
$ \FileBrowser Name
b ->
    case FileBrowser Name -> Maybe FileInfo
forall n. FileBrowser n -> Maybe FileInfo
FB.fileBrowserCursor FileBrowser Name
b of
        Maybe FileInfo
Nothing -> () -> MH ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just FileInfo
entry -> MH () -> MH ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MH () -> MH ()) -> MH () -> MH ()
forall a b. (a -> b) -> a -> b
$ FilePath -> MH ()
openFilePath (FileInfo -> FilePath
FB.fileInfoFilePath FileInfo
entry)

onEventBrowseFile :: Lens' ChatState (MessageInterface Name i) -> V.Event -> MH Bool
onEventBrowseFile :: Lens' ChatState (MessageInterface Name i) -> Event -> MH Bool
onEventBrowseFile Lens' ChatState (MessageInterface Name i)
which Event
e = do
    Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which ((FileBrowser Name -> MH ()) -> MH ())
-> (FileBrowser Name -> MH ()) -> MH ()
forall a b. (a -> b) -> a -> b
$ \FileBrowser Name
b -> do
        case FileBrowser Name -> Bool
forall n. FileBrowser n -> Bool
FB.fileBrowserIsSearching FileBrowser Name
b of
            Bool
False ->
                MH Bool -> MH ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (MH Bool -> MH ()) -> MH Bool -> MH ()
forall a b. (a -> b) -> a -> b
$ [Event -> MH Bool] -> Event -> MH Bool
handleEventWith [ (KeyConfig -> KeyHandlerMap) -> Event -> MH Bool
handleKeyboardEvent (Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
forall i.
Lens' ChatState (MessageInterface Name i)
-> KeyConfig -> KeyHandlerMap
attachmentBrowseKeybindings Lens' ChatState (MessageInterface Name i)
which)
                                       , \Event
_ -> Lens' ChatState (MessageInterface Name i) -> Event -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i) -> Event -> MH ()
handleFileBrowserEvent Lens' ChatState (MessageInterface Name i)
which Event
e MH () -> MH Bool -> MH Bool
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Bool -> MH Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
                                       ] Event
e
            Bool
True ->
                Lens' ChatState (MessageInterface Name i) -> Event -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i) -> Event -> MH ()
handleFileBrowserEvent Lens' ChatState (MessageInterface Name i)
which Event
e

    -- n.b. the FileBrowser may have been updated above, so re-acquire it
    Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which ((FileBrowser Name -> MH ()) -> MH ())
-> (FileBrowser Name -> MH ()) -> MH ()
forall a b. (a -> b) -> a -> b
$ \FileBrowser Name
b -> do
        case FileBrowser Name -> Maybe IOException
forall n. FileBrowser n -> Maybe IOException
FB.fileBrowserException FileBrowser Name
b of
            Maybe IOException
Nothing -> () -> MH ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
            Just IOException
ex -> do
                LogCategory -> Text -> MH ()
mhLog LogCategory
LogError (Text -> MH ()) -> Text -> MH ()
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ FilePath
"FileBrowser exception: " FilePath -> FilePath -> FilePath
forall a. Semigroup a => a -> a -> a
<> IOException -> FilePath
forall a. Show a => a -> FilePath
show IOException
ex

    Bool -> MH Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True

cancelAttachmentBrowse :: Lens' ChatState (MessageInterface Name i) -> MH ()
cancelAttachmentBrowse :: Lens' ChatState (MessageInterface Name i) -> MH ()
cancelAttachmentBrowse Lens' ChatState (MessageInterface Name i)
which = do
    Vector AttachmentData
es <- Getting (Vector AttachmentData) ChatState (Vector AttachmentData)
-> MH (Vector AttachmentData)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Vector AttachmentData) (MessageInterface Name i))
-> ChatState -> Const (Vector AttachmentData) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Vector AttachmentData) (MessageInterface Name i))
 -> ChatState -> Const (Vector AttachmentData) ChatState)
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> MessageInterface Name i
    -> Const (Vector AttachmentData) (MessageInterface Name i))
-> Getting
     (Vector AttachmentData) ChatState (Vector AttachmentData)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Const (Vector AttachmentData) (EditState Name))
-> MessageInterface Name i
-> Const (Vector AttachmentData) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Const (Vector AttachmentData) (EditState Name))
 -> MessageInterface Name i
 -> Const (Vector AttachmentData) (MessageInterface Name i))
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> EditState Name
    -> Const (Vector AttachmentData) (EditState Name))
-> (Vector AttachmentData
    -> Const (Vector AttachmentData) (Vector AttachmentData))
-> MessageInterface Name i
-> Const (Vector AttachmentData) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Const
      (Vector AttachmentData) (GenericList Name Vector AttachmentData))
-> EditState Name -> Const (Vector AttachmentData) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((GenericList Name Vector AttachmentData
  -> Const
       (Vector AttachmentData) (GenericList Name Vector AttachmentData))
 -> EditState Name
 -> Const (Vector AttachmentData) (EditState Name))
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> GenericList Name Vector AttachmentData
    -> Const
         (Vector AttachmentData) (GenericList Name Vector AttachmentData))
-> (Vector AttachmentData
    -> Const (Vector AttachmentData) (Vector AttachmentData))
-> EditState Name
-> Const (Vector AttachmentData) (EditState Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Vector AttachmentData
 -> Const (Vector AttachmentData) (Vector AttachmentData))
-> GenericList Name Vector AttachmentData
-> Const
     (Vector AttachmentData) (GenericList Name Vector AttachmentData)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
L.listElementsL)
    (MessageInterface Name i -> Identity (MessageInterface Name i))
-> ChatState -> Identity ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> Identity (MessageInterface Name i))
 -> ChatState -> Identity ChatState)
-> ((MessageInterfaceMode -> Identity MessageInterfaceMode)
    -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> (MessageInterfaceMode -> Identity MessageInterfaceMode)
-> ChatState
-> Identity ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(MessageInterfaceMode -> Identity MessageInterfaceMode)
-> MessageInterface Name i -> Identity (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) MessageInterfaceMode
miMode ((MessageInterfaceMode -> Identity MessageInterfaceMode)
 -> ChatState -> Identity ChatState)
-> MessageInterfaceMode -> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= case Vector AttachmentData -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector AttachmentData
es of
        Int
0 -> MessageInterfaceMode
Compose
        Int
_ -> MessageInterfaceMode
ManageAttachments

handleFileBrowserEvent :: Lens' ChatState (MessageInterface Name i) -> V.Event -> MH ()
handleFileBrowserEvent :: Lens' ChatState (MessageInterface Name i) -> Event -> MH ()
handleFileBrowserEvent Lens' ChatState (MessageInterface Name i)
which Event
e = do
    let fbHandle :: Event -> t (FileBrowser n) -> EventM n (t (FileBrowser n))
fbHandle Event
ev = t (EventM n (FileBrowser n)) -> EventM n (t (FileBrowser n))
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence (t (EventM n (FileBrowser n)) -> EventM n (t (FileBrowser n)))
-> (t (FileBrowser n) -> t (EventM n (FileBrowser n)))
-> t (FileBrowser n)
-> EventM n (t (FileBrowser n))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FileBrowser n -> EventM n (FileBrowser n))
-> t (FileBrowser n) -> t (EventM n (FileBrowser n))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Event -> FileBrowser n -> EventM n (FileBrowser n)
forall n.
Ord n =>
Event -> FileBrowser n -> EventM n (FileBrowser n)
FB.handleFileBrowserEvent Event
ev))
    Lens' ChatState (Maybe (FileBrowser Name))
-> (Event
    -> Maybe (FileBrowser Name)
    -> EventM Name (Maybe (FileBrowser Name)))
-> Event
-> MH ()
forall b e.
Lens' ChatState b -> (e -> b -> EventM Name b) -> e -> MH ()
mhHandleEventLensed ((MessageInterface Name i -> f (MessageInterface Name i))
-> ChatState -> f ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> f (MessageInterface Name i))
 -> ChatState -> f ChatState)
-> ((Maybe (FileBrowser Name) -> f (Maybe (FileBrowser Name)))
    -> MessageInterface Name i -> f (MessageInterface Name i))
-> (Maybe (FileBrowser Name) -> f (Maybe (FileBrowser Name)))
-> ChatState
-> f ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> f (EditState Name))
-> MessageInterface Name i -> f (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> f (EditState Name))
 -> MessageInterface Name i -> f (MessageInterface Name i))
-> ((Maybe (FileBrowser Name) -> f (Maybe (FileBrowser Name)))
    -> EditState Name -> f (EditState Name))
-> (Maybe (FileBrowser Name) -> f (Maybe (FileBrowser Name)))
-> MessageInterface Name i
-> f (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe (FileBrowser Name) -> f (Maybe (FileBrowser Name)))
-> EditState Name -> f (EditState Name)
forall n. Lens' (EditState n) (Maybe (FileBrowser n))
esFileBrowser) Event
-> Maybe (FileBrowser Name)
-> EventM Name (Maybe (FileBrowser Name))
forall (t :: * -> *) n.
(Traversable t, Ord n) =>
Event -> t (FileBrowser n) -> EventM n (t (FileBrowser n))
fbHandle Event
e
    -- TODO: Check file browser exception state
    Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i)
-> (FileBrowser Name -> MH ()) -> MH ()
withFileBrowser Lens' ChatState (MessageInterface Name i)
which ((FileBrowser Name -> MH ()) -> MH ())
-> (FileBrowser Name -> MH ()) -> MH ()
forall a b. (a -> b) -> a -> b
$ \FileBrowser Name
b ->
        Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
tryAddAttachment Lens' ChatState (MessageInterface Name i)
which (FileBrowser Name -> [FileInfo]
forall n. FileBrowser n -> [FileInfo]
FB.fileBrowserSelection FileBrowser Name
b)

deleteSelectedAttachment :: Lens' ChatState (MessageInterface Name i) -> MH ()
deleteSelectedAttachment :: Lens' ChatState (MessageInterface Name i) -> MH ()
deleteSelectedAttachment Lens' ChatState (MessageInterface Name i)
which = do
    Vector AttachmentData
es <- Getting (Vector AttachmentData) ChatState (Vector AttachmentData)
-> MH (Vector AttachmentData)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Vector AttachmentData) (MessageInterface Name i))
-> ChatState -> Const (Vector AttachmentData) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Vector AttachmentData) (MessageInterface Name i))
 -> ChatState -> Const (Vector AttachmentData) ChatState)
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> MessageInterface Name i
    -> Const (Vector AttachmentData) (MessageInterface Name i))
-> Getting
     (Vector AttachmentData) ChatState (Vector AttachmentData)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Const (Vector AttachmentData) (EditState Name))
-> MessageInterface Name i
-> Const (Vector AttachmentData) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Const (Vector AttachmentData) (EditState Name))
 -> MessageInterface Name i
 -> Const (Vector AttachmentData) (MessageInterface Name i))
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> EditState Name
    -> Const (Vector AttachmentData) (EditState Name))
-> (Vector AttachmentData
    -> Const (Vector AttachmentData) (Vector AttachmentData))
-> MessageInterface Name i
-> Const (Vector AttachmentData) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Const
      (Vector AttachmentData) (GenericList Name Vector AttachmentData))
-> EditState Name -> Const (Vector AttachmentData) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((GenericList Name Vector AttachmentData
  -> Const
       (Vector AttachmentData) (GenericList Name Vector AttachmentData))
 -> EditState Name
 -> Const (Vector AttachmentData) (EditState Name))
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> GenericList Name Vector AttachmentData
    -> Const
         (Vector AttachmentData) (GenericList Name Vector AttachmentData))
-> (Vector AttachmentData
    -> Const (Vector AttachmentData) (Vector AttachmentData))
-> EditState Name
-> Const (Vector AttachmentData) (EditState Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Vector AttachmentData
 -> Const (Vector AttachmentData) (Vector AttachmentData))
-> GenericList Name Vector AttachmentData
-> Const
     (Vector AttachmentData) (GenericList Name Vector AttachmentData)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
L.listElementsL)
    Maybe (Int, AttachmentData)
mSel <- Getting
  (Maybe (Int, AttachmentData))
  ChatState
  (Maybe (Int, AttachmentData))
-> MH (Maybe (Int, AttachmentData))
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> ChatState -> Const (Maybe (Int, AttachmentData)) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
 -> ChatState -> Const (Maybe (Int, AttachmentData)) ChatState)
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> MessageInterface Name i
    -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> Getting
     (Maybe (Int, AttachmentData))
     ChatState
     (Maybe (Int, AttachmentData))
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name
 -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> MessageInterface Name i
-> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name
  -> Const (Maybe (Int, AttachmentData)) (EditState Name))
 -> MessageInterface Name i
 -> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i))
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> EditState Name
    -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> (Maybe (Int, AttachmentData)
    -> Const
         (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
-> MessageInterface Name i
-> Const (Maybe (Int, AttachmentData)) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Const
      (Maybe (Int, AttachmentData))
      (GenericList Name Vector AttachmentData))
-> EditState Name
-> Const (Maybe (Int, AttachmentData)) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((GenericList Name Vector AttachmentData
  -> Const
       (Maybe (Int, AttachmentData))
       (GenericList Name Vector AttachmentData))
 -> EditState Name
 -> Const (Maybe (Int, AttachmentData)) (EditState Name))
-> ((Maybe (Int, AttachmentData)
     -> Const
          (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
    -> GenericList Name Vector AttachmentData
    -> Const
         (Maybe (Int, AttachmentData))
         (GenericList Name Vector AttachmentData))
-> (Maybe (Int, AttachmentData)
    -> Const
         (Maybe (Int, AttachmentData)) (Maybe (Int, AttachmentData)))
-> EditState Name
-> Const (Maybe (Int, AttachmentData)) (EditState Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Maybe (Int, AttachmentData))
-> SimpleGetter
     (GenericList Name Vector AttachmentData)
     (Maybe (Int, AttachmentData))
forall s a. (s -> a) -> SimpleGetter s a
to GenericList Name Vector AttachmentData
-> Maybe (Int, AttachmentData)
forall (t :: * -> *) n e.
(Splittable t, Foldable t) =>
GenericList n t e -> Maybe (Int, e)
L.listSelectedElement)
    case Maybe (Int, AttachmentData)
mSel of
        Maybe (Int, AttachmentData)
Nothing ->
            () -> MH ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        Just (Int
pos, AttachmentData
_) -> do
            Maybe Int
oldIdx <- Getting (Maybe Int) ChatState (Maybe Int) -> MH (Maybe Int)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (Maybe Int) (MessageInterface Name i))
-> ChatState -> Const (Maybe Int) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (Maybe Int) (MessageInterface Name i))
 -> ChatState -> Const (Maybe Int) ChatState)
-> ((Maybe Int -> Const (Maybe Int) (Maybe Int))
    -> MessageInterface Name i
    -> Const (Maybe Int) (MessageInterface Name i))
-> Getting (Maybe Int) ChatState (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Const (Maybe Int) (EditState Name))
-> MessageInterface Name i
-> Const (Maybe Int) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Const (Maybe Int) (EditState Name))
 -> MessageInterface Name i
 -> Const (Maybe Int) (MessageInterface Name i))
-> ((Maybe Int -> Const (Maybe Int) (Maybe Int))
    -> EditState Name -> Const (Maybe Int) (EditState Name))
-> (Maybe Int -> Const (Maybe Int) (Maybe Int))
-> MessageInterface Name i
-> Const (Maybe Int) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Const (Maybe Int) (GenericList Name Vector AttachmentData))
-> EditState Name -> Const (Maybe Int) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((GenericList Name Vector AttachmentData
  -> Const (Maybe Int) (GenericList Name Vector AttachmentData))
 -> EditState Name -> Const (Maybe Int) (EditState Name))
-> ((Maybe Int -> Const (Maybe Int) (Maybe Int))
    -> GenericList Name Vector AttachmentData
    -> Const (Maybe Int) (GenericList Name Vector AttachmentData))
-> (Maybe Int -> Const (Maybe Int) (Maybe Int))
-> EditState Name
-> Const (Maybe Int) (EditState Name)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Maybe Int -> Const (Maybe Int) (Maybe Int))
-> GenericList Name Vector AttachmentData
-> Const (Maybe Int) (GenericList Name Vector AttachmentData)
forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL)
            let idx :: Maybe Int
idx = if Vector AttachmentData -> Int
forall a. Vector a -> Int
Vector.length Vector AttachmentData
es Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1
                      then Maybe Int
forall a. Maybe a
Nothing
                      else case Maybe Int
oldIdx of
                          Maybe Int
Nothing -> Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
                          Just Int
old -> if Int
pos Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
old
                                      then Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ Int
pos Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
                                      else Int -> Maybe Int
forall a. a -> Maybe a
Just Int
pos
            (MessageInterface Name i -> Identity (MessageInterface Name i))
-> ChatState -> Identity ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i -> Identity (MessageInterface Name i))
 -> ChatState -> Identity ChatState)
-> ((GenericList Name Vector AttachmentData
     -> Identity (GenericList Name Vector AttachmentData))
    -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> (GenericList Name Vector AttachmentData
    -> Identity (GenericList Name Vector AttachmentData))
-> ChatState
-> Identity ChatState
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name -> Identity (EditState Name))
-> MessageInterface Name i -> Identity (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name -> Identity (EditState Name))
 -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> ((GenericList Name Vector AttachmentData
     -> Identity (GenericList Name Vector AttachmentData))
    -> EditState Name -> Identity (EditState Name))
-> (GenericList Name Vector AttachmentData
    -> Identity (GenericList Name Vector AttachmentData))
-> MessageInterface Name i
-> Identity (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(GenericList Name Vector AttachmentData
 -> Identity (GenericList Name Vector AttachmentData))
-> EditState Name -> Identity (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList ((GenericList Name Vector AttachmentData
  -> Identity (GenericList Name Vector AttachmentData))
 -> ChatState -> Identity ChatState)
-> (GenericList Name Vector AttachmentData
    -> GenericList Name Vector AttachmentData)
-> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Vector AttachmentData
-> Maybe Int
-> GenericList Name Vector AttachmentData
-> GenericList Name Vector AttachmentData
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
t e -> Maybe Int -> GenericList n t e -> GenericList n t e
L.listReplace (Int -> Vector AttachmentData -> Vector AttachmentData
forall a. Int -> Vector a -> Vector a
deleteAt Int
pos Vector AttachmentData
es) Maybe Int
idx

deleteAt :: Int -> Vector.Vector a -> Vector.Vector a
deleteAt :: Int -> Vector a -> Vector a
deleteAt Int
p Vector a
as | Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Vector a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length Vector a
as = Vector a
as
              | Bool
otherwise = Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
Vector.take Int
p Vector a
as Vector a -> Vector a -> Vector a
forall a. Semigroup a => a -> a -> a
<> Int -> Vector a -> Vector a
forall a. Int -> Vector a -> Vector a
Vector.drop (Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) Vector a
as