{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RankNTypes #-}
module Matterhorn.State.Attachments
  ( showAttachmentList
  , showAttachmentFileBrowser
  , attachFileByPath
  , tryAddAttachment
  , tryReadAttachment
  )
where

import           Prelude ()
import           Matterhorn.Prelude

import qualified Brick.Widgets.List as L
import qualified Brick.Widgets.FileBrowser as FB
import qualified Control.Exception as E
import           Data.Bool ( bool )
import qualified Data.ByteString as BS
import           Data.Either ( isRight )
import           Data.Text ( unpack )
import qualified Data.Vector as Vector
import           GHC.Exception ( toException )
import           Lens.Micro.Platform ( (.=), (%=), Lens' )
import           System.Directory ( doesDirectoryExist, doesFileExist, getDirectoryContents )

import           Matterhorn.Types

validateAttachmentPath :: FilePath -> IO (Maybe FilePath)
validateAttachmentPath :: FilePath -> IO (Maybe FilePath)
validateAttachmentPath FilePath
path = Maybe FilePath -> Maybe FilePath -> Bool -> Maybe FilePath
forall a. a -> a -> Bool -> a
bool Maybe FilePath
forall a. Maybe a
Nothing (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
path) (Bool -> Maybe FilePath) -> IO Bool -> IO (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> do
    Bool
ex <- FilePath -> IO Bool
doesDirectoryExist FilePath
path
    case Bool
ex of
        Bool
False -> Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
        Bool
True -> do
            Either SomeException [FilePath]
result :: Either E.SomeException [FilePath]
                   <- IO [FilePath] -> IO (Either SomeException [FilePath])
forall e a. Exception e => IO a -> IO (Either e a)
E.try (IO [FilePath] -> IO (Either SomeException [FilePath]))
-> IO [FilePath] -> IO (Either SomeException [FilePath])
forall a b. (a -> b) -> a -> b
$ FilePath -> IO [FilePath]
getDirectoryContents FilePath
path
            Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$ Either SomeException [FilePath] -> Bool
forall a b. Either a b -> Bool
isRight Either SomeException [FilePath]
result

defaultAttachmentsPath :: Config -> IO (Maybe FilePath)
defaultAttachmentsPath :: Config -> IO (Maybe FilePath)
defaultAttachmentsPath = IO (Maybe FilePath)
-> (FilePath -> IO (Maybe FilePath))
-> Maybe FilePath
-> IO (Maybe FilePath)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe FilePath -> IO (Maybe FilePath)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FilePath
forall a. Maybe a
Nothing) FilePath -> IO (Maybe FilePath)
validateAttachmentPath (Maybe FilePath -> IO (Maybe FilePath))
-> (Config -> Maybe FilePath) -> Config -> IO (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Config -> Maybe FilePath
configDefaultAttachmentPath

showAttachmentList :: Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentList :: Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentList Lens' ChatState (MessageInterface Name i)
which = do
    List Name AttachmentData
lst <- Getting
  (List Name AttachmentData) ChatState (List Name AttachmentData)
-> MH (List Name AttachmentData)
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((MessageInterface Name i
 -> Const (List Name AttachmentData) (MessageInterface Name i))
-> ChatState -> Const (List Name AttachmentData) ChatState
Lens' ChatState (MessageInterface Name i)
which((MessageInterface Name i
  -> Const (List Name AttachmentData) (MessageInterface Name i))
 -> ChatState -> Const (List Name AttachmentData) ChatState)
-> ((List Name AttachmentData
     -> Const (List Name AttachmentData) (List Name AttachmentData))
    -> MessageInterface Name i
    -> Const (List Name AttachmentData) (MessageInterface Name i))
-> Getting
     (List Name AttachmentData) ChatState (List Name AttachmentData)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(EditState Name
 -> Const (List Name AttachmentData) (EditState Name))
-> MessageInterface Name i
-> Const (List Name AttachmentData) (MessageInterface Name i)
forall n i. Lens' (MessageInterface n i) (EditState n)
miEditor((EditState Name
  -> Const (List Name AttachmentData) (EditState Name))
 -> MessageInterface Name i
 -> Const (List Name AttachmentData) (MessageInterface Name i))
-> ((List Name AttachmentData
     -> Const (List Name AttachmentData) (List Name AttachmentData))
    -> EditState Name
    -> Const (List Name AttachmentData) (EditState Name))
-> (List Name AttachmentData
    -> Const (List Name AttachmentData) (List Name AttachmentData))
-> MessageInterface Name i
-> Const (List Name AttachmentData) (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(List Name AttachmentData
 -> Const (List Name AttachmentData) (List Name AttachmentData))
-> EditState Name
-> Const (List Name AttachmentData) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList)
    case Vector AttachmentData -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (List Name AttachmentData -> Vector AttachmentData
forall n (t :: * -> *) e. GenericList n t e -> t e
L.listElements List Name AttachmentData
lst) of
        Int
0 -> Lens' ChatState (MessageInterface Name i) -> MH ()
forall i. Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentFileBrowser Lens' ChatState (MessageInterface Name i)
which
        Int
_ -> (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
ManageAttachments

showAttachmentFileBrowser :: Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentFileBrowser :: Lens' ChatState (MessageInterface Name i) -> MH ()
showAttachmentFileBrowser Lens' ChatState (MessageInterface Name i)
which = do
    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)
    Config
config <- Getting Config ChatState Config -> MH Config
forall s (m :: * -> *) a. MonadState s m => Getting a s a -> m a
use ((ChatResources -> Const Config ChatResources)
-> ChatState -> Const Config ChatState
Lens' ChatState ChatResources
csResources((ChatResources -> Const Config ChatResources)
 -> ChatState -> Const Config ChatState)
-> ((Config -> Const Config Config)
    -> ChatResources -> Const Config ChatResources)
-> Getting Config ChatState Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(Config -> Const Config Config)
-> ChatResources -> Const Config ChatResources
Lens' ChatResources Config
crConfiguration)
    Maybe FilePath
filePath <- IO (Maybe FilePath) -> MH (Maybe FilePath)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FilePath) -> MH (Maybe FilePath))
-> IO (Maybe FilePath) -> MH (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$ Config -> IO (Maybe FilePath)
defaultAttachmentsPath Config
config
    Maybe (FileBrowser Name)
browser <- IO (Maybe (FileBrowser Name)) -> MH (Maybe (FileBrowser Name))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (FileBrowser Name)) -> MH (Maybe (FileBrowser Name)))
-> IO (Maybe (FileBrowser Name)) -> MH (Maybe (FileBrowser Name))
forall a b. (a -> b) -> a -> b
$ FileBrowser Name -> Maybe (FileBrowser Name)
forall a. a -> Maybe a
Just (FileBrowser Name -> Maybe (FileBrowser Name))
-> IO (FileBrowser Name) -> IO (Maybe (FileBrowser Name))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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
filePath
    (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)
-> Maybe (FileBrowser Name) -> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> b -> m ()
.= Maybe (FileBrowser Name)
browser
    (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
BrowseFiles

attachFileByPath :: Lens' ChatState (MessageInterface Name i) -> Text -> MH ()
attachFileByPath :: Lens' ChatState (MessageInterface Name i) -> Text -> MH ()
attachFileByPath Lens' ChatState (MessageInterface Name i)
which Text
txtPath = do
    let strPath :: FilePath
strPath = Text -> FilePath
unpack Text
txtPath
    FileInfo
fileInfo <- IO FileInfo -> MH FileInfo
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FileInfo -> MH FileInfo) -> IO FileInfo -> MH FileInfo
forall a b. (a -> b) -> a -> b
$ FilePath -> FilePath -> IO FileInfo
FB.getFileInfo FilePath
strPath FilePath
strPath
    case FileInfo -> Either IOException FileStatus
FB.fileInfoFileStatus FileInfo
fileInfo of
        Left IOException
e -> do
            MHError -> MH ()
mhError (MHError -> MH ()) -> MHError -> MH ()
forall a b. (a -> b) -> a -> b
$ SomeException -> MHError
AttachmentException (IOException -> SomeException
forall e. Exception e => e -> SomeException
toException IOException
e)
        Right FileStatus
_ -> Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
forall i.
Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
tryAddAttachment Lens' ChatState (MessageInterface Name i)
which [FileInfo
fileInfo]

checkPathIsFile :: FB.FileInfo -> MH Bool
checkPathIsFile :: FileInfo -> MH Bool
checkPathIsFile = IO Bool -> MH Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> MH Bool)
-> (FileInfo -> IO Bool) -> FileInfo -> MH Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Bool
doesFileExist (FilePath -> IO Bool)
-> (FileInfo -> FilePath) -> FileInfo -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FileInfo -> FilePath
FB.fileInfoFilePath

tryAddAttachment :: Lens' ChatState (MessageInterface Name i) -> [FB.FileInfo] -> MH ()
tryAddAttachment :: Lens' ChatState (MessageInterface Name i) -> [FileInfo] -> MH ()
tryAddAttachment Lens' ChatState (MessageInterface Name i)
which [FileInfo]
entries = do
    [FileInfo] -> (FileInfo -> MH ()) -> MH ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
t a -> (a -> m b) -> m ()
forM_ [FileInfo]
entries ((FileInfo -> MH ()) -> MH ()) -> (FileInfo -> MH ()) -> MH ()
forall a b. (a -> b) -> a -> b
$ \FileInfo
entry -> do
        Bool
isFile <- FileInfo -> MH Bool
checkPathIsFile FileInfo
entry
        if Bool -> Bool
not Bool
isFile
        then MHError -> MH ()
mhError (Text -> MHError
BadAttachmentPath
            Text
"Error attaching file. It either doesn't exist or is a directory, which is not supported.")
        else do
            -- Is the entry already present? If so, ignore the selection.
            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
.(List Name AttachmentData
 -> Const (Vector AttachmentData) (List Name AttachmentData))
-> EditState Name -> Const (Vector AttachmentData) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((List Name AttachmentData
  -> Const (Vector AttachmentData) (List Name AttachmentData))
 -> EditState Name
 -> Const (Vector AttachmentData) (EditState Name))
-> ((Vector AttachmentData
     -> Const (Vector AttachmentData) (Vector AttachmentData))
    -> List Name AttachmentData
    -> Const (Vector AttachmentData) (List Name 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))
-> List Name AttachmentData
-> Const (Vector AttachmentData) (List Name AttachmentData)
forall n (t1 :: * -> *) e1 (t2 :: * -> *) e2.
Lens (GenericList n t1 e1) (GenericList n t2 e2) (t1 e1) (t2 e2)
L.listElementsL)
            let matches :: AttachmentData -> Bool
matches = (FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== FileInfo -> FilePath
FB.fileInfoFilePath FileInfo
entry) (FilePath -> Bool)
-> (AttachmentData -> FilePath) -> AttachmentData -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              FileInfo -> FilePath
FB.fileInfoFilePath (FileInfo -> FilePath)
-> (AttachmentData -> FileInfo) -> AttachmentData -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
                              AttachmentData -> FileInfo
attachmentDataFileInfo
            case (AttachmentData -> Bool)
-> Vector AttachmentData -> Maybe AttachmentData
forall a. (a -> Bool) -> Vector a -> Maybe a
Vector.find AttachmentData -> Bool
matches Vector AttachmentData
es of
                Just AttachmentData
_ -> () -> MH ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                Maybe AttachmentData
Nothing -> do
                    FileInfo -> MH (Either SomeException AttachmentData)
tryReadAttachment FileInfo
entry MH (Either SomeException AttachmentData)
-> (Either SomeException AttachmentData -> MH ()) -> MH ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
                        Right AttachmentData
a -> 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
.(List Name AttachmentData
 -> Const (Maybe Int) (List Name AttachmentData))
-> EditState Name -> Const (Maybe Int) (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList((List Name AttachmentData
  -> Const (Maybe Int) (List Name AttachmentData))
 -> EditState Name -> Const (Maybe Int) (EditState Name))
-> ((Maybe Int -> Const (Maybe Int) (Maybe Int))
    -> List Name AttachmentData
    -> Const (Maybe Int) (List Name 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))
-> List Name AttachmentData
-> Const (Maybe Int) (List Name AttachmentData)
forall n (t :: * -> *) e. Lens' (GenericList n t e) (Maybe Int)
L.listSelectedL)
                            let newIdx :: Maybe Int
newIdx = if Vector AttachmentData -> Bool
forall a. Vector a -> Bool
Vector.null Vector AttachmentData
es
                                         then Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
                                         else Maybe Int
oldIdx
                            (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)
-> ((List Name AttachmentData
     -> Identity (List Name AttachmentData))
    -> MessageInterface Name i -> Identity (MessageInterface Name i))
-> (List Name AttachmentData
    -> Identity (List Name 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))
-> ((List Name AttachmentData
     -> Identity (List Name AttachmentData))
    -> EditState Name -> Identity (EditState Name))
-> (List Name AttachmentData
    -> Identity (List Name AttachmentData))
-> MessageInterface Name i
-> Identity (MessageInterface Name i)
forall b c a. (b -> c) -> (a -> b) -> a -> c
.(List Name AttachmentData -> Identity (List Name AttachmentData))
-> EditState Name -> Identity (EditState Name)
forall n. Lens' (EditState n) (List n AttachmentData)
esAttachmentList ((List Name AttachmentData -> Identity (List Name AttachmentData))
 -> ChatState -> Identity ChatState)
-> (List Name AttachmentData -> List Name AttachmentData) -> MH ()
forall s (m :: * -> *) a b.
MonadState s m =>
ASetter s s a b -> (a -> b) -> m ()
%= Vector AttachmentData
-> Maybe Int
-> List Name AttachmentData
-> List Name AttachmentData
forall (t :: * -> *) e n.
(Foldable t, Splittable t) =>
t e -> Maybe Int -> GenericList n t e -> GenericList n t e
L.listReplace (Vector AttachmentData -> AttachmentData -> Vector AttachmentData
forall a. Vector a -> a -> Vector a
Vector.snoc Vector AttachmentData
es AttachmentData
a) Maybe Int
newIdx
                        Left SomeException
e -> MHError -> MH ()
mhError (MHError -> MH ()) -> MHError -> MH ()
forall a b. (a -> b) -> a -> b
$ SomeException -> MHError
AttachmentException SomeException
e

    Bool -> MH () -> MH ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ [FileInfo] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [FileInfo]
entries) (MH () -> MH ()) -> MH () -> MH ()
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

tryReadAttachment :: FB.FileInfo -> MH (Either E.SomeException AttachmentData)
tryReadAttachment :: FileInfo -> MH (Either SomeException AttachmentData)
tryReadAttachment FileInfo
fi = do
    let path :: FilePath
path = FileInfo -> FilePath
FB.fileInfoFilePath FileInfo
fi
    Either SomeException ByteString
readResult <- IO (Either SomeException ByteString)
-> MH (Either SomeException ByteString)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Either SomeException ByteString)
 -> MH (Either SomeException ByteString))
-> IO (Either SomeException ByteString)
-> MH (Either SomeException ByteString)
forall a b. (a -> b) -> a -> b
$ IO ByteString -> IO (Either SomeException ByteString)
forall e a. Exception e => IO a -> IO (Either e a)
E.try (IO ByteString -> IO (Either SomeException ByteString))
-> IO ByteString -> IO (Either SomeException ByteString)
forall a b. (a -> b) -> a -> b
$ FilePath -> IO ByteString
BS.readFile FilePath
path
    case Either SomeException ByteString
readResult of
        Right ByteString
bytes -> do
            Either SomeException AttachmentData
-> MH (Either SomeException AttachmentData)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException AttachmentData
 -> MH (Either SomeException AttachmentData))
-> Either SomeException AttachmentData
-> MH (Either SomeException AttachmentData)
forall a b. (a -> b) -> a -> b
$ AttachmentData -> Either SomeException AttachmentData
forall a b. b -> Either a b
Right (AttachmentData -> Either SomeException AttachmentData)
-> AttachmentData -> Either SomeException AttachmentData
forall a b. (a -> b) -> a -> b
$
                AttachmentData :: FileInfo -> ByteString -> AttachmentData
AttachmentData { attachmentDataFileInfo :: FileInfo
attachmentDataFileInfo = FileInfo
fi
                               , attachmentDataBytes :: ByteString
attachmentDataBytes = ByteString
bytes
                               }
        Left SomeException
e -> Either SomeException AttachmentData
-> MH (Either SomeException AttachmentData)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException AttachmentData
 -> MH (Either SomeException AttachmentData))
-> Either SomeException AttachmentData
-> MH (Either SomeException AttachmentData)
forall a b. (a -> b) -> a -> b
$ SomeException -> Either SomeException AttachmentData
forall a b. a -> Either a b
Left SomeException
e