Skip to content

Instantly share code, notes, and snippets.

@andreasabel
Created April 10, 2022 20:19
Show Gist options
  • Save andreasabel/f5c877491d32b653efba44cb283ba490 to your computer and use it in GitHub Desktop.
Save andreasabel/f5c877491d32b653efba44cb283ba490 to your computer and use it in GitHub Desktop.
Interpreter for C-style expression in Linear Haskell
-- BNFC grammar for C-style arithmetic expressions
-- Build parser with: bnfc --haskell --generic -d -m Exp.cf && make
EVar. Exp2 ::= Ident;
EInt. Exp2 ::= Integer;
EPlus. Exp1 ::= Exp1 "+" Exp2;
EAss. Exp ::= Ident "=" Exp1;
coercions Exp 2;
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE LinearTypes #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
-- | An interpreter for C-style expressions written in Linear Haskell.
import Prelude.Linear hiding (fst)
import Data.Tuple.Linear (fst)
import Data.Hashable (Hashable)
import Data.HashMap.Mutable.Linear (HashMap, Keyed)
import Data.HashMap.Mutable.Linear qualified as HashMap
import Control.Functor.Linear
import Exp.Abs (Exp(..), Ident(..))
import Exp.Par (pExp, myLexer)
-- | Parse expression from stdin and print its value on stdout.
main :: IO ()
main = do
input <- getContents
let e = either (applyMove error) id (pExp (myLexer input))
let Ur (i :: Int) = HashMap.empty 100 (\ env -> move (evalState (eval e) env))
-- empty :: Int -> (HashMap k v %1 -> Ur b) %1 -> Ur b
putStrLn (show i)
-- | Environment maps identifiers to their 'Int'-value.
type Env = HashMap Ident Int
-- | Linear interpreter for C-style arithmetic expressions.
eval :: Exp %1 -> State Env Int
eval = \case
EInt i -> pure (fromInteger i)
-- @instance Additive Integer@ is missing, so I truncate to @Int@
EPlus e1 e2 -> liftA2 (+) (eval e1) (eval e2)
EVar x -> lookupEnv x
EAss x e -> eval e >>= assign x
-- * Auxiliary definitions
lookupEnv :: Ident %1 -> State Env Int
lookupEnv x = fromMaybe (error "unbound identifier") . unur <$> lookupSt x
assign :: Ident %1 -> Int %1 -> State Env Int
assign x v = assignUr `applyMove` x `applyMove` v
assignUr :: Ident -> Int -> State Env Int
assignUr x v = state (\ env -> (v, HashMap.insert x v env))
instance Hashable Ident where
deriving instance Consumable Ident
deriving instance Dupable Ident
deriving instance Movable Ident
-- * General utilities
evalState :: Consumable s => State s a %1 -> s %1 -> a
evalState m s = fst (runState m s)
-- Key is used several times when looking up in a map
lookupSt :: (Keyed k, Movable k) => k %1 -> State (HashMap k v) (Ur (Maybe v))
lookupSt k = state (HashMap.lookup `applyMove` k)
applyMove :: Movable a => (a -> b) %1 -> a %1 -> b
applyMove f x = f `applyUr` move x
applyUr :: (a -> b) %1 -> Ur a %1 -> b
applyUr f (Ur a) = f a
# hpack Haskell package description
name: interpreter-linear
dependencies:
- base >= 4.15
- array
- hashable
- linear-base
executable:
source-dirs: .
main: InterpreterMain.hs
other-modules:
Exp.Abs
Exp.Lex
Exp.Par
Exp.Print
verbatim:
default-language: GHC2021
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment