Skip to content

Commit

Permalink
Pretty printing
Browse files Browse the repository at this point in the history
  • Loading branch information
danieljharvey committed Oct 15, 2024
1 parent 5675219 commit b778353
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 19 deletions.
2 changes: 1 addition & 1 deletion wasm-calc12/src/Calc/Parser/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -74,7 +74,7 @@ lambdaParser = label "lambda" $ addLocation $ do
stringLiteral "->"
ty <- typeParser
stringLiteral "{"
expr <- exprParserInternal
expr <- exprParser
stringLiteral "}"
pure $ ELambda mempty args ty expr

Expand Down
35 changes: 18 additions & 17 deletions wasm-calc12/src/Calc/Types/Expr.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@

module Calc.Types.Expr (Expr (..)) where

import Calc.Utils
import Calc.Types.Constructor
import Calc.Types.FunctionName
import Calc.Types.Identifier
Expand Down Expand Up @@ -34,30 +35,30 @@ data Expr ann
| ELambda ann [(Identifier, Type ann)] (Type ann) (Expr ann)
deriving stock (Eq, Ord, Show, Functor, Foldable, Traversable)

-- when on multilines, indent by `i`, if not then nothing
indentMulti :: Integer -> PP.Doc style -> PP.Doc style
indentMulti i doc =
PP.flatAlt (PP.indent (fromIntegral i) doc) doc

-- | this instance defines how to nicely print `Expr`
instance PP.Pretty (Expr ann) where
pretty (EPrim _ prim) =
PP.pretty prim
pretty (EAnn _ ty expr) =
PP.parens (PP.pretty expr <> ":" <+> PP.pretty ty)
pretty (ELambda _ args tyReturn body) =
"\\("
<> PP.cat prettyArgs
<> ")"
<+> "->"
<+> PP.pretty tyReturn
<+> "{"
<> PP.pretty body
<> "}"
where
prettyArgs =
PP.punctuate ", " (prettyArg <$> args)
pretty (ELambda _ fnArgs fnReturnType fnBody) =
"\\"
<> PP.group
( "("
<> newlines
( indentMulti
2
(PP.cat (PP.punctuate ", " (prettyArg <$> fnArgs)))
)
)
<> ")"

<+> "->"
<+> PP.pretty fnReturnType
<+> "{"
<+> PP.group (newlines $ indentMulti 2 (PP.pretty fnBody))
<> "}"
where
prettyArg (ident, ty) = PP.pretty ident <> ":" <> PP.pretty ty
pretty (ELet _ (PWildcard _) body rest) =
PP.pretty body
Expand Down
3 changes: 2 additions & 1 deletion wasm-calc12/src/Calc/Utils.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
module Calc.Utils (prettyShow, ltrace, ltraceM, neZipWith, neZipWithM, neUnzip, indentMulti, newlines) where
module Calc.Utils (prettyShow,
ltrace, ltraceM, neZipWith, neZipWithM, neUnzip, indentMulti, newlines) where

-- useful junk goes here

Expand Down
12 changes: 12 additions & 0 deletions wasm-calc12/test/Test/Parser/ParserSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -445,6 +445,18 @@ spec = do
( "\\(a: Int32,b: Boolean) -> Int32 { 3 }",
ELambda () [("a", tyInt32), ("b", tyBool)] tyInt32 (int 3)
),
( "let f = \\() -> Boolean { True }; f",
ELet () (PVar () "f")
(ELambda () [] tyBool
(bool True) )
(var "f")
),
( "let f = \\() -> Boolean { let a = True; a }; f",
ELet () (PVar () "f")
(ELambda () [] tyBool
(ELet () (PVar () "a") (bool True) (var "a")))
(var "f")
),
("let a = 100; a", ELet () (PVar () "a") (int 100) (var "a")),
( "let (a,b) = (1,2); a + b",
ELet
Expand Down
9 changes: 9 additions & 0 deletions wasm-calc12/test/static/lambda.calc
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
function main() -> Int64 {
let f = \(a:Int64, b:Int64, c:Int64) -> Int64 {
let total = a + 100;
total + 1 + b + c
};
let g = \() -> Boolean { False};
let a = f(100, 2, 3);
if g() then a else 200
}

0 comments on commit b778353

Please sign in to comment.