module Desktop.Portal.FileChooser
(
Filter (..),
FilterFileType (..),
ChoiceCombo (..),
ChoiceComboOption (..),
ChoiceComboSelection (..),
OpenFileOptions (..),
OpenFileResults (..),
openFile,
SaveFileOptions (..),
SaveFileResults (..),
saveFile,
)
where
import Control.Exception (throwIO)
import DBus (InterfaceName, Variant)
import DBus qualified
import DBus.Client qualified as DBus
import Data.Default (Default (def))
import Data.Map (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe (catMaybes, fromMaybe)
import Data.Text (Text)
import Data.Word (Word32)
import Desktop.Portal.Internal (Client, Request, sendRequest)
import Desktop.Portal.Util (decodeFileUris, encodeNullTerminated, mapJust, optionalFromVariant, toVariantPair, toVariantPair')
import System.OsPath (OsPath)
data Filter = Filter
{ Filter -> Text
name :: Text,
Filter -> [FilterFileType]
fileTypes :: [FilterFileType]
}
deriving (Filter -> Filter -> Bool
(Filter -> Filter -> Bool)
-> (Filter -> Filter -> Bool) -> Eq Filter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Filter -> Filter -> Bool
== :: Filter -> Filter -> Bool
$c/= :: Filter -> Filter -> Bool
/= :: Filter -> Filter -> Bool
Eq, Int -> Filter -> ShowS
[Filter] -> ShowS
Filter -> String
(Int -> Filter -> ShowS)
-> (Filter -> String) -> ([Filter] -> ShowS) -> Show Filter
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Filter -> ShowS
showsPrec :: Int -> Filter -> ShowS
$cshow :: Filter -> String
show :: Filter -> String
$cshowList :: [Filter] -> ShowS
showList :: [Filter] -> ShowS
Show)
data FilterFileType
= GlobFilter Text
| MimeFilter Text
deriving (FilterFileType -> FilterFileType -> Bool
(FilterFileType -> FilterFileType -> Bool)
-> (FilterFileType -> FilterFileType -> Bool) -> Eq FilterFileType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FilterFileType -> FilterFileType -> Bool
== :: FilterFileType -> FilterFileType -> Bool
$c/= :: FilterFileType -> FilterFileType -> Bool
/= :: FilterFileType -> FilterFileType -> Bool
Eq, Int -> FilterFileType -> ShowS
[FilterFileType] -> ShowS
FilterFileType -> String
(Int -> FilterFileType -> ShowS)
-> (FilterFileType -> String)
-> ([FilterFileType] -> ShowS)
-> Show FilterFileType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FilterFileType -> ShowS
showsPrec :: Int -> FilterFileType -> ShowS
$cshow :: FilterFileType -> String
show :: FilterFileType -> String
$cshowList :: [FilterFileType] -> ShowS
showList :: [FilterFileType] -> ShowS
Show)
data ChoiceCombo = ChoiceCombo
{ ChoiceCombo -> Text
id :: Text,
ChoiceCombo -> Text
label_ :: Text,
ChoiceCombo -> [ChoiceComboOption]
choices :: [ChoiceComboOption],
ChoiceCombo -> Text
defaultChoiceId :: Text
}
deriving (ChoiceCombo -> ChoiceCombo -> Bool
(ChoiceCombo -> ChoiceCombo -> Bool)
-> (ChoiceCombo -> ChoiceCombo -> Bool) -> Eq ChoiceCombo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChoiceCombo -> ChoiceCombo -> Bool
== :: ChoiceCombo -> ChoiceCombo -> Bool
$c/= :: ChoiceCombo -> ChoiceCombo -> Bool
/= :: ChoiceCombo -> ChoiceCombo -> Bool
Eq, Int -> ChoiceCombo -> ShowS
[ChoiceCombo] -> ShowS
ChoiceCombo -> String
(Int -> ChoiceCombo -> ShowS)
-> (ChoiceCombo -> String)
-> ([ChoiceCombo] -> ShowS)
-> Show ChoiceCombo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChoiceCombo -> ShowS
showsPrec :: Int -> ChoiceCombo -> ShowS
$cshow :: ChoiceCombo -> String
show :: ChoiceCombo -> String
$cshowList :: [ChoiceCombo] -> ShowS
showList :: [ChoiceCombo] -> ShowS
Show)
data ChoiceComboOption = ChoiceComboOption
{ ChoiceComboOption -> Text
id :: Text,
ChoiceComboOption -> Text
label_ :: Text
}
deriving (ChoiceComboOption -> ChoiceComboOption -> Bool
(ChoiceComboOption -> ChoiceComboOption -> Bool)
-> (ChoiceComboOption -> ChoiceComboOption -> Bool)
-> Eq ChoiceComboOption
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChoiceComboOption -> ChoiceComboOption -> Bool
== :: ChoiceComboOption -> ChoiceComboOption -> Bool
$c/= :: ChoiceComboOption -> ChoiceComboOption -> Bool
/= :: ChoiceComboOption -> ChoiceComboOption -> Bool
Eq, Int -> ChoiceComboOption -> ShowS
[ChoiceComboOption] -> ShowS
ChoiceComboOption -> String
(Int -> ChoiceComboOption -> ShowS)
-> (ChoiceComboOption -> String)
-> ([ChoiceComboOption] -> ShowS)
-> Show ChoiceComboOption
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChoiceComboOption -> ShowS
showsPrec :: Int -> ChoiceComboOption -> ShowS
$cshow :: ChoiceComboOption -> String
show :: ChoiceComboOption -> String
$cshowList :: [ChoiceComboOption] -> ShowS
showList :: [ChoiceComboOption] -> ShowS
Show)
data ChoiceComboSelection = ChoiceComboSelection
{ ChoiceComboSelection -> Text
comboId :: Text,
ChoiceComboSelection -> Text
optionId :: Text
}
deriving (ChoiceComboSelection -> ChoiceComboSelection -> Bool
(ChoiceComboSelection -> ChoiceComboSelection -> Bool)
-> (ChoiceComboSelection -> ChoiceComboSelection -> Bool)
-> Eq ChoiceComboSelection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChoiceComboSelection -> ChoiceComboSelection -> Bool
== :: ChoiceComboSelection -> ChoiceComboSelection -> Bool
$c/= :: ChoiceComboSelection -> ChoiceComboSelection -> Bool
/= :: ChoiceComboSelection -> ChoiceComboSelection -> Bool
Eq, Int -> ChoiceComboSelection -> ShowS
[ChoiceComboSelection] -> ShowS
ChoiceComboSelection -> String
(Int -> ChoiceComboSelection -> ShowS)
-> (ChoiceComboSelection -> String)
-> ([ChoiceComboSelection] -> ShowS)
-> Show ChoiceComboSelection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChoiceComboSelection -> ShowS
showsPrec :: Int -> ChoiceComboSelection -> ShowS
$cshow :: ChoiceComboSelection -> String
show :: ChoiceComboSelection -> String
$cshowList :: [ChoiceComboSelection] -> ShowS
showList :: [ChoiceComboSelection] -> ShowS
Show)
data OpenFileOptions = OpenFileOptions
{ OpenFileOptions -> Maybe Text
parentWindow :: Maybe Text,
OpenFileOptions -> Maybe Text
title :: Maybe Text,
OpenFileOptions -> Maybe Text
acceptLabel :: Maybe Text,
OpenFileOptions -> Maybe Bool
modal :: Maybe Bool,
OpenFileOptions -> Maybe Bool
multiple :: Maybe Bool,
OpenFileOptions -> Maybe Bool
directory :: Maybe Bool,
OpenFileOptions -> Maybe [Filter]
filters :: Maybe [Filter],
OpenFileOptions -> Maybe Filter
currentFilter :: Maybe Filter,
OpenFileOptions -> Maybe [ChoiceCombo]
choices :: Maybe [ChoiceCombo]
}
deriving (OpenFileOptions -> OpenFileOptions -> Bool
(OpenFileOptions -> OpenFileOptions -> Bool)
-> (OpenFileOptions -> OpenFileOptions -> Bool)
-> Eq OpenFileOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenFileOptions -> OpenFileOptions -> Bool
== :: OpenFileOptions -> OpenFileOptions -> Bool
$c/= :: OpenFileOptions -> OpenFileOptions -> Bool
/= :: OpenFileOptions -> OpenFileOptions -> Bool
Eq, Int -> OpenFileOptions -> ShowS
[OpenFileOptions] -> ShowS
OpenFileOptions -> String
(Int -> OpenFileOptions -> ShowS)
-> (OpenFileOptions -> String)
-> ([OpenFileOptions] -> ShowS)
-> Show OpenFileOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenFileOptions -> ShowS
showsPrec :: Int -> OpenFileOptions -> ShowS
$cshow :: OpenFileOptions -> String
show :: OpenFileOptions -> String
$cshowList :: [OpenFileOptions] -> ShowS
showList :: [OpenFileOptions] -> ShowS
Show)
instance Default OpenFileOptions where
def :: OpenFileOptions
def =
OpenFileOptions
{ $sel:parentWindow:OpenFileOptions :: Maybe Text
parentWindow = Maybe Text
forall a. Maybe a
Nothing,
$sel:title:OpenFileOptions :: Maybe Text
title = Maybe Text
forall a. Maybe a
Nothing,
$sel:acceptLabel:OpenFileOptions :: Maybe Text
acceptLabel = Maybe Text
forall a. Maybe a
Nothing,
$sel:modal:OpenFileOptions :: Maybe Bool
modal = Maybe Bool
forall a. Maybe a
Nothing,
$sel:multiple:OpenFileOptions :: Maybe Bool
multiple = Maybe Bool
forall a. Maybe a
Nothing,
$sel:directory:OpenFileOptions :: Maybe Bool
directory = Maybe Bool
forall a. Maybe a
Nothing,
$sel:filters:OpenFileOptions :: Maybe [Filter]
filters = Maybe [Filter]
forall a. Maybe a
Nothing,
$sel:currentFilter:OpenFileOptions :: Maybe Filter
currentFilter = Maybe Filter
forall a. Maybe a
Nothing,
$sel:choices:OpenFileOptions :: Maybe [ChoiceCombo]
choices = Maybe [ChoiceCombo]
forall a. Maybe a
Nothing
}
data OpenFileResults = OpenFileResults
{ OpenFileResults -> [OsPath]
uris :: [OsPath],
OpenFileResults -> Maybe [ChoiceComboSelection]
choices :: Maybe [ChoiceComboSelection],
OpenFileResults -> Maybe Filter
currentFilter :: Maybe Filter
}
deriving (OpenFileResults -> OpenFileResults -> Bool
(OpenFileResults -> OpenFileResults -> Bool)
-> (OpenFileResults -> OpenFileResults -> Bool)
-> Eq OpenFileResults
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OpenFileResults -> OpenFileResults -> Bool
== :: OpenFileResults -> OpenFileResults -> Bool
$c/= :: OpenFileResults -> OpenFileResults -> Bool
/= :: OpenFileResults -> OpenFileResults -> Bool
Eq, Int -> OpenFileResults -> ShowS
[OpenFileResults] -> ShowS
OpenFileResults -> String
(Int -> OpenFileResults -> ShowS)
-> (OpenFileResults -> String)
-> ([OpenFileResults] -> ShowS)
-> Show OpenFileResults
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> OpenFileResults -> ShowS
showsPrec :: Int -> OpenFileResults -> ShowS
$cshow :: OpenFileResults -> String
show :: OpenFileResults -> String
$cshowList :: [OpenFileResults] -> ShowS
showList :: [OpenFileResults] -> ShowS
Show)
data SaveFileOptions = SaveFileOptions
{ SaveFileOptions -> Maybe Text
parentWindow :: Maybe Text,
SaveFileOptions -> Maybe Text
title :: Maybe Text,
SaveFileOptions -> Maybe Text
acceptLabel :: Maybe Text,
SaveFileOptions -> Maybe Bool
modal :: Maybe Bool,
SaveFileOptions -> Maybe [Filter]
filters :: Maybe [Filter],
SaveFileOptions -> Maybe Filter
currentFilter :: Maybe Filter,
SaveFileOptions -> Maybe [ChoiceCombo]
choices :: Maybe [ChoiceCombo],
SaveFileOptions -> Maybe Text
currentName :: Maybe Text,
SaveFileOptions -> Maybe OsPath
currentFolder :: Maybe OsPath,
SaveFileOptions -> Maybe OsPath
currentFile :: Maybe OsPath
}
deriving (SaveFileOptions -> SaveFileOptions -> Bool
(SaveFileOptions -> SaveFileOptions -> Bool)
-> (SaveFileOptions -> SaveFileOptions -> Bool)
-> Eq SaveFileOptions
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SaveFileOptions -> SaveFileOptions -> Bool
== :: SaveFileOptions -> SaveFileOptions -> Bool
$c/= :: SaveFileOptions -> SaveFileOptions -> Bool
/= :: SaveFileOptions -> SaveFileOptions -> Bool
Eq, Int -> SaveFileOptions -> ShowS
[SaveFileOptions] -> ShowS
SaveFileOptions -> String
(Int -> SaveFileOptions -> ShowS)
-> (SaveFileOptions -> String)
-> ([SaveFileOptions] -> ShowS)
-> Show SaveFileOptions
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SaveFileOptions -> ShowS
showsPrec :: Int -> SaveFileOptions -> ShowS
$cshow :: SaveFileOptions -> String
show :: SaveFileOptions -> String
$cshowList :: [SaveFileOptions] -> ShowS
showList :: [SaveFileOptions] -> ShowS
Show)
instance Default SaveFileOptions where
def :: SaveFileOptions
def =
SaveFileOptions
{ $sel:parentWindow:SaveFileOptions :: Maybe Text
parentWindow = Maybe Text
forall a. Maybe a
Nothing,
$sel:title:SaveFileOptions :: Maybe Text
title = Maybe Text
forall a. Maybe a
Nothing,
$sel:acceptLabel:SaveFileOptions :: Maybe Text
acceptLabel = Maybe Text
forall a. Maybe a
Nothing,
$sel:modal:SaveFileOptions :: Maybe Bool
modal = Maybe Bool
forall a. Maybe a
Nothing,
$sel:filters:SaveFileOptions :: Maybe [Filter]
filters = Maybe [Filter]
forall a. Maybe a
Nothing,
$sel:currentFilter:SaveFileOptions :: Maybe Filter
currentFilter = Maybe Filter
forall a. Maybe a
Nothing,
$sel:choices:SaveFileOptions :: Maybe [ChoiceCombo]
choices = Maybe [ChoiceCombo]
forall a. Maybe a
Nothing,
$sel:currentName:SaveFileOptions :: Maybe Text
currentName = Maybe Text
forall a. Maybe a
Nothing,
$sel:currentFolder:SaveFileOptions :: Maybe OsPath
currentFolder = Maybe OsPath
forall a. Maybe a
Nothing,
$sel:currentFile:SaveFileOptions :: Maybe OsPath
currentFile = Maybe OsPath
forall a. Maybe a
Nothing
}
data SaveFileResults = SaveFileResults
{ SaveFileResults -> [OsPath]
uris :: [OsPath],
SaveFileResults -> Maybe [ChoiceComboSelection]
choices :: Maybe [ChoiceComboSelection],
SaveFileResults -> Maybe Filter
currentFilter :: Maybe Filter
}
deriving (SaveFileResults -> SaveFileResults -> Bool
(SaveFileResults -> SaveFileResults -> Bool)
-> (SaveFileResults -> SaveFileResults -> Bool)
-> Eq SaveFileResults
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SaveFileResults -> SaveFileResults -> Bool
== :: SaveFileResults -> SaveFileResults -> Bool
$c/= :: SaveFileResults -> SaveFileResults -> Bool
/= :: SaveFileResults -> SaveFileResults -> Bool
Eq, Int -> SaveFileResults -> ShowS
[SaveFileResults] -> ShowS
SaveFileResults -> String
(Int -> SaveFileResults -> ShowS)
-> (SaveFileResults -> String)
-> ([SaveFileResults] -> ShowS)
-> Show SaveFileResults
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SaveFileResults -> ShowS
showsPrec :: Int -> SaveFileResults -> ShowS
$cshow :: SaveFileResults -> String
show :: SaveFileResults -> String
$cshowList :: [SaveFileResults] -> ShowS
showList :: [SaveFileResults] -> ShowS
Show)
fileChooserInterface :: InterfaceName
fileChooserInterface :: InterfaceName
fileChooserInterface = InterfaceName
"org.freedesktop.portal.FileChooser"
openFile :: Client -> OpenFileOptions -> IO (Request OpenFileResults)
openFile :: Client -> OpenFileOptions -> IO (Request OpenFileResults)
openFile Client
client OpenFileOptions
options =
Client
-> InterfaceName
-> MemberName
-> [Variant]
-> Map Text Variant
-> (Map Text Variant -> IO OpenFileResults)
-> IO (Request OpenFileResults)
forall a.
Client
-> InterfaceName
-> MemberName
-> [Variant]
-> Map Text Variant
-> (Map Text Variant -> IO a)
-> IO (Request a)
sendRequest Client
client InterfaceName
fileChooserInterface MemberName
"OpenFile" [Variant]
args Map Text Variant
optionsArg Map Text Variant -> IO OpenFileResults
parseOpenFileResponse
where
args :: [Variant]
args = [Text -> Variant
forall a. IsVariant a => a -> Variant
DBus.toVariant Text
parentWindow, Text -> Variant
forall a. IsVariant a => a -> Variant
DBus.toVariant Text
title]
parentWindow :: Text
parentWindow = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" OpenFileOptions
options.parentWindow
title :: Text
title = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" OpenFileOptions
options.title
optionsArg :: Map Text Variant
optionsArg =
[(Text, Variant)] -> Map Text Variant
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Text, Variant)] -> Map Text Variant)
-> ([Maybe (Text, Variant)] -> [(Text, Variant)])
-> [Maybe (Text, Variant)]
-> Map Text Variant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (Text, Variant)] -> [(Text, Variant)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (Text, Variant)] -> Map Text Variant)
-> [Maybe (Text, Variant)] -> Map Text Variant
forall a b. (a -> b) -> a -> b
$
[ Text -> Maybe Text -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"accept_label" OpenFileOptions
options.acceptLabel,
Text -> Maybe Bool -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"modal" OpenFileOptions
options.modal,
Text -> Maybe Bool -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"multiple" OpenFileOptions
options.multiple,
Text -> Maybe Bool -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"directory" OpenFileOptions
options.directory,
([Filter] -> [(Text, [(Word32, Text)])])
-> Text -> Maybe [Filter] -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' ((Filter -> (Text, [(Word32, Text)]))
-> [Filter] -> [(Text, [(Word32, Text)])]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Filter -> (Text, [(Word32, Text)])
encodeFilter) Text
"filters" OpenFileOptions
options.filters,
(Filter -> (Text, [(Word32, Text)]))
-> Text -> Maybe Filter -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' Filter -> (Text, [(Word32, Text)])
encodeFilter Text
"current_filter" OpenFileOptions
options.currentFilter,
([ChoiceCombo] -> [(Text, Text, [(Text, Text)], Text)])
-> Text -> Maybe [ChoiceCombo] -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' ((ChoiceCombo -> (Text, Text, [(Text, Text)], Text))
-> [ChoiceCombo] -> [(Text, Text, [(Text, Text)], Text)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ChoiceCombo -> (Text, Text, [(Text, Text)], Text)
encodeCombo) Text
"choices" OpenFileOptions
options.choices
]
saveFile :: Client -> SaveFileOptions -> IO (Request SaveFileResults)
saveFile :: Client -> SaveFileOptions -> IO (Request SaveFileResults)
saveFile Client
client SaveFileOptions
options =
Client
-> InterfaceName
-> MemberName
-> [Variant]
-> Map Text Variant
-> (Map Text Variant -> IO SaveFileResults)
-> IO (Request SaveFileResults)
forall a.
Client
-> InterfaceName
-> MemberName
-> [Variant]
-> Map Text Variant
-> (Map Text Variant -> IO a)
-> IO (Request a)
sendRequest Client
client InterfaceName
fileChooserInterface MemberName
"SaveFile" [Variant]
args Map Text Variant
optionsArgs Map Text Variant -> IO SaveFileResults
parseResponse
where
args :: [Variant]
args = [Text -> Variant
forall a. IsVariant a => a -> Variant
DBus.toVariant Text
parentWindow, Text -> Variant
forall a. IsVariant a => a -> Variant
DBus.toVariant Text
title]
parentWindow :: Text
parentWindow = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" SaveFileOptions
options.parentWindow
title :: Text
title = Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"" SaveFileOptions
options.title
optionsArgs :: Map Text Variant
optionsArgs =
[(Text, Variant)] -> Map Text Variant
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(Text, Variant)] -> Map Text Variant)
-> ([Maybe (Text, Variant)] -> [(Text, Variant)])
-> [Maybe (Text, Variant)]
-> Map Text Variant
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Maybe (Text, Variant)] -> [(Text, Variant)]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe (Text, Variant)] -> Map Text Variant)
-> [Maybe (Text, Variant)] -> Map Text Variant
forall a b. (a -> b) -> a -> b
$
[ Text -> Maybe Text -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"accept_label" SaveFileOptions
options.acceptLabel,
Text -> Maybe Bool -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"modal" SaveFileOptions
options.modal,
([Filter] -> [(Text, [(Word32, Text)])])
-> Text -> Maybe [Filter] -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' ((Filter -> (Text, [(Word32, Text)]))
-> [Filter] -> [(Text, [(Word32, Text)])]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Filter -> (Text, [(Word32, Text)])
encodeFilter) Text
"filters" SaveFileOptions
options.filters,
(Filter -> (Text, [(Word32, Text)]))
-> Text -> Maybe Filter -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' Filter -> (Text, [(Word32, Text)])
encodeFilter Text
"current_filter" SaveFileOptions
options.currentFilter,
([ChoiceCombo] -> [(Text, Text, [(Text, Text)], Text)])
-> Text -> Maybe [ChoiceCombo] -> Maybe (Text, Variant)
forall b a.
IsVariant b =>
(a -> b) -> Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair' ((ChoiceCombo -> (Text, Text, [(Text, Text)], Text))
-> [ChoiceCombo] -> [(Text, Text, [(Text, Text)], Text)]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ChoiceCombo -> (Text, Text, [(Text, Text)], Text)
encodeCombo) Text
"choices" SaveFileOptions
options.choices,
Text -> Maybe Text -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"current_name" SaveFileOptions
options.currentName,
Text -> Maybe ByteString -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"current_folder" (OsPath -> ByteString
encodeNullTerminated (OsPath -> ByteString) -> Maybe OsPath -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SaveFileOptions
options.currentFolder),
Text -> Maybe ByteString -> Maybe (Text, Variant)
forall a. IsVariant a => Text -> Maybe a -> Maybe (Text, Variant)
toVariantPair Text
"current_file" (OsPath -> ByteString
encodeNullTerminated (OsPath -> ByteString) -> Maybe OsPath -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SaveFileOptions
options.currentFile)
]
parseResponse :: Map Text Variant -> IO SaveFileResults
parseResponse Map Text Variant
resMap = do
OpenFileResults {[OsPath]
$sel:uris:OpenFileResults :: OpenFileResults -> [OsPath]
uris :: [OsPath]
uris, Maybe [ChoiceComboSelection]
$sel:choices:OpenFileResults :: OpenFileResults -> Maybe [ChoiceComboSelection]
choices :: Maybe [ChoiceComboSelection]
choices, Maybe Filter
$sel:currentFilter:OpenFileResults :: OpenFileResults -> Maybe Filter
currentFilter :: Maybe Filter
currentFilter} <- Map Text Variant -> IO OpenFileResults
parseOpenFileResponse Map Text Variant
resMap
SaveFileResults -> IO SaveFileResults
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure SaveFileResults {[OsPath]
$sel:uris:SaveFileResults :: [OsPath]
uris :: [OsPath]
uris, Maybe [ChoiceComboSelection]
$sel:choices:SaveFileResults :: Maybe [ChoiceComboSelection]
choices :: Maybe [ChoiceComboSelection]
choices, Maybe Filter
$sel:currentFilter:SaveFileResults :: Maybe Filter
currentFilter :: Maybe Filter
currentFilter}
parseOpenFileResponse :: Map Text Variant -> IO OpenFileResults
parseOpenFileResponse :: Map Text Variant -> IO OpenFileResults
parseOpenFileResponse = \case
Map Text Variant
resMap
| Just [OsPath]
uris <- [Text] -> Maybe [OsPath]
decodeFileUris ([Text] -> Maybe [OsPath]) -> Maybe [Text] -> Maybe [OsPath]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Variant -> Maybe [Text]
forall a. IsVariant a => Variant -> Maybe a
DBus.fromVariant (Variant -> Maybe [Text]) -> Maybe Variant -> Maybe [Text]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Text -> Map Text Variant -> Maybe Variant
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
"uris" Map Text Variant
resMap,
Just Maybe [(Text, Text)]
choicesRaw <- Text -> Map Text Variant -> Maybe (Maybe [(Text, Text)])
forall a.
IsVariant a =>
Text -> Map Text Variant -> Maybe (Maybe a)
optionalFromVariant Text
"choices" Map Text Variant
resMap,
Maybe [ChoiceComboSelection]
choices <- ((Text, Text) -> ChoiceComboSelection)
-> [(Text, Text)] -> [ChoiceComboSelection]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Text, Text) -> ChoiceComboSelection
decodeChoiceComboSelection ([(Text, Text)] -> [ChoiceComboSelection])
-> Maybe [(Text, Text)] -> Maybe [ChoiceComboSelection]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [(Text, Text)]
choicesRaw,
Just Maybe (Text, [(Word32, Text)])
currentFilterRaw <- Text -> Map Text Variant -> Maybe (Maybe (Text, [(Word32, Text)]))
forall a.
IsVariant a =>
Text -> Map Text Variant -> Maybe (Maybe a)
optionalFromVariant Text
"current_filter" Map Text Variant
resMap,
Just Maybe Filter
currentFilter <- ((Text, [(Word32, Text)]) -> Maybe Filter)
-> Maybe (Text, [(Word32, Text)]) -> Maybe (Maybe Filter)
forall a b. (a -> Maybe b) -> Maybe a -> Maybe (Maybe b)
mapJust (Text, [(Word32, Text)]) -> Maybe Filter
decodeFilter Maybe (Text, [(Word32, Text)])
currentFilterRaw ->
OpenFileResults -> IO OpenFileResults
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure OpenFileResults {[OsPath]
$sel:uris:OpenFileResults :: [OsPath]
uris :: [OsPath]
uris, Maybe [ChoiceComboSelection]
$sel:choices:OpenFileResults :: Maybe [ChoiceComboSelection]
choices :: Maybe [ChoiceComboSelection]
choices, Maybe Filter
$sel:currentFilter:OpenFileResults :: Maybe Filter
currentFilter :: Maybe Filter
currentFilter}
Map Text Variant
resMap ->
ClientError -> IO OpenFileResults
forall e a. Exception e => e -> IO a
throwIO (ClientError -> IO OpenFileResults)
-> (String -> ClientError) -> String -> IO OpenFileResults
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ClientError
DBus.clientError (String -> IO OpenFileResults) -> String -> IO OpenFileResults
forall a b. (a -> b) -> a -> b
$ String
"openFile: could not parse response: " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Map Text Variant -> String
forall a. Show a => a -> String
show Map Text Variant
resMap
encodeFilter :: Filter -> (Text, [(Word32, Text)])
encodeFilter :: Filter -> (Text, [(Word32, Text)])
encodeFilter Filter
filtr =
(Filter
filtr.name, FilterFileType -> (Word32, Text)
encodeFilterFileType (FilterFileType -> (Word32, Text))
-> [FilterFileType] -> [(Word32, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Filter
filtr.fileTypes)
decodeFilter :: (Text, [(Word32, Text)]) -> Maybe Filter
decodeFilter :: (Text, [(Word32, Text)]) -> Maybe Filter
decodeFilter (Text
name, [(Word32, Text)]
rawFileTypes) = do
[FilterFileType]
fileTypes <- ((Word32, Text) -> Maybe FilterFileType)
-> [(Word32, Text)] -> Maybe [FilterFileType]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (Word32, Text) -> Maybe FilterFileType
decodeFileType [(Word32, Text)]
rawFileTypes
Filter -> Maybe Filter
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Filter {Text
$sel:name:Filter :: Text
name :: Text
name, [FilterFileType]
$sel:fileTypes:Filter :: [FilterFileType]
fileTypes :: [FilterFileType]
fileTypes}
encodeFilterFileType :: FilterFileType -> (Word32, Text)
encodeFilterFileType :: FilterFileType -> (Word32, Text)
encodeFilterFileType = \case
GlobFilter Text
pat -> (Word32
0, Text
pat)
MimeFilter Text
mime -> (Word32
1, Text
mime)
decodeFileType :: (Word32, Text) -> Maybe FilterFileType
decodeFileType :: (Word32, Text) -> Maybe FilterFileType
decodeFileType = \case
(Word32
0, Text
pat) -> FilterFileType -> Maybe FilterFileType
forall a. a -> Maybe a
Just (Text -> FilterFileType
GlobFilter Text
pat)
(Word32
1, Text
mime) -> FilterFileType -> Maybe FilterFileType
forall a. a -> Maybe a
Just (Text -> FilterFileType
MimeFilter Text
mime)
(Word32, Text)
_ -> Maybe FilterFileType
forall a. Maybe a
Nothing
encodeCombo :: ChoiceCombo -> (Text, Text, [(Text, Text)], Text)
encodeCombo :: ChoiceCombo -> (Text, Text, [(Text, Text)], Text)
encodeCombo ChoiceCombo
combo =
( ChoiceCombo
combo.id,
ChoiceCombo
combo.label_,
ChoiceComboOption -> (Text, Text)
encodeComboOption (ChoiceComboOption -> (Text, Text))
-> [ChoiceComboOption] -> [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ChoiceCombo
combo.choices,
ChoiceCombo
combo.defaultChoiceId
)
encodeComboOption :: ChoiceComboOption -> (Text, Text)
encodeComboOption :: ChoiceComboOption -> (Text, Text)
encodeComboOption ChoiceComboOption
option =
(ChoiceComboOption
option.id, ChoiceComboOption
option.label_)
decodeChoiceComboSelection :: (Text, Text) -> ChoiceComboSelection
decodeChoiceComboSelection :: (Text, Text) -> ChoiceComboSelection
decodeChoiceComboSelection =
(Text -> Text -> ChoiceComboSelection)
-> (Text, Text) -> ChoiceComboSelection
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Text -> Text -> ChoiceComboSelection
ChoiceComboSelection