Skip to content
Snippets Groups Projects
Commit 41c69acf authored by Eduardo Trujillo's avatar Eduardo Trujillo
Browse files

feat(Server): Allow output format to be specified

parent f5203438
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Shift.Server (runServer) where
import Web.Scotty (scotty, get, param, html)
import CMarkGFM (commonmarkToHtml, nodeToCommonmark, nodeToHtml)
import Control.Monad.IO.Class (MonadIO (liftIO))
import Data.Text.Lazy (fromChunks)
import Shift.CLI (ShiftOptions)
import Shift.Git (renderToNode)
import Control.Monad.IO.Class (MonadIO(liftIO))
import CMarkGFM (nodeToHtml, nodeToHtml, commonmarkToHtml)
import Data.Text.Lazy (fromChunks)
import Web.Scotty (rescue, rescue, get, html, param, scotty, text)
runServer :: ShiftOptions -> IO ()
runServer options = scotty 3000 $
get "/" $ do
node <- liftIO $ renderToNode options
html $ fromChunks [nodeToHtml [] [] node]
get "/" $ do
(asMarkdown :: Bool) <- param "as_markdown" `rescue` (\_ -> pure False)
node <- liftIO $ renderToNode options
if asMarkdown
then text $ fromChunks [nodeToCommonmark [] Nothing node]
else html $ fromChunks [nodeToHtml [] [] node]
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment