aboutsummaryrefslogtreecommitdiff
path: root/pandoc-cli/server
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-09-27 11:25:54 +0200
committerJohn MacFarlane <[email protected]>2022-09-27 08:42:27 -0700
commit2bad9a9aa4eeb6cd63eef53422751ce5fd307c6b (patch)
tree6d1731f9c1b2da52c48a19938884ecb131a1aed4 /pandoc-cli/server
parent5e6b28cd0ee09904e625d37a6acf484654013cab (diff)
pandoc-cli: Avoid the CPP language extension
Alternative behavior for the *server* flag is implemented by using separate modules.
Diffstat (limited to 'pandoc-cli/server')
-rw-r--r--pandoc-cli/server/PandocCLI/Server.hs32
1 files changed, 32 insertions, 0 deletions
diff --git a/pandoc-cli/server/PandocCLI/Server.hs b/pandoc-cli/server/PandocCLI/Server.hs
new file mode 100644
index 000000000..ce9b4e8d0
--- /dev/null
+++ b/pandoc-cli/server/PandocCLI/Server.hs
@@ -0,0 +1,32 @@
+{-# LANGUAGE OverloadedStrings #-}
+{- |
+ Module : Main
+ Copyright : © 2006-2022 John MacFarlane
+ License : GPL-2.0-or-later
+ Maintainer : John MacFarlane <jgm@berkeley@edu>
+
+Functions for the pandoc server CLI.
+-}
+module PandocCLI.Server
+ ( runCGI
+ , runServer
+ )
+where
+import qualified Network.Wai.Handler.CGI as CGI
+import qualified Network.Wai.Handler.Warp as Warp
+import Network.Wai.Middleware.Timeout (timeout)
+import Safe (readDef)
+import System.Environment (lookupEnv)
+import Text.Pandoc.Server (ServerOpts(..), parseServerOpts, app)
+
+-- | Runs the CGI server.
+runCGI :: IO ()
+runCGI = do
+ cgiTimeout <- maybe 2 (readDef 2) <$> lookupEnv "PANDOC_SERVER_TIMEOUT"
+ CGI.run (timeout cgiTimeout app)
+
+-- | Runs the HTTP server.
+runServer :: IO ()
+runServer = do
+ sopts <- parseServerOpts
+ Warp.run (serverPort sopts) (timeout (serverTimeout sopts) app)