Skip to content

Commit

Permalink
💡 Haddock for Services
Browse files Browse the repository at this point in the history
  • Loading branch information
Philipp Middendorf committed Apr 10, 2020
1 parent 19558bd commit a58f31f
Show file tree
Hide file tree
Showing 8 changed files with 86 additions and 25 deletions.
1 change: 1 addition & 0 deletions src/NixManager/Packages/View.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-|
Description: Contains the actual GUI (widgets) for the Packages tab
Contains the actual GUI (widgets) for the Packages tab
-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE FlexibleContexts #-}
Expand Down
16 changes: 14 additions & 2 deletions src/NixManager/Services/Download.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{-|
Description: Contains all functions relating to the service JSON download
Contains all functions relating to the service JSON download
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings #-}
module NixManager.Services.Download
Expand Down Expand Up @@ -45,21 +49,26 @@ import Data.ByteString.Lazy ( ByteString
)
import Codec.Compression.Brotli ( decompress )

-- | When the download finishes, this type contains either an error or the filepath to the downloaded file
type DownloadResult = TextualError FilePath

-- | We regularly check for the current state of the download. Locking is done with this 'MVar'
type DownloadVar = MVar DownloadResult

-- | The current state of the download
data DownloadState = DownloadState {
_sdsVar :: DownloadVar
, _sdsThreadId :: ThreadId
_sdsVar :: DownloadVar -- ^ The mutex to check
, _sdsThreadId :: ThreadId -- ^ The thread we started the download in
}

makeLenses ''DownloadState

-- | Try to decompress the received data (it’s Brotli compressed nowadays)
tryDecompress
:: Response ByteString -> IO (Either SomeException (Response ByteString))
tryDecompress bs = try (pure (decompress <$> bs))

-- | Try to download and decompress the options file
tryDownload :: IO (Either SomeException (Response ByteString))
tryDownload = do
errorOrResponse <- try
Expand All @@ -69,6 +78,7 @@ tryDownload = do
Left e -> pure (Left e)
Right v -> tryDecompress v

-- | Start the download, return its state
start :: IO DownloadState
start = do
resultVar <- newEmptyMVar
Expand All @@ -88,8 +98,10 @@ start = do
(Left ("HTTP error, status code: " <> showText sc))
pure (DownloadState resultVar resultThreadId)

-- | Cancel a started download
cancel :: DownloadState -> IO ()
cancel = killThread . view sdsThreadId

-- | Return the result of the download, maybe
result :: DownloadState -> IO (Maybe DownloadResult)
result = tryTakeMVar . view sdsVar
24 changes: 14 additions & 10 deletions src/NixManager/Services/Event.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{-|
Description: Contains the event type for all events corresponding to the Services tab
Contains the event type for all events corresponding to the Services tab
-}
module NixManager.Services.Event
( Event(..)
)
Expand All @@ -9,14 +13,14 @@ import NixManager.Services.Download ( DownloadState )
import NixManager.Services.State ( State )
import Data.Text ( Text )

data Event = EventDownloadStart
| EventSelected (Maybe Int)
| EventDownloadCheck DownloadState
| EventDownloadStarted DownloadState
| EventDownloadCancel
| EventStateResult State
| EventStateReload
| EventSearchChanged Text
| EventSettingChanged (Endo NixExpr)
| EventCategoryIdxChanged Int
data Event = EventDownloadStart -- ^ Triggered when the user presses the “Start download” button. The next event will be the 'EventDownloadStarted' event.
| EventSelected (Maybe Int) -- ^ Triggered when the current service selection changes
| EventDownloadCheck DownloadState -- ^ Triggered regularly while the download is in progress to check if it’s finished and to “pulse” the progress bar
| EventDownloadStarted DownloadState -- ^ Triggered just after the download has begun
| EventDownloadCancel -- ^ Triggered when the user presses the Cancel button on a running download
| EventStateResult State -- ^ Triggered when the download has finished and the results are in
| EventStateReload -- ^ This is triggered externally whenever we need to reload the cache. For example, when the download has finished.
| EventSearchChanged Text -- ^ Triggered when the search string changes
| EventSettingChanged (Endo NixExpr) -- ^ Triggered whenever we change a service setting. Contains an endomorphism that changes the service Nix expression
| EventCategoryIdxChanged Int -- ^ Triggered when the service category combobox changes

10 changes: 10 additions & 0 deletions src/NixManager/Services/ServiceCategory.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
{-|
Description: Contains the service category comboxbox values
Contains the service category comboxbox values
-}
{-# LANGUAGE OverloadedStrings #-}
module NixManager.Services.ServiceCategory
( ServiceCategory(..)
Expand All @@ -15,30 +20,35 @@ import Control.Lens ( Iso'
)
import Data.List ( elemIndex )

-- | All values for the service category combobox
data ServiceCategory = ServiceCategoryServices
| ServiceCategoryHardware
| ServiceCategoryPrograms
| ServiceCategoryBoot
| ServiceCategoryNix
deriving(Enum, Bounded, Eq)

-- | Prettyprint the category
categoryToText :: ServiceCategory -> Text
categoryToText ServiceCategoryServices = "Services"
categoryToText ServiceCategoryPrograms = "Programs"
categoryToText ServiceCategoryHardware = "Hardware"
categoryToText ServiceCategoryBoot = "Boot"
categoryToText ServiceCategoryNix = "Nix"

-- | Conver a category to its option prefix
categoryToNixPrefix :: ServiceCategory -> Text
categoryToNixPrefix ServiceCategoryServices = "services"
categoryToNixPrefix ServiceCategoryPrograms = "programs"
categoryToNixPrefix ServiceCategoryHardware = "hardware"
categoryToNixPrefix ServiceCategoryBoot = "boot"
categoryToNixPrefix ServiceCategoryNix = "nix"

-- | List of all the service categories
serviceCategories :: [ServiceCategory]
serviceCategories = [minBound .. maxBound]

-- | Isomorphism between a category and its index in the list of all categories (needed for the combobox logic)
serviceCategoryIdx :: Iso' ServiceCategory Int
serviceCategoryIdx =
iso (fromJust . (`elemIndex` serviceCategories)) (serviceCategories !!)
17 changes: 11 additions & 6 deletions src/NixManager/Services/State.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,6 @@
{-|
Description: Contains all the state for the Services tab
-}
{-# LANGUAGE TemplateHaskell #-}
module NixManager.Services.State
( State(StateInvalidExpr, StateDownloading, StateDone, StateInvalidOptions)
Expand Down Expand Up @@ -26,21 +29,23 @@ import NixManager.NixService ( makeServices
)
import NixManager.Util ( TextualError )

-- | This contains the all data for the state “we’re currently downloading the services file”
data StateDownloadingData = StateDownloadingData {
_sddCounter :: Int
, _sddVar :: DownloadState
_sddCounter :: Int -- ^ This field is necessary to “pulse” the GTK progress bar while building, see "NixManager.View.ProgressBar" for details
, _sddVar :: DownloadState -- ^ The actual download state
}

makeLenses ''StateDownloadingData

data State = StateInvalidOptions (Maybe Text)
| StateInvalidExpr Text
| StateDownloading StateDownloadingData
| StateDone StateData
data State = StateInvalidOptions (Maybe Text) -- ^ Parsing the service options file failed for some reason
| StateInvalidExpr Text -- ^ Parsing the services Nix expression failed for some reason
| StateDownloading StateDownloadingData -- ^ We’re currently downloading the options file
| StateDone StateData -- ^ We have a valid options file

makePrisms ''State

-- FIXME: Better happy path
-- | The initial Services tab state (needs to read the options file changes, hence the side-effect)
initState :: IO State
initState = do
optionsFile' <- locateOptionsFile
Expand Down
16 changes: 11 additions & 5 deletions src/NixManager/Services/StateData.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
{-|
Description: Contains the service tab data, assuming we have successfully read the options JSON File
Contains the service tab data, assuming we have successfully read the options JSON File
-}
{-# LANGUAGE TemplateHaskell #-}
module NixManager.Services.StateData
( StateData(StateData)
Expand All @@ -14,12 +19,13 @@ import NixManager.NixExpr ( NixExpr )
import Control.Lens ( makeLenses )
import Data.Text ( Text )

-- | Contains the service tab data, assuming we have successfully read the options JSON File
data StateData = StateData {
_sdCache :: [NixService]
, _sdSelectedIdx :: Maybe Int
, _sdExpression :: NixExpr
, _sdSearchString :: Text
, _sdCategoryIdx :: Int
_sdCache :: [NixService] -- ^ The list of all services
, _sdSelectedIdx :: Maybe Int -- ^ The currently selected service in the list
, _sdExpression :: NixExpr -- ^ The current service expression
, _sdSearchString :: Text -- ^ The current service search string
, _sdCategoryIdx :: Int -- ^ The currently selected service category, see "NixManager.Services.ServiceCategory"
}

makeLenses ''StateData
5 changes: 5 additions & 0 deletions src/NixManager/Services/Update.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{-|
Description: Contains the update logic for the Services tab
Contains the update logic for the Services tab
-}
module NixManager.Services.Update
( updateEvent
)
Expand Down Expand Up @@ -60,6 +64,7 @@ import Prelude hiding ( length
)


-- | The actual update function
updateEvent :: ManagerState -> Event -> Transition ManagerState ManagerEvent
updateEvent s EventDownloadStart =
Transition s (servicesEvent . EventDownloadStarted <$> ServiceDownload.start)
Expand Down
22 changes: 20 additions & 2 deletions src/NixManager/Services/View.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{-|
Description: Contains the actual GUI (widgets) for the services tab
Contains the actual GUI (widgets) for the services tab
-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
Expand Down Expand Up @@ -164,7 +168,7 @@ import NixManager.NixServiceOptionType
)
)


-- | Create a list box row widget from a service
buildServiceRow
:: FromWidget (Bin Gtk.ListBoxRow) target => NixService -> target event
buildServiceRow svc =
Expand All @@ -175,6 +179,7 @@ buildServiceRow svc =
[]
(widget Gtk.Label [#label := markedUp, #useMarkup := True])

-- | Handles a row selection event
rowSelectionHandler :: Maybe Gtk.ListBoxRow -> Gtk.ListBox -> IO ManagerEvent
rowSelectionHandler (Just row) _ = do
selectedIndex <- Gtk.listBoxRowGetIndex row
Expand All @@ -187,9 +192,11 @@ rowSelectionHandler (Just row) _ = do
)
rowSelectionHandler _ _ = pure (ManagerEventServices (EventSelected Nothing))

-- | Check if a service matches a cateogry
categoryMatches :: ServiceCategory -> NixLocation -> Bool
categoryMatches c loc = categoryToNixPrefix c == firstComponent loc

-- | We need to filter some option categories, for example something like @service.<name>.bar@ or @service.*.bar@. At least until we can handle that, too.
filterPredicate :: StateData -> NixService -> Bool
filterPredicate sd =
( (((sd ^. sdSearchString) `isInfixOf`) . flattenLocation)
Expand All @@ -200,12 +207,13 @@ filterPredicate sd =
. view serviceLoc


-- | The list of service rows (the left half of the tab, minus the search)
serviceRows :: StateData -> Vector.Vector (Bin Gtk.ListBoxRow event)
serviceRows sd = toVectorOf
(sdCache . folded . filtered (filterPredicate sd) . to buildServiceRow)
sd


-- | The left half of the tab
servicesLeftPane sd _ =
let searchField = widget
Gtk.SearchEntry
Expand Down Expand Up @@ -239,9 +247,11 @@ servicesLeftPane sd _ =
, BoxChild expandAndFill $ bin Gtk.ScrolledWindow [] serviceList
]

-- | Given an option path, return a traversal for the corresponding attribute set element
optionLens' :: Text -> Traversal' NixExpr (Maybe NixExpr)
optionLens' optionPath = _NixFunctionDecl . nfExpr . _NixSet . at optionPath

-- | Given the whole services Nix expression and a concrete service option, construct the edit widget for that option. This does some case analysis on the type.
buildOptionValueCell :: NixExpr -> NixServiceOption -> Widget ManagerEvent
buildOptionValueCell serviceExpression serviceOption =
let
Expand Down Expand Up @@ -323,11 +333,13 @@ buildOptionValueCell serviceExpression serviceOption =
]
]

-- | Convert the docbook documentation markup to GTK (pango) markup
convertMarkup :: Text -> Text
convertMarkup t = case parseDocbook t of
Left e -> "error parsing description: " <> e
Right v -> docbookToPango v

-- | Build all the option rows for a selected service, given the whole services Nix expression
buildOptionRows :: NixExpr -> NixServiceOption -> BoxChild ManagerEvent
buildOptionRows serviceExpression serviceOption =
let
Expand Down Expand Up @@ -362,6 +374,7 @@ buildOptionRows serviceExpression serviceOption =
in
BoxChild defaultBoxChildProperties rootBox

-- | The right half of the services tab
servicesRightPane
:: ( FromWidget (SingleWidget Gtk.Label) target
, FromWidget (Bin Gtk.ScrolledWindow) target
Expand Down Expand Up @@ -401,19 +414,23 @@ servicesBox s = container
[]
[BoxChild expandAndFill (servicesBox' (s ^. msServiceState) s)]

-- | What to display when the service definitions couldn't be parsed
invalidOptionsMessage :: Maybe Text -> Text
invalidOptionsMessage (Just e) =
"Service definition file is invalid, possibly because of a corrupt download. You should try again. The error is:\n\n"
<> e
invalidOptionsMessage Nothing =
"Service definitions need to be downloaded first.\nPress the button below to start the download. It'll only take a few seconds, depending on your internet speed."

-- | The icon to display in case the service definitions aren't there or invalid
invalidOptionsIcon (Just _) = IconName.DialogError
invalidOptionsIcon Nothing = IconName.EmblemDocuments

-- | The button text to display in case the service definitions aren't there or invalid
invalidOptionsButtonText (Just _) = "Retry Download"
invalidOptionsButtonText Nothing = "Start Download"

-- | General function to display the notice box in case the service definitions aren't there or are invalid
noticeBox icon buttonEvent buttonIcon buttonText message = container
Gtk.Box
[ #orientation := Gtk.OrientationVertical
Expand All @@ -438,6 +455,7 @@ noticeBox icon buttonEvent buttonIcon buttonText message = container
)
]

-- | The while services tab
servicesBox' (StateDownloading ssdd) _ = container
Gtk.Box
[ #orientation := Gtk.OrientationVertical
Expand Down

0 comments on commit a58f31f

Please sign in to comment.