Skip to content

Commit

Permalink
make location to store app state configurable
Browse files Browse the repository at this point in the history
and show location in footer
  • Loading branch information
sectore committed Nov 22, 2024
1 parent 34d0b0c commit 10d7995
Show file tree
Hide file tree
Showing 5 changed files with 58 additions and 42 deletions.
4 changes: 2 additions & 2 deletions src/TUI.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ run = do
-- get `Config` from args
config <- getConfig
-- get `TUIStorage` from file
mStorage <- liftIO STG.load
mStorage <- liftIO $ STG.load $ cfgStorageDirectory config
-- out channel to send messages from TUI app
outCh <- newTChanIO
-- in channel to send messages into TUI app
Expand Down Expand Up @@ -80,7 +80,7 @@ run = do
(lastState, _) <- customMainWithInterval interval (Just inCh) (theApp outCh config) initialState

-- persistant parts of `TUIState`
_ <- liftIO $ STG.save (STG.toStorage lastState)
_ <- liftIO $ STG.save (STG.toStorage lastState) (cfgStorageDirectory config)
-- kill threads
killThread foreverId
where
Expand Down
28 changes: 22 additions & 6 deletions src/TUI/Config.hs
Original file line number Diff line number Diff line change
@@ -1,16 +1,21 @@
module TUI.Config where

import Options.Applicative
import System.Directory (
XdgDirectory (..),
getXdgDirectory,
)
import TUI.Types (MempoolUrl (..))

data Config = Config
{ cfgMempoolUrl :: !MempoolUrl
, cfgReloadInterval :: !Int
, cfgStorageDirectory :: !FilePath
}
deriving (Show)

parser :: Parser Config
parser =
parser :: FilePath -> Parser Config
parser defaultStorageDirectory =
Config
<$> ( MempoolUrl
<$> strOption
Expand All @@ -31,14 +36,25 @@ parser =
<> value 180
<> showDefault
)
<*> option
auto
( long "storage"
<> short 's'
<> metavar "DIRECTORY"
<> help "Folder to store application state"
<> value defaultStorageDirectory
<> showDefault
)

getConfig :: IO Config
getConfig = execParser opts
getConfig = do
defaultStorageDirectory <- getXdgDirectory XdgState "tick-tock-tui"
execParser (opts defaultStorageDirectory)
where
opts :: ParserInfo Config
opts =
opts :: FilePath -> ParserInfo Config
opts path =
info
(parser <**> helper)
(parser path <**> helper)
( fullDesc
<> progDesc "TUI app to handle Bitcoin data provided by Mempool: fees, blocks and price converter."
<> header "tick-tock-tui"
Expand Down
31 changes: 11 additions & 20 deletions src/TUI/Storage.hs
Original file line number Diff line number Diff line change
@@ -1,14 +1,12 @@
module TUI.Storage (save, load, toStorage) where
module TUI.Storage (save, load, toStorage, getStoragePath) where

import Brick.Forms (formState)
import qualified Data.Aeson as A
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy as LBS
import Lens.Micro (to, (^.))
import System.Directory (
XdgDirectory (..),
createDirectoryIfMissing,
doesFileExist,
getXdgDirectory,
)
import System.FilePath ((</>))
import TUI.Types
Expand All @@ -28,25 +26,18 @@ toStorage st =
, stgBtcAmount = st ^. converterForm . to formState . cdBTC
}

path :: FilePath -> FilePath
path dir = dir </> "data" <> show stgVersion <> ".json"
getStoragePath :: FilePath -> FilePath
getStoragePath dir = dir </> "data" <> show stgVersion <> ".json"

{- | Path to store data
Note: It uses 'System.Directory.XdgState' to save parts of 'TUIState'
-}
getStorageDirectory :: IO FilePath
getStorageDirectory = getXdgDirectory XdgState "tick-tock-tui"

save :: TUIStorage -> IO ()
save st = do
dir <- getStorageDirectory
save :: TUIStorage -> FilePath -> IO ()
save st dir = do
createDirectoryIfMissing True dir
BL.writeFile (path dir) (A.encode st)
LBS.writeFile (getStoragePath dir) (A.encode st)

load :: IO (Maybe TUIStorage)
load = do
filePath <- path <$> getStorageDirectory
load :: FilePath -> IO (Maybe TUIStorage)
load dir = do
let filePath = getStoragePath dir
exists <- doesFileExist filePath
if exists
then A.decode <$> BL.readFile filePath
then A.decode <$> LBS.readFile filePath
else pure Nothing
4 changes: 2 additions & 2 deletions src/TUI/Widgets/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ import Brick.Types (
import Brick.Widgets.Center
import Brick.Widgets.Core
import Lens.Micro ((^.))
import TUI.Config (Config, cfgMempoolUrl)
import TUI.Config (Config)
import TUI.Types
import TUI.Widgets.Block (drawBlock)
import TUI.Widgets.Converter (drawConverter)
Expand All @@ -26,5 +26,5 @@ drawApp conf st = [padTopBottom 1 ui]
vBox
[ drawHeader st
, hCenter $ vCenter main
, drawFooter st (cfgMempoolUrl conf)
, drawFooter st conf
]
33 changes: 21 additions & 12 deletions src/TUI/Widgets/Footer.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,3 @@
{-# OPTIONS_GHC -Wno-unrecognised-pragmas #-}

{-# HLINT ignore "Move brackets to avoid $" #-}
module TUI.Widgets.Footer where

import Brick.Types (
Expand All @@ -16,6 +13,7 @@ import Brick.Widgets.Core (
padLeft,
padLeftRight,
padRight,
padTop,
str,
txt,
vBox,
Expand All @@ -26,21 +24,24 @@ import Brick.Widgets.Core (
import Brick.Widgets.Table
import Lens.Micro ((^.))
import TUI.Attr (withBold)
import TUI.Config (Config (cfgMempoolUrl, cfgStorageDirectory))
import TUI.Service.Types (Bitcoin (BTC))
import TUI.Storage (getStoragePath)
import TUI.Types (
MempoolUrl (..),
TUIResource (..),
TUIState,
View (..),
animate,
currentView,
extraInfo,
selectedBitcoin,
showMenu,
)
import TUI.Widgets.Countdown (drawCountdown)

drawFooter :: TUIState -> MempoolUrl -> Widget TUIResource
drawFooter st (MempoolUrl url) =
drawFooter :: TUIState -> Config -> Widget TUIResource
drawFooter st config =
vBox $
[ hBox
[ padLeftRight 1 $ str $ "[m]enu " <> if st ^. showMenu then "" else ""
Expand All @@ -56,14 +57,22 @@ drawFooter st (MempoolUrl url) =
columnBorders False $
setDefaultColAlignment AlignLeft $
table
[ [col1 $ str "screens", views]
, [col1 $ str "actions", actions]
, [col1 emptyWidget, actions2]
,
[ col1 $ str "endpoint"
, txt url
( [ [col1 $ str "screens", views]
, [col1 $ str "actions", actions]
, [col1 emptyWidget, actions2]
]
]
++ [ row | st ^. extraInfo, row <-
[
[ padTop (Pad 1) $ col1 $ str "endpoint"
, padTop (Pad 1) $ txt $ unMempoolUrl $ cfgMempoolUrl config
]
,
[ col1 $ str "storage"
, str $ getStoragePath $ cfgStorageDirectory config
]
]
]
)
| st ^. showMenu
]
)
Expand Down

0 comments on commit 10d7995

Please sign in to comment.