summaryrefslogtreecommitdiff
path: root/Run/Que/Website.hs
blob: 5e2f4d68100b5745024fc7dcf5977147ecd313d6 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE LambdaCase #-}

-- | spawns a few processes that serve the que.run website
--
-- : exe que-website
--
-- : dep async
-- : dep config-ini
-- : dep process
-- : dep protolude
-- : dep req
module Run.Que.Website
  ( main
  )
where

import qualified Control.Concurrent.Async      as Async
import           Com.Simatime.Alpha
import qualified Data.ByteString.Char8         as BS
import qualified Data.Ini.Config               as Config
import qualified Data.Text                     as Text
import           Data.Text.Encoding             ( encodeUtf8 )
import qualified Data.Text.IO                  as Text
import           Network.HTTP.Req
import qualified System.Directory              as Directory
import           System.Environment            as Environment
import qualified System.Exit                   as Exit
import           System.FilePath                ( (</>) )
import qualified System.Process                as Process

main :: IO ()
main = do
  (src, ns) <- Environment.getArgs >>= \case
    [src]     -> return (src, "_") -- default to _ ns which is special
    [src, ns] -> return (src, ns)
    _         -> Exit.die "usage: que-website <srcdir> [namespace]"
  home <- Directory.getHomeDirectory
  conf <- Text.readFile <| home </> ".config" </> "que.conf"
  let (Auth _ key) =
        either needConf identity
          <| Config.parseIniFile conf
          <| auth
          <| Text.pack ns
  putStrLn $ "serving " ++ src ++ " at " ++ ns
  run key (Text.pack ns) $ Sources { index      = src </> "index.md"
                                   , client     = src </> "client.py"
                                   , quescripts = src </> "quescripts.md"
                                   , style      = src </> "style.css"
                                   , apidocs    = src </> "apidocs.md"
                                   , tutorial   = src </> "tutorial.md"
                                   }

needConf :: error
needConf = panic "you need a ~/.config/que.conf"

data Sources = Sources
  { index :: FilePath
  , quescripts :: FilePath
  , client :: FilePath
  , style :: FilePath
  , tutorial :: FilePath
  , apidocs :: FilePath
  }

type Namespace = Text
type Key = Text

data Auth = Auth Namespace Key

auth :: Text -> Config.IniParser Auth
auth ns = Config.section ns $ do
  key <- Config.field "key"
  return <| Auth ns key

run :: Key -> Text -> Sources -> IO ()
run key ns Sources {..} = Async.runConcurrently actions >> return ()
 where
  actions = traverse
    Async.Concurrently
    [ forever <| toHtml index >>= serve key ns "index"
    , forever <| toHtml quescripts >>= serve key ns "quescripts"
    , forever <| BS.readFile client >>= serve key ns "client"
    , forever <| toHtml tutorial >>= serve key ns "tutorial"
    , forever <| toHtml apidocs >>= serve key ns "apidocs"
    ]
  toHtml :: FilePath -> IO ByteString
  toHtml md =
    BS.pack
      <$> Process.readProcess
            "pandoc"
            [ "--self-contained"
            , "--css"
            , style
            , "-i"
            , md
            , "--from"
            , "markdown"
            , "--to"
            , "html"
            ]
            []

-- TODO: recover from 502 errors
serve :: Key -> Namespace -> Text -> ByteString -> IO ()
serve key ns path content = runReq defaultHttpConfig $ do
  let options =
        header "Authorization" (encodeUtf8 key) <> responseTimeout maxBound
  _ <- req POST
           (http "que.run" /: ns /: path)
           (ReqBodyBs content)
           ignoreResponse
           options
  liftIO $ return ()