diff options
Diffstat (limited to 'src/Compile.hs')
| -rw-r--r-- | src/Compile.hs | 19 | 
1 files changed, 9 insertions, 10 deletions
| diff --git a/src/Compile.hs b/src/Compile.hs index 92eb6d5..48a03b5 100644 --- a/src/Compile.hs +++ b/src/Compile.hs @@ -1,9 +1,8 @@ -{-# LANGUAGE DeriveFunctor #-}  {-# LANGUAGE GADTs #-}  {-# LANGUAGE LambdaCase #-}  {-# LANGUAGE PolyKinds #-}  {-# LANGUAGE TypeApplications #-} -module Compile where +module Compile (compile) where  import Control.Monad.Trans.State.Strict  import Data.Bifunctor (first, second) @@ -68,16 +67,16 @@ data Stmt    | SAsg String CExpr  -- ^ variable name, right-hand side    | SBlock [Stmt]    | SIf CExpr [Stmt] [Stmt] -  | SVerbatim String +  | SVerbatim String  -- ^ no implicit ';', just printed as-is    deriving (Show)  data CExpr -  = CELit String -  | CEStruct String [(String, CExpr)] -  | CEProj CExpr String -  | CECall String [CExpr] -  | CEBinop CExpr String CExpr -  | CEIf CExpr CExpr CExpr +  = CELit String  -- ^ inserted as-is, assumed no parentheses needed +  | CEStruct String [(String, CExpr)]  -- ^ struct construction literal: `(name){.field=expr}` +  | CEProj CExpr String  -- ^ field projection: expr.field +  | CECall String [CExpr]  -- ^ function(arg1, ..., argn) +  | CEBinop CExpr String CExpr  -- ^ expr + expr +  | CEIf CExpr CExpr CExpr  -- ^ expr ? expr : expr    deriving (Show)  printStructDecl :: StructDecl -> ShowS @@ -533,7 +532,7 @@ compile' env = \case      STI64 -> return $ CELit $ "(int64_t)" ++ show x      STF32 -> return $ CELit $ show x ++ "f"      STF64 -> return $ CELit $ show x -    STBool -> return $ CELit $ if x then "true" else "false" +    STBool -> return $ CELit $ if x then "1" else "0"    -- EIdx0 _ e -> error "TODO" -- EIdx0 ext (compile' e) | 
