{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
module Zenity
( Text
, Default (..)
, Config (..)
, CalendarFlags (..)
, EntryFlags (..)
, FileSelectionFlags (..)
, InfoFlags (..)
, ReturnedColumns (..)
, ListFlags (..)
, SelectionHeader (..)
, ListType (..)
, radio
, check
, Matrix (..)
, Dialog (..)
, zenity
, keyedList
) where
import Control.Monad (void, when)
import Control.Monad.Fail (MonadFail)
import Data.Bool (bool)
import Data.Default (Default (..))
import Data.String (IsString)
import Data.Text (Text)
import Data.Time.Calendar (Day)
import Data.Time.Format (defaultTimeLocale, parseTimeM)
import qualified Data.Text as Text
import Data.Word (Word)
import qualified System.Process.Text as Text
import System.Process (showCommandForUser)
chunk :: Int -> [a] -> [[a]]
chunk n as
| n >= 1 = go (length as) as
| otherwise = error "chunk: chunk size must be >= 1"
where
go l bs
| l <= n = [bs]
| otherwise = take n bs : go (l - n) (drop n bs)
data Config = Config
{ title :: Maybe Text
, windowIcon :: Maybe FilePath
, width :: Maybe Int
, height :: Maybe Int
, timeout :: Maybe Int
}
instance Default Config where
def = Config
{ title = Nothing
, windowIcon = Nothing
, width = Nothing
, height = Nothing
, timeout = Nothing
}
data CmdFlag where
CmdFlag
:: { _flagName :: String
, _flagField :: Maybe a
, _flagParam :: a -> String}
-> CmdFlag
cmdFlag :: CmdFlag -> [String]
cmdFlag (CmdFlag flag fld mkParam) = maybe [] (\f -> [flag, mkParam f]) fld
configFlags :: Config -> [String]
configFlags Config {..} =
concatMap
cmdFlag
[ CmdFlag "--title" title Text.unpack
, CmdFlag "--window-icon" windowIcon id
, CmdFlag "--width" width show
, CmdFlag "--height" height show
, CmdFlag "--timeout" timeout show
]
class CmdParam p where
serializeParam :: p -> [String]
boolParam :: Bool -> String -> [String]
boolParam param flag = bool [] [flag] param
maybeParam :: Maybe a -> (a -> [String]) -> [String]
maybeParam = flip $ maybe []
data CalendarFlags = CalendarFlags
{ text :: Maybe Text
, year :: Maybe Word
, month :: Maybe Word
, day :: Maybe Word
} deriving (Eq, Show)
instance Default CalendarFlags where
def = CalendarFlags Nothing Nothing Nothing Nothing
instance CmdParam CalendarFlags where
serializeParam CalendarFlags {..} = concat
[ maybeParam text $ \t -> ["--text", Text.unpack t]
, maybeParam year $ \y -> ["--year", show y]
, maybeParam month $ \m -> ["--month", show m]
, maybeParam day $ \d -> ["--day", show d]
]
data EntryFlags = EntryFlags
{ text :: Maybe Text
, entryText :: Maybe Text
, hideText :: Bool
} deriving (Eq, Show)
instance Default EntryFlags where
def = EntryFlags Nothing Nothing False
instance CmdParam EntryFlags where
serializeParam EntryFlags {..} = concat
[ maybeParam text $ \t -> ["--text", Text.unpack t]
, maybeParam entryText $ \t -> ["--entry-text", Text.unpack t]
, boolParam hideText "--hide-text"
]
data FileSelectionFlags = FileSelectionFlags
{ fileName :: Maybe FilePath
, directory :: Bool
, save :: Bool
, confirmOverwrite :: Bool
} deriving (Eq, Show)
instance Default FileSelectionFlags where
def = FileSelectionFlags Nothing False False False
instance CmdParam FileSelectionFlags where
serializeParam FileSelectionFlags {..} = concat
[ maybeParam fileName $ \f -> ["--filename", f]
, boolParam directory "--directory"
, boolParam save "--save"
, boolParam confirmOverwrite "--confirm-overwrite"
]
data InfoFlags = InfoFlags
{ text :: Maybe Text
, noWrap :: Bool
, noMarkup :: Bool
} deriving (Eq, Show)
instance Default InfoFlags where
def = InfoFlags Nothing False False
instance CmdParam InfoFlags where
serializeParam InfoFlags {..} = concat
[ maybeParam text $ \t -> ["--text", Text.unpack t]
, boolParam noWrap "--no-wrap"
, boolParam noMarkup "--no-markup"
]
data ReturnedColumns a
= All
| Col a
deriving (Eq, Show, Functor)
data ListFlags = ListFlags
{ text :: Maybe Text
, editable :: Bool
, returnColumn :: ReturnedColumns Word
, hideColumn :: Maybe Word
, hideHeader :: Bool
} deriving (Eq, Show)
instance Default ListFlags where
def = ListFlags Nothing False (Col 1) Nothing False
instance CmdParam ListFlags where
serializeParam ListFlags {..} = concat
[ maybeParam text $ \t -> ["--text", Text.unpack t]
, boolParam editable "--editable"
, case returnColumn of
All -> ["--print-column", "ALL"]
Col c -> ["--print-column", show c]
, maybeParam hideColumn $ \c -> ["--hide-column", show c]
, boolParam hideHeader "--hide-header"
]
shiftColumns :: ListFlags -> ListFlags
shiftColumns ListFlags {..} = ListFlags
{ returnColumn = fmap shift returnColumn
, hideColumn = fmap shift hideColumn
, ..
}
where
shift 0 = 0
shift c = c+1
newtype SelectionHeader = SelectionHeader {unSelectionHeader :: Text}
deriving (Eq, Show, IsString)
data ListType a where
Single :: ListType (Maybe Text)
Multi :: ListType [Text]
Radio :: SelectionHeader -> ListType (Maybe Text)
Check :: SelectionHeader -> ListType [Text]
deriving instance Eq (ListType a)
deriving instance Show (ListType a)
radio :: ListType (Maybe Text)
radio = Radio ""
check :: ListType [Text]
check = Check ""
data Matrix = Matrix
{ headers :: [Text]
, rows :: [[Text]]
} deriving (Eq, Show)
matrixWidth :: Matrix -> Int
matrixWidth Matrix {..} = max (length headers) (maximum $ 1 : map length rows)
fixMatrix :: Matrix -> Matrix
fixMatrix mat@Matrix {..} = Matrix
{ headers = widen $ if null headers then [""] else headers
, rows = map widen $ if null rows then [[]] else rows
}
where
width = matrixWidth mat
widen as = as ++ replicate n ""
where
n = width - length as
addSelectionColumn :: SelectionHeader -> Matrix -> Matrix
addSelectionColumn hdr mat = Matrix
{ headers = unSelectionHeader hdr : headers
, rows = map ("" :) rows
}
where
Matrix {..} = fixMatrix mat
matrixFlags :: Matrix -> [String]
matrixFlags mat = concat
[ concatMap (\hdr -> ["--column", Text.unpack hdr]) headers
, concatMap (map (map convertNewline . Text.unpack)) rows
]
where
Matrix {..} = fixMatrix mat
convertNewline '\n' = ' '
convertNewline c = c
data Dialog a where
Calendar :: CalendarFlags -> Dialog (Maybe Day)
Entry :: EntryFlags -> Dialog (Maybe Text)
Error :: InfoFlags -> Dialog ()
FileSelection :: FileSelectionFlags -> Dialog (Maybe FilePath)
MultiFileSelection :: FileSelectionFlags -> Dialog [FilePath]
Info :: InfoFlags -> Dialog ()
List :: ListType a -> ListFlags -> Matrix -> Dialog a
Notification :: InfoFlags -> Dialog ()
Warning :: InfoFlags -> Dialog ()
callZenity ::
Config
-> [String]
-> IO Text
callZenity cfg flags = do
when False $ putStrLn $ showCommandForUser "zenity" flags'
(\(_, o, _) -> o) <$> Text.readProcessWithExitCode "zenity" flags' ""
where
flags' = configFlags cfg ++ flags
parseResult :: Text -> Maybe Text
parseResult "" = Nothing
parseResult t = Just $ Text.dropWhileEnd (== '\n') t
dateFormat = "%Y-%m-%d"
readDay :: MonadFail m => Text -> m Day
readDay = parseTimeM False defaultTimeLocale dateFormat . Text.unpack
unconcat ::
ListFlags
-> Matrix
-> [Text]
-> [Text]
unconcat ListFlags {..} mat
| All <- returnColumn =
map (Text.dropEnd 1 . Text.unlines) . chunk (matrixWidth mat)
| otherwise = id
zenity :: Config -> Dialog a -> IO a
zenity cfg (Calendar flags) =
traverse readDay . parseResult =<<
callZenity
cfg
("--calendar" : ("--date-format=" ++ dateFormat) : serializeParam flags)
zenity cfg (Entry flags) =
fmap parseResult $ callZenity cfg ("--entry" : serializeParam flags)
zenity cfg (Error flags) =
void $ callZenity cfg $ "--error" : serializeParam flags
zenity cfg (FileSelection flags) =
fmap (fmap Text.unpack . parseResult) $
callZenity cfg $ "--file-selection" : serializeParam flags
zenity cfg (MultiFileSelection flags) =
fmap (lines . Text.unpack) $
callZenity cfg $
"--file-selection" :
"--multiple" : "--separator" : "\n" : serializeParam flags
zenity cfg (Info flags) =
void $ callZenity cfg $ "--info" : serializeParam flags
zenity cfg (List Single flags mat) =
fmap parseResult $
callZenity cfg $
"--list" : "--separator" : "\n" : serializeParam flags ++ matrixFlags mat
zenity cfg (List Multi flags mat) =
fmap (unconcat flags mat . Text.lines) $
callZenity cfg $
"--list" :
"--separator" : "\n" : "--multiple" : serializeParam flags ++ matrixFlags mat
zenity cfg (List (Radio h) flags mat) =
fmap parseResult $
callZenity cfg $
"--list" :
"--separator" :
"\n" :
"--radiolist" :
serializeParam (shiftColumns flags) ++ matrixFlags (addSelectionColumn h mat)
zenity cfg (List (Check h) flags mat) =
fmap (unconcat flags mat . Text.lines) $
callZenity cfg $
"--list" :
"--separator" :
"\n" :
"--checklist" :
serializeParam (shiftColumns flags) ++ matrixFlags (addSelectionColumn h mat)
zenity cfg (Notification flags) =
void $ callZenity cfg $ "--notification" : serializeParam flags'
where
flags' = flags {noWrap = False, noMarkup = False}
zenity cfg (Warning flags) =
void $ callZenity cfg $ "--warning" : serializeParam flags
keyedList ::
(Show a, Read a, Functor f)
=> Config
-> ListType (f Text)
-> ListFlags
-> Text
-> [(a, Text)]
-> IO (f a)
keyedList cfg ltype flags hd as =
fmap (fmap (read . Text.unpack)) $
zenity cfg $
List ltype flags {returnColumn = Col 1, hideColumn = Just 1} $
Matrix
{headers = ["", hd], rows = [[Text.pack (show a), txt] | (a, txt) <- as]}