Skip to content

Instantly share code, notes, and snippets.

@christianlavoie
Created July 27, 2020 15:26
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save christianlavoie/06254660f118fb718909f448ff1273d5 to your computer and use it in GitHub Desktop.
Save christianlavoie/06254660f118fb718909f448ff1273d5 to your computer and use it in GitHub Desktop.
{-# LANGUAGE ScopedTypeVariables #-}
module Main (runParser, main) where
import Asterius.Text
import Asterius.Types
import Control.Concurrent (threadDelay)
import Data.Text (Text)
import Data.Void (Void)
import Text.Megaparsec hiding (runParser)
import Text.Megaparsec.Char
data Expr = ExprNum Int
deriving Show
type Parser = Parsec Void Text
exprParser :: Parser Expr
exprParser = do
nums :: [Expr] <- sepBy1 number (do { space ; _ <- char '+' ; space })
return . ExprNum . sum $ map (\(ExprNum a) -> a) nums
where number :: Parser Expr
number = do a <- some digitChar
return $ ExprNum (read a)
runParser :: JSString -> JSString
runParser input = toJSString . show $ parse exprParser "" (textFromJSString input)
foreign export javascript "runParser" runParser :: JSString -> JSString
main :: IO ()
main = do
putStrLn . fromJSString . runParser $ toJSString "1 + 2"
putStrLn "Main worker initialized"
threadDelay $ 1000 * 1000 * 24 * 60 * 60
main
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment