summaryrefslogtreecommitdiff
path: root/Hero/Host.hs
diff options
context:
space:
mode:
authorBen Sima <ben@bsima.me>2021-01-16 05:57:06 -0500
committerBen Sima <ben@bsima.me>2021-01-16 05:57:06 -0500
commitb66a045cd6e491987130145f311674fcedc00ca9 (patch)
treed008feacd595b5edb5dc30e88bb604f3001fc0e7 /Hero/Host.hs
parentebea9b0005b983935f7bc159bb738ace874591f8 (diff)
Port Hero.Host to Biz.Cli
Diffstat (limited to 'Hero/Host.hs')
-rw-r--r--Hero/Host.hs25
1 files changed, 24 insertions, 1 deletions
diff --git a/Hero/Host.hs b/Hero/Host.hs
index 9d10f02..468bd0f 100644
--- a/Hero/Host.hs
+++ b/Hero/Host.hs
@@ -5,6 +5,7 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
@@ -19,6 +20,7 @@
-- : dep aeson
-- : dep clay
-- : dep containers
+-- : dep docopt
-- : dep envy
-- : dep http-types
-- : dep ixset
@@ -36,6 +38,8 @@
-- : dep split
-- : dep split
-- : dep string-quote
+-- : dep tasty
+-- : dep tasty-hunit
-- : dep text
-- : dep wai
-- : dep wai-app-static
@@ -51,6 +55,9 @@ where
import Alpha
import Biz.App (CSS (..), Manifest (..))
+import qualified Biz.Cli as Cli
+import Biz.Test ((@=?))
+import qualified Biz.Test as Test
import qualified Clay
import qualified Crypto.JOSE.JWK as Crypto
import Data.Acid (AcidState)
@@ -78,7 +85,23 @@ import qualified System.Exit as Exit
import qualified System.IO as IO
main :: IO ()
-main = bracket startup shutdown run
+main = Cli.main <| Cli.Plan help move test
+
+help :: Cli.Docopt
+help =
+ [Cli.docopt|
+mmc
+
+Usage:
+ mmc
+ mmc test
+|]
+
+test :: Test.Tree
+test = Test.group "Hero.Host" [Test.unit "id" <| 1 @=? (1 :: Integer)]
+
+move :: Cli.Arguments -> IO ()
+move _ = bracket startup shutdown run
where
run (cfg, app, _) = Warp.run (heroPort cfg) app
prn = IO.hPutStrLn IO.stderr