Skip to content
This repository was archived by the owner on Apr 1, 2025. It is now read-only.

Commit e8ac13f

Browse files
author
Patrick Thomson
committed
Institute parser for Core.
I tried to pull the history from this patch over but I was not able to figure out how to resolve conflicts from `git am`.
1 parent ac8bd44 commit e8ac13f

File tree

3 files changed

+151
-11
lines changed

3 files changed

+151
-11
lines changed

semantic-core/semantic-core.cabal

Lines changed: 14 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -26,22 +26,26 @@ library
2626
, Analysis.Typecheck
2727
, Control.Effect.Readline
2828
, Data.Core
29+
, Data.Core.Parser
2930
, Data.File
3031
, Data.Loc
3132
, Data.Name
3233
, Data.Stack
3334
-- other-modules:
3435
-- other-extensions:
35-
build-depends: algebraic-graphs ^>= 0.3
36-
, base >= 4.11 && < 5
37-
, containers ^>= 0.6
38-
, directory ^>= 1.3
39-
, filepath ^>= 1.4
40-
, fused-effects ^>= 0.4
41-
, haskeline ^>= 0.7.5
42-
, prettyprinter ^>= 1.2.1
43-
, semigroupoids ^>= 5.3
44-
, transformers ^>= 0.5.6
36+
build-depends: algebraic-graphs ^>= 0.3
37+
, base >= 4.11 && < 5
38+
, containers ^>= 0.6
39+
, directory ^>= 1.3
40+
, filepath ^>= 1.4
41+
, fused-effects ^>= 0.4
42+
, haskeline ^>= 0.7.5
43+
, parsers ^>= 0.12.10
44+
, prettyprinter ^>= 1.2.1
45+
, semigroupoids ^>= 5.3
46+
, transformers ^>= 0.5.6
47+
, trifecta ^>= 2
48+
, unordered-containers ^>= 0.2.10
4549
hs-source-dirs: src
4650
default-language: Haskell2010
4751
ghc-options: -Weverything -Wno-missing-local-signatures -Wno-missing-import-lists -Wno-implicit-prelude -Wno-safe -Wno-unsafe -Wno-name-shadowing -Wno-monomorphism-restriction -Wno-missed-specialisations -Wno-all-missed-specialisations
Lines changed: 118 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,118 @@
1+
{-# LANGUAGE ExplicitForAll, FlexibleInstances, LambdaCase, MultiParamTypeClasses, OverloadedLists,
2+
ScopedTypeVariables #-}
3+
4+
module Data.Core.Parser
5+
( module Text.Trifecta
6+
, core
7+
, lit
8+
, expr
9+
, lvalue
10+
) where
11+
12+
-- Consult @doc/grammar.md@ for an EBNF grammar.
13+
14+
import Control.Applicative
15+
import qualified Data.Char as Char
16+
import Data.Core
17+
import Data.Name
18+
import Data.Semigroup
19+
import Data.String
20+
import qualified Text.Parser.Token as Token
21+
import qualified Text.Parser.Token.Highlight as Highlight
22+
import Text.Trifecta hiding (ident)
23+
24+
-- * Identifier styles and derived parsers
25+
26+
validIdentifierStart :: Char -> Bool
27+
validIdentifierStart c = not (Char.isDigit c) && isSimpleCharacter c
28+
29+
coreIdents :: TokenParsing m => IdentifierStyle m
30+
coreIdents = Token.IdentifierStyle
31+
{ _styleName = "core"
32+
, _styleStart = satisfy validIdentifierStart
33+
, _styleLetter = satisfy isSimpleCharacter
34+
, _styleReserved = reservedNames
35+
, _styleHighlight = Highlight.Identifier
36+
, _styleReservedHighlight = Highlight.ReservedIdentifier
37+
}
38+
39+
reserved :: (TokenParsing m, Monad m) => String -> m ()
40+
reserved = Token.reserve coreIdents
41+
42+
identifier :: (TokenParsing m, Monad m, IsString s) => m s
43+
identifier = choice [quote, plain] <?> "identifier" where
44+
plain = Token.ident coreIdents
45+
quote = between (string "#{") (symbol "}") (fromString <$> some (noneOf "{}"))
46+
47+
-- * Parsers (corresponding to EBNF)
48+
49+
core :: (TokenParsing m, Monad m) => m Core
50+
core = expr
51+
52+
expr :: (TokenParsing m, Monad m) => m Core
53+
expr = chainl1 atom go where
54+
go = choice [ (:.) <$ dot
55+
, (:$) <$ notFollowedBy dot
56+
]
57+
58+
atom :: (TokenParsing m, Monad m) => m Core
59+
atom = choice
60+
[ comp
61+
, ifthenelse
62+
, edge
63+
, lit
64+
, ident
65+
, assign
66+
, parens expr
67+
]
68+
69+
comp :: (TokenParsing m, Monad m) => m Core
70+
comp = braces (sconcat <$> sepEndByNonEmpty expr semi)
71+
72+
ifthenelse :: (TokenParsing m, Monad m) => m Core
73+
ifthenelse = If
74+
<$ reserved "if" <*> core
75+
<* reserved "then" <*> core
76+
<* reserved "else" <*> core
77+
<?> "if-then-else statement"
78+
79+
assign :: (TokenParsing m, Monad m) => m Core
80+
assign = (:=) <$> try (lvalue <* symbolic '=') <*> core
81+
82+
edge :: (TokenParsing m, Monad m) => m Core
83+
edge = kw <*> expr where kw = choice [ Edge Lexical <$ reserved "lexical"
84+
, Edge Import <$ reserved "import"
85+
, Load <$ reserved "load"
86+
]
87+
88+
lvalue :: (TokenParsing m, Monad m) => m Core
89+
lvalue = choice
90+
[ Let <$ reserved "let" <*> name
91+
, ident
92+
, parens expr
93+
]
94+
95+
-- * Literals
96+
97+
name :: (TokenParsing m, Monad m) => m Name
98+
name = choice [regular, strpath] <?> "name" where
99+
regular = User <$> identifier
100+
strpath = Path <$> between (symbolic '"') (symbolic '"') (some $ noneOf "\"")
101+
102+
lit :: (TokenParsing m, Monad m) => m Core
103+
lit = let x `given` n = x <$ reserved n in choice
104+
[ Bool True `given` "#true"
105+
, Bool False `given` "#false"
106+
, Unit `given` "#unit"
107+
, Frame `given` "#frame"
108+
, lambda
109+
] <?> "literal"
110+
111+
lambda :: (TokenParsing m, Monad m) => m Core
112+
lambda = Lam <$ lambduh <*> name <* arrow <*> core <?> "lambda" where
113+
lambduh = symbolic 'λ' <|> symbolic '\\'
114+
arrow = symbol "" <|> symbol "->"
115+
116+
ident :: (Monad m, TokenParsing m) => m Core
117+
ident = Var <$> name <?> "identifier"
118+

semantic-core/src/Data/Name.hs

Lines changed: 19 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,10 @@
1-
{-# LANGUAGE DeriveFunctor, ExistentialQuantification, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, MultiParamTypeClasses, OverloadedStrings, StandaloneDeriving, TypeOperators, UndecidableInstances #-}
1+
{-# LANGUAGE DeriveFunctor, ExistentialQuantification, FlexibleContexts, FlexibleInstances, GeneralizedNewtypeDeriving, LambdaCase, MultiParamTypeClasses, OverloadedLists, OverloadedStrings,StandaloneDeriving, TypeOperators, UndecidableInstances #-}
22
module Data.Name
33
( User
44
, Namespaced
55
, Name(..)
6+
, reservedNames
7+
, isSimpleCharacter
68
, Gensym(..)
79
, (//)
810
, gensym
@@ -20,6 +22,8 @@ import Control.Effect.State
2022
import Control.Effect.Sum
2123
import Control.Monad.Fail
2224
import Control.Monad.IO.Class
25+
import qualified Data.Char as Char
26+
import Data.HashSet (HashSet)
2327
import Data.Text.Prettyprint.Doc (Pretty (..))
2428
import qualified Data.Text.Prettyprint.Doc as Pretty
2529

@@ -50,6 +54,20 @@ instance Pretty Name where
5054
User n -> pretty n
5155
Path p -> pretty (show p)
5256

57+
reservedNames :: HashSet User
58+
reservedNames = [ "#true", "#false", "let", "#frame", "if", "then", "else"
59+
, "lexical", "import", "#unit", "load"]
60+
61+
-- | A ‘simple’ character is, loosely defined, a character that is compatible
62+
-- with identifiers in most ASCII-oriented programming languages. This is defined
63+
-- as the alphanumeric set plus @$@ and @_@.
64+
isSimpleCharacter :: Char -> Bool
65+
isSimpleCharacter = \case
66+
'$' -> True -- common in JS
67+
'_' -> True
68+
'?' -> True -- common in Ruby
69+
c -> Char.isAlphaNum c
70+
5371
data Gensym
5472
= Root String
5573
| Gensym :/ (String, Int)

0 commit comments

Comments
 (0)