Skip to content

Commit

Permalink
Finished UI
Browse files Browse the repository at this point in the history
  • Loading branch information
sigrdrifa committed Dec 1, 2023
1 parent ba0f437 commit f523d21
Show file tree
Hide file tree
Showing 13 changed files with 1,544 additions and 490 deletions.
1 change: 1 addition & 0 deletions audiocate.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,7 @@ executable audiocate-gui
other-modules:
MainWindow
, View.EncodeView
, View.DecodeView
, View.LoadView
, AppState
default-language: GHC2021
Expand Down
1,236 changes: 823 additions & 413 deletions csrc/resources.c

Large diffs are not rendered by default.

10 changes: 4 additions & 6 deletions gui/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,12 +6,10 @@ where

import Audiocate (version)
import Control.Monad (void)
import GI.Adw qualified as Adw
import qualified GI.Adw as Adw
import System.Environment (getArgs, getProgName)
import MainWindow (initMainWindow, MainWindow (window))
import Data.Audio.Wave (WaveAudio)
import Control.Concurrent (newEmptyMVar, MVar)
import AppState (AppState (..), newAppState)
import AppState (newAppState)


activate :: Adw.Application -> IO ()
Expand All @@ -27,8 +25,8 @@ main = do
[ #applicationId Adw.:= "eldr-io.audiocate.gui",
Adw.On #activate (activate ?self)
]
sm <- Adw.getApplicationStyleManager app
Adw.setStyleManagerColorScheme sm Adw.ColorSchemeForceLight
-- sm <- Adw.getApplicationStyleManager app
-- Adw.setStyleManagerColorScheme sm Adw.ColorSchemeForceLight
putStrLn $ "Audiocate GUI v" ++ version
args <- getArgs
progName <- getProgName
Expand Down
101 changes: 61 additions & 40 deletions gui/MainWindow.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,84 +2,105 @@ module MainWindow where

import AppState (AppState)
import Audiocate (version)
import Data.Text qualified as T
import GI.Adw (AttrOp ((:=)), new)
import GI.Adw qualified as Adw
import GI.Gtk qualified as Gtk
import View.EncodeView (EncodeView (..), initEncodeView, updateEncodeViewAudioFileLoaded)
import View.LoadView (LoadView (..), initLoadView)
import Control.Concurrent (newEmptyMVar, forkIO, takeMVar, MVar)
import Control.Concurrent (MVar, forkIO, newEmptyMVar, takeMVar, putMVar)
import Control.Monad (forever)

data MainWindow = MainWindow
{ application :: !Adw.Application
, appState :: AppState
, toastOverlay :: !Adw.ToastOverlay
, window :: !Adw.ApplicationWindow
, encodeView :: !EncodeView
, loadView :: !LoadView
}
import qualified Data.Text as T
import GI.Adw (AttrOp((:=)), new)
import qualified GI.Adw as Adw
import qualified GI.Gtk as Gtk
import View.DecodeView
( DecodeView(..)
, initDecodeView
, updateDecodeViewAudioFileLoaded
)
import View.EncodeView
( EncodeView(..)
, initEncodeView
, updateEncodeViewAudioFileLoaded
)
import View.LoadView (LoadView(..), initLoadView)

data MainWindow =
MainWindow
{ application :: !Adw.Application
, appState :: AppState
, toastOverlay :: !Adw.ToastOverlay
, window :: !Adw.ApplicationWindow
, encodeView :: !EncodeView
, decodeView :: !DecodeView
, loadView :: !LoadView
}

updateEncodeViewFileLoad :: MVar Bool -> AppState -> EncodeView -> IO ()
updateEncodeViewFileLoad fileLoadedMVar state encodeView = do
_ <- takeMVar fileLoadedMVar
updateEncodeViewAudioFileLoaded state encodeView
putMVar fileLoadedMVar True

updateDecodeViewFileLoad :: MVar Bool -> AppState -> DecodeView -> IO ()
updateDecodeViewFileLoad fileLoadedMVar state decodeView = do
_ <- takeMVar fileLoadedMVar
updateDecodeViewAudioFileLoaded state decodeView

initMainWindow :: Adw.Application -> AppState -> IO MainWindow
initMainWindow app state = do
content <- new Gtk.Box [#orientation := Gtk.OrientationVertical]
overlay <- new Adw.ToastOverlay [#child := content]
stack <- new Adw.ViewStack [#hexpand := True]

window <-
new
Adw.ApplicationWindow
[ #application := app
, #content := overlay
, #defaultWidth := 1220
, #defaultHeight := 760
, #defaultHeight := 800
]

label1 <- new Gtk.Label [#label := "Decode", #hexpand := True]

let welcomeTitle = "Audiocate " <> version

encodeView <- initEncodeView state overlay
let encViewBox = encodeViewBox encodeView

decodeView <- initDecodeView state overlay
let decViewBox = decodeViewBox decodeView
fileLoadedMVar <- newEmptyMVar

_ <- forkIO (forever $ updateEncodeViewFileLoad fileLoadedMVar state encodeView)

_ <-
forkIO (forever $ updateEncodeViewFileLoad fileLoadedMVar state encodeView)
_ <-
forkIO (forever $ updateDecodeViewFileLoad fileLoadedMVar state decodeView)
loadView <- initLoadView window state overlay fileLoadedMVar
let lViewBox = loadViewBox loadView

welcomePage <-
new
Adw.StatusPage
[ #iconName := "org.gnome.Adwaita1.Demo"
, #title := T.pack welcomeTitle
, #description
:= "Audio encoding authentication and "
<> "validation library for verifying audio as being from a trusted source"
, #description := "Audio encoding authentication and " <>
"validation library for verifying audio as being from a trusted source"
, #child := lViewBox
]

Adw.viewStackAddTitledWithIcon stack welcomePage (Just "welcome-page") "Load" "audio-x-generic"

Adw.viewStackAddTitledWithIcon stack encViewBox (Just "encode-page") "Encode" "mail-send-symbolic"
Adw.viewStackAddTitledWithIcon stack label1 (Just "decode-page") "Decode" "mail-send-symbolic"

Adw.viewStackAddTitledWithIcon
stack
welcomePage
(Just "welcome-page")
"Load"
"audio-x-generic"
Adw.viewStackAddTitledWithIcon
stack
encViewBox
(Just "encode-page")
"Encode"
"mail-send-symbolic"
Adw.viewStackAddTitledWithIcon
stack
decViewBox
(Just "decode-page")
"Decode"
"mail-send-symbolic"
viewSwitcherBar <- new Adw.ViewSwitcherBar [#stack := stack]
viewSwitcherTitle <- new Adw.ViewSwitcherTitle [#stack := stack]
headerBar <- new Adw.HeaderBar [#titleWidget := viewSwitcherTitle]

menuBtn <- new Gtk.Button [#iconName := "open-menu-symbolic"]
Adw.headerBarPackStart headerBar menuBtn

content.append headerBar
content.append stack
content.append viewSwitcherBar

let mw = MainWindow app state overlay window encodeView loadView
let mw = MainWindow app state overlay window encodeView decodeView loadView
pure mw
Loading

0 comments on commit f523d21

Please sign in to comment.