diff options
| -rw-r--r-- | webgui/src/Main.hs | 67 | ||||
| -rw-r--r-- | webgui/thermoprint-webgui.cabal | 5 | ||||
| -rw-r--r-- | webgui/thermoprint-webgui.nix | 10 |
3 files changed, 66 insertions, 16 deletions
diff --git a/webgui/src/Main.hs b/webgui/src/Main.hs index d96083e..7ead572 100644 --- a/webgui/src/Main.hs +++ b/webgui/src/Main.hs | |||
| @@ -1,9 +1,16 @@ | |||
| 1 | {-# LANGUAGE RecordWildCards #-} | ||
| 2 | {-# LANGUAGE ViewPatterns #-} | ||
| 3 | |||
| 1 | module Main (main) where | 4 | module Main (main) where |
| 2 | 5 | ||
| 3 | import qualified Graphics.UI.Threepenny as UI | 6 | import qualified Graphics.UI.Threepenny as UI |
| 4 | import Graphics.UI.Threepenny.Core | 7 | import qualified Graphics.UI.Threepenny.Core as TP (Config) |
| 8 | import Graphics.UI.Threepenny.Core hiding (Config) | ||
| 5 | 9 | ||
| 6 | import Thermoprint.Client | 10 | import Thermoprint.Client |
| 11 | import Network.WebSockets | ||
| 12 | import Network.Socket (withSocketsDo) | ||
| 13 | import Network.URI | ||
| 7 | 14 | ||
| 8 | import qualified Options.Applicative as Opt | 15 | import qualified Options.Applicative as Opt |
| 9 | import System.Environment | 16 | import System.Environment |
| @@ -12,14 +19,26 @@ import Data.ByteString (ByteString) | |||
| 12 | import qualified Data.ByteString as BS | 19 | import qualified Data.ByteString as BS |
| 13 | import qualified Data.ByteString.Char8 as CBS | 20 | import qualified Data.ByteString.Char8 as CBS |
| 14 | 21 | ||
| 22 | import Data.Text (Text) | ||
| 23 | import qualified Data.Text as T | ||
| 24 | |||
| 25 | import Control.Concurrent | ||
| 26 | import Control.Exception | ||
| 27 | import Control.Monad.Catch | ||
| 28 | |||
| 15 | import Control.Applicative | 29 | import Control.Applicative |
| 16 | import Control.Monad | 30 | import Control.Monad |
| 17 | import Data.Maybe | 31 | import Data.Maybe |
| 18 | import Data.Monoid | 32 | import Data.Monoid |
| 19 | import Text.Read | 33 | import Text.Read |
| 20 | 34 | ||
| 35 | data Config = Config | ||
| 36 | { tpConfig :: TP.Config | ||
| 37 | , server :: BaseUrl | ||
| 38 | } | ||
| 39 | |||
| 21 | main :: IO () | 40 | main :: IO () |
| 22 | main = config >>= Opt.execParser . opts >>= flip startGUI setup | 41 | main = withSocketsDo $ config >>= Opt.execParser . opts >>= (\c -> startGUI (tpConfig c) $ (withWebSocket setup) c) |
| 23 | where | 42 | where |
| 24 | opts config = Opt.info (Opt.helper <*> config) | 43 | opts config = Opt.info (Opt.helper <*> config) |
| 25 | ( Opt.fullDesc | 44 | ( Opt.fullDesc |
| @@ -30,9 +49,11 @@ config :: IO (Opt.Parser Config) | |||
| 30 | config = do | 49 | config = do |
| 31 | p <- fromMaybe 8023 . (readMaybe =<<) <$> lookupEnv portEnv | 50 | p <- fromMaybe 8023 . (readMaybe =<<) <$> lookupEnv portEnv |
| 32 | a <- fromMaybe "localhost" <$> lookupEnv hostEnv | 51 | a <- fromMaybe "localhost" <$> lookupEnv hostEnv |
| 33 | return $ (\port addr -> defaultConfig { jsPort = port, jsAddr = addr }) | 52 | return $ Config <$> ((\port addr -> defaultConfig { jsPort = port, jsAddr = addr }) <$> optional (Opt.option Opt.auto $ port p) <*> optional (fmap CBS.pack $ Opt.strOption $ addr a)) |
| 34 | <$> optional (Opt.option Opt.auto $ port p) | 53 | <*> (BaseUrl Http |
| 35 | <*> optional (fmap CBS.pack $ Opt.strOption $ addr a) | 54 | <$> Opt.strOption (Opt.long "target-addr" <> Opt.short 'A' <> Opt.metavar "HOST" <> Opt.help "Host to connect to" <> Opt.value "localhost" <> Opt.showDefault) |
| 55 | <*> Opt.option Opt.auto (Opt.long "target-port" <> Opt.short 'P' <> Opt.metavar "PORT" <> Opt.help "Port to connect to" <> Opt.value 3000 <> Opt.showDefault) | ||
| 56 | ) | ||
| 36 | where | 57 | where |
| 37 | port def = Opt.long "port" | 58 | port def = Opt.long "port" |
| 38 | <> Opt.short 'p' | 59 | <> Opt.short 'p' |
| @@ -49,8 +70,10 @@ config = do | |||
| 49 | hostEnv = "ADDR" | 70 | hostEnv = "ADDR" |
| 50 | portEnv = "PORT" | 71 | portEnv = "PORT" |
| 51 | 72 | ||
| 52 | setup :: Window -> UI () | 73 | setup :: Config -> Window -> Event (Either WebSocketException URI) -> UI () |
| 53 | setup window = void $ do | 74 | setup Config{..} window (split -> (socketErr, dataUpdate)) = void $ do |
| 75 | onEvent socketErr handleSocketErr | ||
| 76 | |||
| 54 | return window # set UI.title "Thermoprint" | 77 | return window # set UI.title "Thermoprint" |
| 55 | 78 | ||
| 56 | title <- UI.input | 79 | title <- UI.input |
| @@ -64,11 +87,11 @@ setup window = void $ do | |||
| 64 | prntBtn <- UI.button #+ [string "Print"] | 87 | prntBtn <- UI.button #+ [string "Print"] |
| 65 | 88 | ||
| 66 | getBody window #+ [ row [ column [ UI.h1 #+ [string "Current draft"] | 89 | getBody window #+ [ row [ column [ UI.h1 #+ [string "Current draft"] |
| 67 | , row [UI.label # set text "Title" # set UI.for "title", element title] | 90 | , row [UI.label # set text "Title" # set UI.for "title", element title # set style [("width", "100%")]] |
| 68 | , element content | 91 | , element content # set style [("width", "100%")] |
| 69 | , row [ element saveBtn | 92 | , row [ element saveBtn # set style [("width", "100%")] |
| 70 | , element prntBtn | 93 | , element prntBtn # set style [("width", "100%")] |
| 71 | , element discBtn | 94 | , element discBtn # set style [("width", "100%")] |
| 72 | ] | 95 | ] |
| 73 | ] | 96 | ] |
| 74 | , column [ UI.h1 #+ [string "Saved drafts"] | 97 | , column [ UI.h1 #+ [string "Saved drafts"] |
| @@ -76,3 +99,23 @@ setup window = void $ do | |||
| 76 | ] | 99 | ] |
| 77 | ] | 100 | ] |
| 78 | ] | 101 | ] |
| 102 | |||
| 103 | where | ||
| 104 | handleSocketErr InvalidMessage = debug "Received unparseable message from websocket" | ||
| 105 | handleSocketErr e@(UnknownException e') = void $ do | ||
| 106 | getBody window #+ [UI.p # set text (show e') # set UI.id_ "error"] | ||
| 107 | liftIO $ throwIO e | ||
| 108 | |||
| 109 | data WebSocketException = InvalidMessage | UnknownException SomeException | ||
| 110 | deriving (Show) | ||
| 111 | |||
| 112 | instance Exception WebSocketException | ||
| 113 | |||
| 114 | withWebSocket :: (Config -> Window -> Event (Either WebSocketException URI) -> UI void) -> Config -> Window -> UI () | ||
| 115 | withWebSocket setup c@(Config{..}) w = do | ||
| 116 | (dataUpdate, triggerData) <- liftIO newEvent | ||
| 117 | let | ||
| 118 | rcvEvents = runClient (baseUrlHost server) (baseUrlPort server) "" $ forever . (triggerData . maybe (Left InvalidMessage) Right . parseURI . T.unpack <=< receiveData) | ||
| 119 | liftIO . forkIO $ rcvEvents `catchAll` (triggerData . Left . UnknownException) | ||
| 120 | void $ setup c w dataUpdate | ||
| 121 | |||
diff --git a/webgui/thermoprint-webgui.cabal b/webgui/thermoprint-webgui.cabal index 51a302a..c1f4d19 100644 --- a/webgui/thermoprint-webgui.cabal +++ b/webgui/thermoprint-webgui.cabal | |||
| @@ -26,5 +26,10 @@ executable thermoprint-webgui | |||
| 26 | , threepenny-gui >=0.6.0 && <1 | 26 | , threepenny-gui >=0.6.0 && <1 |
| 27 | , optparse-applicative >=0.12.1 && <1 | 27 | , optparse-applicative >=0.12.1 && <1 |
| 28 | , bytestring >=0.10.6 && <1 | 28 | , bytestring >=0.10.6 && <1 |
| 29 | , websockets >=0.9.5 && <1 | ||
| 30 | , network >=2.6.2 && <3 | ||
| 31 | , network-uri >=2.6.0 && <3 | ||
| 32 | , text >=1.2.2 && <2 | ||
| 33 | , exceptions >=0.8.2 && <1 | ||
| 29 | hs-source-dirs: src | 34 | hs-source-dirs: src |
| 30 | default-language: Haskell2010 \ No newline at end of file | 35 | default-language: Haskell2010 \ No newline at end of file |
diff --git a/webgui/thermoprint-webgui.nix b/webgui/thermoprint-webgui.nix index 0450eae..5eb5912 100644 --- a/webgui/thermoprint-webgui.nix +++ b/webgui/thermoprint-webgui.nix | |||
| @@ -1,5 +1,6 @@ | |||
| 1 | { mkDerivation, base, bytestring, optparse-applicative, stdenv | 1 | { mkDerivation, base, bytestring, exceptions, network, network-uri |
| 2 | , thermoprint-bbcode, thermoprint-client, threepenny-gui | 2 | , optparse-applicative, stdenv, text, thermoprint-bbcode |
| 3 | , thermoprint-client, threepenny-gui, websockets | ||
| 3 | }: | 4 | }: |
| 4 | mkDerivation { | 5 | mkDerivation { |
| 5 | pname = "thermoprint-webgui"; | 6 | pname = "thermoprint-webgui"; |
| @@ -8,8 +9,9 @@ mkDerivation { | |||
| 8 | isLibrary = false; | 9 | isLibrary = false; |
| 9 | isExecutable = true; | 10 | isExecutable = true; |
| 10 | executableHaskellDepends = [ | 11 | executableHaskellDepends = [ |
| 11 | base bytestring optparse-applicative thermoprint-bbcode | 12 | base bytestring exceptions network network-uri optparse-applicative |
| 12 | thermoprint-client threepenny-gui | 13 | text thermoprint-bbcode thermoprint-client threepenny-gui |
| 14 | websockets | ||
| 13 | ]; | 15 | ]; |
| 14 | homepage = "http://dirty-haskell.org/tags/thermoprint.html"; | 16 | homepage = "http://dirty-haskell.org/tags/thermoprint.html"; |
| 15 | description = "Threepenny interface for thermoprint-spec compliant servers"; | 17 | description = "Threepenny interface for thermoprint-spec compliant servers"; |
