{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} module Main where import Web.Scotty import Network.JavaScript import Data.Semigroup import Text.Read(readMaybe) import Paths_javascript_bridge main :: IO () main = main_ 3000 data Applets = Commands | Procedures | Constructors | Promises deriving (Eq, Ord, Show, Read, Enum, Bounded) main_ :: Int -> IO () main_ i = do dataDir <- getDataDir --dataDir <- return "." -- use for debugging scotty i $ do middleware $ start app -- Any path, including /, returns the contents of Main.hs get "/:cmd" $ file $ dataDir ++ "/examples/Main.html" app :: Engine -> IO () app eng = do -- simple dispatch based on location hash <- send eng $ procedure "window.location.pathname" case hash of "/" -> indexPage eng '/':xs -> case readMaybe xs of Just sub -> applet eng sub Nothing -> return () _ -> return () indexPage :: Engine -> IO () indexPage eng = send eng $ render $ "