Skip to content

Commit

Permalink
More comments and some prettifying
Browse files Browse the repository at this point in the history
  • Loading branch information
WoWaster committed Oct 25, 2024
1 parent caa876a commit 84814cb
Show file tree
Hide file tree
Showing 16 changed files with 97 additions and 40 deletions.
2 changes: 1 addition & 1 deletion .pre-commit-config.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ repos:
hooks:
- id: trailing-whitespace
- id: end-of-file-fixer
exclude: ".*\\.lml\\.ast"
exclude: "ast/.*|ppr/.*"
- id: check-yaml
- id: fix-byte-order-marker
- id: mixed-line-ending
6 changes: 3 additions & 3 deletions lamagraph-compiler/lamagraph-compiler.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,8 +30,8 @@ library
Lamagraph.Compiler.Parser.LexerTypes
Lamagraph.Compiler.Parser.LexerUtils
Lamagraph.Compiler.Parser.SrcLoc
Lamagraph.Compiler.PrettyAST
Lamagraph.Compiler.PrettyLML
Lamagraph.Compiler.PrettyAst
Lamagraph.Compiler.PrettyLml
Lamagraph.Compiler.Syntax
Lamagraph.Compiler.Syntax.Decl
Lamagraph.Compiler.Syntax.Expr
Expand Down Expand Up @@ -93,7 +93,7 @@ test-suite lamagraph-compiler-test
Lamagraph.Compiler.Parser.GoldenCommon
Lamagraph.Compiler.Parser.LexerTest
Lamagraph.Compiler.Parser.ParserRoundtrip
Lamagraph.Compiler.Parser.PrettyASTGolden
Lamagraph.Compiler.Parser.PrettyAstGolden
Lamagraph.Compiler.Parser.PrettyLmlGolden
Paths_lamagraph_compiler
hs-source-dirs:
Expand Down
5 changes: 4 additions & 1 deletion lamagraph-compiler/src/Lamagraph/Compiler/Extension.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}

-- | Lmlc (LamagraphML Compiler) specializations for LML AST
module Lamagraph.Compiler.Extension (Pass (..), LmlcPass (..), LmlcPs) where

import Lamagraph.Compiler.Parser.SrcLoc
Expand All @@ -11,7 +12,9 @@ data Pass = Parsed
data LmlcPass (c :: Pass) where
LmlcPs :: LmlcPass 'Parsed

type LmlcPs = LmlcPass 'Parsed -- Output of parser
type LmlcPs =
-- | Output of parser
LmlcPass 'Parsed

type instance XLocated (LmlcPass p) a = Located a

Expand Down
3 changes: 3 additions & 0 deletions lamagraph-compiler/src/Lamagraph/Compiler/Parser.y
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
but Happy docs recommend this flag -}
{-# OPTIONS_GHC -fglasgow-exts #-}

{- | LamagraphML parser made with Happy
-}
module Lamagraph.Compiler.Parser (parseLamagraphML) where

import Relude
Expand Down Expand Up @@ -645,6 +647,7 @@ mkFunExpr pats mType rhsExpr = foldr helper init pats
helper :: LLmlPat LmlcPs -> LLmlExpr LmlcPs -> LLmlExpr LmlcPs
helper pat acc = sLL pat acc $ LmlExprFunction noExtField pat acc

-- | Parser entry point
parseLamagraphML :: Text -> Either String (LmlModule LmlcPs)
parseLamagraphML text = runAlex text pLamagraphML
}
52 changes: 37 additions & 15 deletions lamagraph-compiler/src/Lamagraph/Compiler/Parser/Lexer.x
Original file line number Diff line number Diff line change
@@ -1,12 +1,20 @@
-- Alex "Haskell code fragment top"
--------------------------------------
-- Alex "Haskell code fragment top" --
--------------------------------------
{
-- Some of the Alex generated code contains @undefinded@ which is considered
-- deprecated in Relude
{- Some of the Alex generated code contains @undefinded@ which is considered
deprecated in Relude
-}
{-# OPTIONS_GHC -Wno-deprecations #-}
-- Because of the active use of lenses, in this project field selectors are generally
-- disabled, but because Alex relies on them, they must be turned on explicitly
{- Because of the active use of lenses, in this project field selectors are generally
disabled, but because Alex relies on them, they must be turned on explicitly
-}
{-# LANGUAGE FieldSelectors #-}

{- | Module with Alex parser

Some of the exports aren't used in other modules, but are useful in docs.
-}
module Lamagraph.Compiler.Parser.Lexer (
Byte,
AlexInput,
Expand All @@ -19,8 +27,9 @@ module Lamagraph.Compiler.Parser.Lexer (
) where

import Relude
-- These functions must be used only for crashing the entire app,
-- because of the bug in Alex, not in this code
{- These functions must be used only for crashing the entire app,
because of the bug in Alex, not in this code
-}
import Relude.Unsafe (fromJust, read)

import Control.Lens
Expand All @@ -29,29 +38,35 @@ import qualified Data.Text as Text
import Lamagraph.Compiler.Parser.LexerTypes
import Lamagraph.Compiler.Parser.SrcLoc
}
-- Alex "Wrapper"
--------------------
-- Alex "Wrapper" --
--------------------
%wrapper "monadUserState-strict-text"

-- Alex "Character set macros"
---------------------------------
-- Alex "Character set macros" --
---------------------------------

$digit = [0-9]
$letter = [a-zA-Z]
$capital_letter = [A-Z]
$lowercase_letter = [a-z]

$escape_sequence = [\\ \" \' \n]
$regular_char = [\ -\~] # $escape_sequence
$regular_char = [\ -\~] # $escape_sequence -- # is a set difference

$operator_char = [\! \$ \% & \* \+ \. \/ \: \< \= \> \? \@ \^ \| \~]

-- Alex "Regular expression macros"
--------------------------------------
-- Alex "Regular expression macros" --
--------------------------------------

-- Identifiers
@ident_tail = ( $letter | $digit | \_ | \' )*
@capitalized_ident = $capital_letter @ident_tail
-- @lowercase_ident = ( $lowercase_letter | \_ ) @ident_tail
@lowercase_ident = (
( $lowercase_letter @ident_tail)
-- In constrast to the grammar @_@ is reserved as a wildcard and thus cannot be identifier
| ( \_ ( $letter | $digit ) @ident_tail )
)

Expand All @@ -69,10 +84,15 @@ $operator_char = [\! \$ \% & \* \+ \. \/ \: \< \= \> \? \@ \^ \| \~]
| ( ( \? | \~ ) ( $operator_char )+ )
)

-- Alex "Identifier"
-----------------------
-- Alex "Identifier" --
-----------------------

lamagraphml :-

-- Alex "Rules"
------------------
-- Alex "Rules" --
------------------

<0> $white+ ;

Expand Down Expand Up @@ -161,7 +181,9 @@ lamagraphml :-

<0> @prefix_symbol { tokAnyIdent TokPrefixSymbol }

-- Alex "Haskell code fragment bottom"
-----------------------------------------
-- Alex "Haskell code fragment bottom" --
-----------------------------------------
{
instance MonadState AlexUserState Alex where
get :: Alex AlexUserState
Expand Down
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE TemplateHaskell #-}

-- | Module for types produced by lexer
module Lamagraph.Compiler.Parser.LexerTypes (
IdentType (..),
Token (..),
Expand All @@ -20,6 +21,7 @@ import Lamagraph.Compiler.Parser.SrcLoc
data AlexUserState = AlexUserState
{ _lexerCommentDepth :: Int
, _lexerStringStartPos :: Maybe SrcLoc
-- ^ t'SrcLoc' here allows to untie cyclic dependency on 'Lamagraph.Compiler.Parser.Lexer.AlexPosn'
, _lexerStringValue :: Text
}
deriving (Eq, Show)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,7 @@
{- | Module with functions for working with lexer token stream
For now they are used only in tests.
-}
module Lamagraph.Compiler.Parser.LexerUtils (scanner, getTokenTypes, getTokenTypesFromText) where

import Relude
Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# OPTIONS_GHC -Wno-orphans #-}

-- | Orphan instances for pretty-printing AST
module Lamagraph.Compiler.PrettyAST () where
{- | Orphan instances for pretty-printing AST
__Warning__: DO NOT import together with "Lamagraph.Compiler.PrettyLml"!
-}
module Lamagraph.Compiler.PrettyAst () where

import Relude

Expand Down
Original file line number Diff line number Diff line change
@@ -1,7 +1,10 @@
{-# OPTIONS_GHC -Wno-orphans #-}

-- | Orphan instances for pretty-printing LamagraphML
module Lamagraph.Compiler.PrettyLML () where
{- | Orphan instances for pretty-printing LamagraphML
__Warning__: DO NOT import together with "Lamagraph.Compiler.PrettyAst"!
-}
module Lamagraph.Compiler.PrettyLml () where

import Relude

Expand Down
4 changes: 3 additions & 1 deletion lamagraph-compiler/src/Lamagraph/Compiler/Syntax.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,9 @@

{- |
LamagraphML syntax
LamagraphML syntax description and top-level module type
For more information on design see "Lamagraph.Compiler.Syntax.Extension".
-}
module Lamagraph.Compiler.Syntax (
-- * Language description
Expand Down
11 changes: 10 additions & 1 deletion lamagraph-compiler/src/Lamagraph/Compiler/Syntax/Extension.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,16 @@
-- Exporting every type family from here will be too tedious
{-# OPTIONS_GHC -Wno-missing-export-lists #-}

-- | Module with TTG extension points type families
{- | Module with TTG extension points type families
AST here is designed using Trees That Grow (<https://www.jucs.org/jucs_23_1/trees_that_grow/jucs_23_01_0042_0062_najd.pdf>) pattern.
It uses type families to contain phase-specific information.
Regarding directory structure, it loosely follows GHC's one.
In "Lamagraph.Compiler.Syntax".* we have the most general tree with open type families,
meaning that "Lamagraph.Compiler.Syntax".* can easily be transformed into a library.
All the specialization must be done outside (currently in "Lamagraph.Compiler.Extension").
-}
module Lamagraph.Compiler.Syntax.Extension where

import Relude
Expand Down
6 changes: 2 additions & 4 deletions lamagraph-compiler/src/Lamagraph/Compiler/Syntax/Longident.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,11 @@
-- | LamagraphML long identifiers
module Lamagraph.Compiler.Syntax.Longident (Longident (..), mkLongident, LLongident) where

import Relude

import Lamagraph.Compiler.Syntax.Extension

{- | LamagraphML long identifier.
'Text' fragments are dot separated in the source code.
-}
-- | This type represents 'Text' dot-separated fragments in the source code.
newtype Longident = Longident (NonEmpty Text)
deriving (Show, Eq)

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ import Prettyprinter.Render.Text
import Lamagraph.Compiler.Extension
import Lamagraph.Compiler.Parser
import Lamagraph.Compiler.Parser.SrcLoc
import Lamagraph.Compiler.PrettyLML ()
import Lamagraph.Compiler.PrettyLml ()
import Lamagraph.Compiler.Syntax

{- | '<>' lifted to 'Applicative'
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Lamagraph.Compiler.Parser.PrettyASTGolden (parserGoldenTestsAST) where
module Lamagraph.Compiler.Parser.PrettyAstGolden (parserPrettyAstGolden) where

import Relude

Expand All @@ -9,17 +9,23 @@ import Test.Tasty.Golden

import Lamagraph.Compiler.Parser
import Lamagraph.Compiler.Parser.GoldenCommon
import Lamagraph.Compiler.PrettyAST ()
import Lamagraph.Compiler.PrettyAst ()

parserGoldenTestsAST :: IO TestTree
parserGoldenTestsAST = do
newExt :: String
newExt = "ast"

newDir :: FilePath
newDir = ".." </> "ast"

parserPrettyAstGolden :: IO TestTree
parserPrettyAstGolden = do
lmlFiles <- findByExtension [lmlExt] parserGoldenTestsDir
return $
testGroup
"Pretty AST Golden tests"
[ goldenVsString (takeBaseName lmlFile) resLmlFile (helper lmlFile)
| lmlFile <- lmlFiles
, let resLmlFile = addExtension (changeFileDir lmlFile "../ast") "ast"
, let resLmlFile = addExtension (changeFileDir lmlFile newDir) newExt
]
where
helper :: FilePath -> IO LByteString
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -9,15 +9,17 @@ import Test.Tasty.Golden

import Lamagraph.Compiler.Parser
import Lamagraph.Compiler.Parser.GoldenCommon
import Lamagraph.Compiler.PrettyLML ()
import Lamagraph.Compiler.PrettyLml ()

parserPrettyLmlGolden :: IO TestTree
parserPrettyLmlGolden = do
lmlFiles <- findByExtension [lmlExt] parserGoldenTestsDir
return $
testGroup
"Pretty LML Golden tests"
[ goldenVsString (takeBaseName lmlFile) resLmlFile (helper lmlFile) | lmlFile <- lmlFiles, let resLmlFile = changeFileDir lmlFile "../ppr"
[ goldenVsString (takeBaseName lmlFile) resLmlFile (helper lmlFile)
| lmlFile <- lmlFiles
, let resLmlFile = changeFileDir lmlFile "../ppr"
]
where
helper :: FilePath -> IO LByteString
Expand Down
4 changes: 2 additions & 2 deletions lamagraph-compiler/test/Spec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Test.Tasty.Hedgehog

import Lamagraph.Compiler.Parser.LexerTest
import Lamagraph.Compiler.Parser.ParserRoundtrip
import Lamagraph.Compiler.Parser.PrettyASTGolden
import Lamagraph.Compiler.Parser.PrettyAstGolden
import Lamagraph.Compiler.Parser.PrettyLmlGolden

main :: IO ()
Expand All @@ -19,7 +19,7 @@ lexerTests = testGroup "Lexer" [lexerUnitTests]

parserTests :: IO TestTree
parserTests = do
parserASTGolden <- parserGoldenTestsAST
parserASTGolden <- parserPrettyAstGolden
parserLmlGolden <- parserPrettyLmlGolden
let roundtrip = testPropertyNamed "Parser roundtrip (AST -> LML -> AST)" "prop_ParserRoundtrip" prop_ParserRoundtrip
return $ testGroup "Parser" [parserASTGolden, parserLmlGolden, roundtrip]

0 comments on commit 84814cb

Please sign in to comment.