1
1
mirror of https://github.com/anoma/juvix.git synced 2024-12-14 08:27:03 +03:00

[scoper] use atoms information instead of scope to parse infix operators

This commit is contained in:
Jan Mas Rovira 2022-02-18 01:53:10 +01:00
parent 85601c6332
commit 4651906e32
10 changed files with 260 additions and 143 deletions

View File

@ -43,6 +43,7 @@ dependencies:
- template-haskell == 2.17.* - template-haskell == 2.17.*
- text == 1.2.* - text == 1.2.*
- th-utilities == 0.2.* - th-utilities == 0.2.*
- uniplate
- unordered-containers == 0.2.* - unordered-containers == 0.2.*
# the tasty dependencies are here to avoid having to recompile minijuvix # the tasty dependencies are here to avoid having to recompile minijuvix
@ -61,6 +62,7 @@ ghc-options:
default-extensions: default-extensions:
- DataKinds - DataKinds
- DeriveDataTypeable
- DeriveLift - DeriveLift
- DerivingStrategies - DerivingStrategies
- FlexibleContexts - FlexibleContexts

View File

@ -1,13 +1,13 @@
module MiniJuvix.Syntax.Concrete.Fixity where module MiniJuvix.Syntax.Concrete.Fixity where
import Language.Haskell.TH.Syntax (Lift)
import MiniJuvix.Prelude import MiniJuvix.Prelude
data Precedence = data Precedence =
PrecMinusOmega PrecMinusOmega
| PrecNat Natural | PrecNat Natural
| PrecOmega | PrecOmega
deriving stock (Show, Eq, Lift) deriving stock (Show, Eq, Data)
instance Ord Precedence where instance Ord Precedence where
compare a b = case (a, b) of compare a b = case (a, b) of
@ -21,10 +21,10 @@ instance Ord Precedence where
data UnaryAssoc = AssocPostfix data UnaryAssoc = AssocPostfix
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
data BinaryAssoc = AssocNone | AssocLeft | AssocRight data BinaryAssoc = AssocNone | AssocLeft | AssocRight
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
data OperatorArity data OperatorArity
= Unary = Unary
@ -33,10 +33,10 @@ data OperatorArity
| Binary | Binary
{ binaryAssoc :: BinaryAssoc { binaryAssoc :: BinaryAssoc
} }
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
data Fixity = Fixity data Fixity = Fixity
{ fixityPrecedence :: Precedence, { fixityPrecedence :: Precedence,
fixityArity :: OperatorArity fixityArity :: OperatorArity
} }
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableInstances #-}
module MiniJuvix.Syntax.Concrete.Language module MiniJuvix.Syntax.Concrete.Language
@ -139,7 +140,7 @@ data Usage
= UsageNone = UsageNone
| UsageOnce | UsageOnce
| UsageOmega | UsageOmega
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Type signature declaration -- Type signature declaration
@ -156,6 +157,8 @@ deriving stock instance (Eq (ExpressionType s), Eq (SymbolType s)) => Eq (TypeSi
deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (TypeSignature s) deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (TypeSignature s)
deriving stock instance (Data (ExpressionType s), Data (SymbolType s), Typeable s) => Data (TypeSignature s)
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Axioms -- Axioms
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
@ -224,14 +227,14 @@ data PatternInfixApp = PatternInfixApp
patInfixConstructor :: NameType 'Scoped, patInfixConstructor :: NameType 'Scoped,
patInfixRight :: Pattern patInfixRight :: Pattern
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
data PatternPostfixApp = PatternPostfixApp data PatternPostfixApp = PatternPostfixApp
{ {
patPostfixParameter :: Pattern, patPostfixParameter :: Pattern,
patPostfixConstructor :: NameType 'Scoped patPostfixConstructor :: NameType 'Scoped
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
data Pattern data Pattern
= PatternVariable (SymbolType 'Scoped) = PatternVariable (SymbolType 'Scoped)
@ -241,7 +244,7 @@ data Pattern
| PatternPostfixApplication PatternPostfixApp | PatternPostfixApplication PatternPostfixApp
| PatternWildcard | PatternWildcard
| PatternEmpty | PatternEmpty
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Pattern section -- Pattern section
@ -274,6 +277,14 @@ deriving stock instance
) => ) =>
Ord (PatternAtom s) Ord (PatternAtom s)
deriving stock instance
( Data (ExpressionType s),
Data (NameType s),
Data (PatternType s),
Typeable s
) =>
Data (PatternAtom s)
newtype PatternAtoms (s :: Stage) newtype PatternAtoms (s :: Stage)
= PatternAtoms (NonEmpty (PatternAtom s)) = PatternAtoms (NonEmpty (PatternAtom s))
@ -298,6 +309,14 @@ deriving stock instance
) => ) =>
Ord (PatternAtoms s) Ord (PatternAtoms s)
deriving stock instance
( Data (ExpressionType s),
Data (NameType s),
Data (PatternType s),
Typeable s
) =>
Data (PatternAtoms s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Function binding declaration -- Function binding declaration
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -335,6 +354,15 @@ deriving stock instance
) => ) =>
Ord (FunctionClause s) Ord (FunctionClause s)
deriving stock instance
( Data (PatternType s),
Data (NameType s),
Data (SymbolType s),
Data (ExpressionType s),
Typeable s
) =>
Data (FunctionClause s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Module declaration -- Module declaration
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -399,7 +427,7 @@ deriving stock instance
data UsingHiding data UsingHiding
= Using (NonEmpty Symbol) = Using (NonEmpty Symbol)
| Hiding (NonEmpty Symbol) | Hiding (NonEmpty Symbol)
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
data OpenModule (s :: Stage) = OpenModule data OpenModule (s :: Stage) = OpenModule
{ openModuleName :: NameType s, { openModuleName :: NameType s,
@ -415,6 +443,7 @@ deriving stock instance
Eq (ExpressionType s) Eq (ExpressionType s)
) => ) =>
Eq (OpenModule s) Eq (OpenModule s)
deriving stock instance deriving stock instance
( (
Ord (NameType s), Ord (NameType s),
@ -423,6 +452,17 @@ deriving stock instance
Ord (ExpressionType s) Ord (ExpressionType s)
) => ) =>
Ord (OpenModule s) Ord (OpenModule s)
deriving stock instance
(
Data (NameType s),
Data (SymbolType s),
Data (PatternType s),
Data (ExpressionType s),
Typeable s
) =>
Data (OpenModule s)
deriving stock instance deriving stock instance
( (
Show (NameType s), Show (NameType s),
@ -445,7 +485,7 @@ data Expression
| ExpressionLetBlock (LetBlock 'Scoped) | ExpressionLetBlock (LetBlock 'Scoped)
| ExpressionUniverse Universe | ExpressionUniverse Universe
| ExpressionFunction (Function 'Scoped) | ExpressionFunction (Function 'Scoped)
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Expression section -- Expression section
@ -486,6 +526,15 @@ deriving stock instance
) => ) =>
Ord (ExpressionAtom s) Ord (ExpressionAtom s)
deriving stock instance
( Data (ExpressionType s),
Data (NameType s),
Data (SymbolType s),
Data (PatternType s),
Typeable s
) =>
Data (ExpressionAtom s)
-- | Expressions without application -- | Expressions without application
newtype ExpressionAtoms (s :: Stage) newtype ExpressionAtoms (s :: Stage)
= ExpressionAtoms (NonEmpty (ExpressionAtom s)) = ExpressionAtoms (NonEmpty (ExpressionAtom s))
@ -514,6 +563,16 @@ deriving stock instance
) => ) =>
Ord (ExpressionAtoms s) Ord (ExpressionAtoms s)
deriving stock instance
( Data (ExpressionType s),
Data (NameType s),
Data (SymbolType s),
Data (PatternType s),
Typeable s
) =>
Data (ExpressionAtoms s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Match expression -- Match expression
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -541,6 +600,14 @@ deriving stock instance
) => ) =>
Ord (MatchAlt s) Ord (MatchAlt s)
deriving stock instance
( Data (ExpressionType s),
Data (PatternType s),
Typeable s
) =>
Data (MatchAlt s)
data Match (s :: Stage) = Match data Match (s :: Stage) = Match
{ matchExpression :: ExpressionType s, { matchExpression :: ExpressionType s,
matchAlts :: [MatchAlt s] matchAlts :: [MatchAlt s]
@ -564,6 +631,14 @@ deriving stock instance
) => ) =>
Ord (Match s) Ord (Match s)
deriving stock instance
( Data (ExpressionType s),
Data (PatternType s),
Typeable s
) =>
Data (Match s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Universe expression -- Universe expression
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -571,7 +646,7 @@ deriving stock instance
newtype Universe = Universe newtype Universe = Universe
{ universeLevel :: Maybe Natural { universeLevel :: Maybe Natural
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Function expression -- Function expression
@ -589,6 +664,8 @@ deriving stock instance (Eq (ExpressionType s), Eq (SymbolType s)) => Eq (Functi
deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (FunctionParameter s) deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (FunctionParameter s)
deriving stock instance (Data (ExpressionType s), Data (SymbolType s), Typeable s) => Data (FunctionParameter s)
data Function (s :: Stage) = Function data Function (s :: Stage) = Function
{ funParameter :: FunctionParameter s, { funParameter :: FunctionParameter s,
funReturn :: ExpressionType s funReturn :: ExpressionType s
@ -600,6 +677,8 @@ deriving stock instance (Eq (ExpressionType s), Eq (SymbolType s)) => Eq (Functi
deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (Function s) deriving stock instance (Ord (ExpressionType s), Ord (SymbolType s)) => Ord (Function s)
deriving stock instance (Data (ExpressionType s), Data (SymbolType s), Typeable s) => Data (Function s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Where block clauses -- Where block clauses
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -632,6 +711,15 @@ deriving stock instance
) => ) =>
Ord (WhereBlock s) Ord (WhereBlock s)
deriving stock instance
( Data (PatternType s),
Data (NameType s),
Data (SymbolType s),
Data (ExpressionType s),
Typeable s
) =>
Data (WhereBlock s)
data WhereClause (s :: Stage) data WhereClause (s :: Stage)
= WhereOpenModule (OpenModule s) = WhereOpenModule (OpenModule s)
| WhereTypeSig (TypeSignature s) | WhereTypeSig (TypeSignature s)
@ -661,6 +749,15 @@ deriving stock instance
) => ) =>
Ord (WhereClause s) Ord (WhereClause s)
deriving stock instance
( Data (PatternType s),
Data (NameType s),
Data (SymbolType s),
Data (ExpressionType s),
Typeable s
) =>
Data (WhereClause s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Lambda expression -- Lambda expression
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -689,6 +786,13 @@ deriving stock instance
) => ) =>
Ord (Lambda s) Ord (Lambda s)
deriving stock instance
( Data (PatternType s),
Data (ExpressionType s),
Typeable s
) =>
Data (Lambda s)
data LambdaClause (s :: Stage) = LambdaClause data LambdaClause (s :: Stage) = LambdaClause
{ lambdaParameters :: NonEmpty (PatternType s), { lambdaParameters :: NonEmpty (PatternType s),
lambdaBody :: ExpressionType s lambdaBody :: ExpressionType s
@ -712,6 +816,13 @@ deriving stock instance
) => ) =>
Ord (LambdaClause s) Ord (LambdaClause s)
deriving stock instance
( Data (PatternType s),
Data (ExpressionType s),
Typeable s
) =>
Data (LambdaClause s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Application expression -- Application expression
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
@ -720,21 +831,21 @@ data Application = Application
{ applicationFunction :: ExpressionType 'Scoped, { applicationFunction :: ExpressionType 'Scoped,
applicationParameter :: ExpressionType 'Scoped applicationParameter :: ExpressionType 'Scoped
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
data InfixApplication = InfixApplication data InfixApplication = InfixApplication
{ infixAppLeft :: ExpressionType 'Scoped, { infixAppLeft :: ExpressionType 'Scoped,
infixAppOperator :: NameType 'Scoped, infixAppOperator :: NameType 'Scoped,
infixAppRight :: ExpressionType 'Scoped infixAppRight :: ExpressionType 'Scoped
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
data PostfixApplication = PostfixApplication data PostfixApplication = PostfixApplication
{ {
postfixAppParameter :: ExpressionType 'Scoped, postfixAppParameter :: ExpressionType 'Scoped,
postfixAppOperator :: NameType 'Scoped postfixAppOperator :: NameType 'Scoped
} }
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Let block expression -- Let block expression
@ -769,6 +880,15 @@ deriving stock instance
) => ) =>
Ord (LetBlock s) Ord (LetBlock s)
deriving stock instance
( Data (PatternType s),
Data (NameType s),
Data (SymbolType s),
Data (ExpressionType s),
Typeable s
) =>
Data (LetBlock s)
data LetClause (s :: Stage) data LetClause (s :: Stage)
= LetTypeSig (TypeSignature s) = LetTypeSig (TypeSignature s)
| LetFunClause (FunctionClause s) | LetFunClause (FunctionClause s)
@ -797,6 +917,15 @@ deriving stock instance
) => ) =>
Ord (LetClause s) Ord (LetClause s)
deriving stock instance
( Data (PatternType s),
Data (NameType s),
Data (SymbolType s),
Data (ExpressionType s),
Typeable s
) =>
Data (LetClause s)
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
-- Debugging statements -- Debugging statements
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE StandaloneKindSignatures #-} {-# LANGUAGE StandaloneKindSignatures #-}
module MiniJuvix.Syntax.Concrete.Language.Stage where module MiniJuvix.Syntax.Concrete.Language.Stage where
@ -7,7 +8,7 @@ import MiniJuvix.Prelude
data Stage data Stage
= Parsed = Parsed
| Scoped | Scoped
deriving stock (Show) deriving stock (Show, Data)
$(genSingletons [''Stage]) $(genSingletons [''Stage])

View File

@ -1,11 +1,11 @@
module MiniJuvix.Syntax.Concrete.Loc where module MiniJuvix.Syntax.Concrete.Loc where
import MiniJuvix.Prelude import MiniJuvix.Prelude
import Prettyprinter import Prettyprinter
import Language.Haskell.TH.Syntax (Lift)
newtype Pos = Pos Word64 newtype Pos = Pos Word64
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
instance Semigroup Pos where instance Semigroup Pos where
Pos x <> Pos y = Pos (x + y) Pos x <> Pos y = Pos (x + y)
@ -19,7 +19,7 @@ data FileLoc = FileLoc {
-- | Column number -- | Column number
_locCol :: !Pos _locCol :: !Pos
} }
deriving stock (Show, Eq, Lift) deriving stock (Show, Eq, Data)
instance Ord FileLoc where instance Ord FileLoc where
compare (FileLoc l c) (FileLoc l' c') = compare (l, c) (l', c') compare (FileLoc l c) (FileLoc l' c') = compare (l, c) (l', c')
@ -30,7 +30,7 @@ data Loc = Loc
-- | Position within the file -- | Position within the file
_locFileLoc :: !FileLoc _locFileLoc :: !FileLoc
} }
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
-- | Inclusive interval -- | Inclusive interval
data Interval = Interval { data Interval = Interval {
@ -38,7 +38,7 @@ data Interval = Interval {
_intStart :: FileLoc, _intStart :: FileLoc,
_intEnd :: FileLoc _intEnd :: FileLoc
} }
deriving stock (Show, Ord, Eq, Lift) deriving stock (Show, Ord, Eq, Data)
class HasLoc t where class HasLoc t where
getLoc :: t -> Interval getLoc :: t -> Interval

View File

@ -1,10 +1,10 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module MiniJuvix.Syntax.Concrete.Name where module MiniJuvix.Syntax.Concrete.Name where
import Language.Haskell.TH.Syntax (Lift)
import MiniJuvix.Prelude import MiniJuvix.Prelude
import MiniJuvix.Syntax.Concrete.Loc import MiniJuvix.Syntax.Concrete.Loc
import qualified Data.List.NonEmpty.Extra as NonEmpty import qualified Data.List.NonEmpty.Extra as NonEmpty
@ -13,7 +13,7 @@ data Symbol = Symbol {
_symbolText :: Text, _symbolText :: Text,
_symbolLoc :: Interval _symbolLoc :: Interval
} }
deriving stock (Show, Lift) deriving stock (Show, Data)
instance Eq Symbol where instance Eq Symbol where
(==) = (==) `on` _symbolText (==) = (==) `on` _symbolText
@ -30,7 +30,7 @@ instance Hashable Symbol where
data Name data Name
= NameQualified QualifiedName = NameQualified QualifiedName
| NameUnqualified Symbol | NameUnqualified Symbol
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
instance HasLoc Name where instance HasLoc Name where
getLoc n = case n of getLoc n = case n of
@ -40,13 +40,13 @@ instance HasLoc Name where
newtype Path = Path newtype Path = Path
{ pathParts :: NonEmpty Symbol { pathParts :: NonEmpty Symbol
} }
deriving stock (Show, Eq, Ord, Lift) deriving stock (Show, Eq, Ord, Data)
data QualifiedName = QualifiedName data QualifiedName = QualifiedName
{ _qualifiedPath :: Path, { _qualifiedPath :: Path,
_qualifiedSymbol :: Symbol _qualifiedSymbol :: Symbol
} }
deriving stock (Show, Eq, Ord, Generic, Lift) deriving stock (Show, Eq, Ord, Generic, Data)
instance HasLoc QualifiedName where instance HasLoc QualifiedName where
getLoc QualifiedName {..} = getLoc QualifiedName {..} =
@ -66,7 +66,7 @@ data TopModulePath = TopModulePath
{ modulePathDir :: [Symbol], { modulePathDir :: [Symbol],
modulePathName :: Symbol modulePathName :: Symbol
} }
deriving stock (Show, Eq, Ord, Generic, Lift) deriving stock (Show, Eq, Ord, Generic, Data)
instance HasLoc TopModulePath where instance HasLoc TopModulePath where
getLoc TopModulePath {..} = getLoc TopModulePath {..} =

View File

@ -1,3 +1,4 @@
module MiniJuvix.Syntax.Concrete.PublicAnn where module MiniJuvix.Syntax.Concrete.PublicAnn where
import MiniJuvix.Prelude import MiniJuvix.Prelude
@ -7,4 +8,4 @@ data PublicAnn =
Public Public
-- | No annotation. Do not confuse this with 'not public' or 'private'. -- | No annotation. Do not confuse this with 'not public' or 'private'.
| NoPublic | NoPublic
deriving stock (Show, Eq, Ord) deriving stock (Show, Eq, Ord, Data)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
@ -21,13 +22,13 @@ import qualified Data.Kind as GHC
-------------------------------------------------------------------------------- --------------------------------------------------------------------------------
newtype NameId = NameId Word64 newtype NameId = NameId Word64
deriving stock (Show, Eq, Ord, Generic) deriving stock (Show, Eq, Ord, Generic, Data)
data AbsModulePath = AbsModulePath data AbsModulePath = AbsModulePath
{ absTopModulePath :: C.TopModulePath, { absTopModulePath :: C.TopModulePath,
absLocalPath :: [C.Symbol] absLocalPath :: [C.Symbol]
} }
deriving stock (Show, Eq, Generic) deriving stock (Show, Eq, Generic, Data)
topModulePathToAbsPath :: C.TopModulePath -> AbsModulePath topModulePathToAbsPath :: C.TopModulePath -> AbsModulePath
topModulePathToAbsPath p = AbsModulePath p [] topModulePathToAbsPath p = AbsModulePath p []
@ -60,7 +61,7 @@ instance Hashable NameId
data NameFixity data NameFixity
= NoFixity = NoFixity
| SomeFixity C.Fixity | SomeFixity C.Fixity
deriving stock (Show, Eq) deriving stock (Show, Eq, Data)
data NameInfo = NameIndo { data NameInfo = NameIndo {
@ -76,7 +77,7 @@ data WhyInScope =
| BecauseImportedOpened | BecauseImportedOpened
-- | Defined in this module. -- | Defined in this module.
| BecauseDefined | BecauseDefined
deriving stock (Show) deriving stock (Show, Data)
type Name = Name' C.Name type Name = Name' C.Name
@ -97,7 +98,7 @@ data Name' n = Name'
_nameWhyInScope :: WhyInScope, _nameWhyInScope :: WhyInScope,
_namePublicAnn :: PublicAnn _namePublicAnn :: PublicAnn
} }
deriving stock (Show) deriving stock (Show, Data)
makeLenses ''Name' makeLenses ''Name'
instance HasLoc n => HasLoc (Name' n) where instance HasLoc n => HasLoc (Name' n) where

View File

@ -19,7 +19,7 @@ data NameKind
KNameLocalModule KNameLocalModule
| -- | An top module name. | -- | An top module name.
KNameTopModule KNameTopModule
deriving stock (Show, Eq) deriving stock (Show, Eq, Data)
$(genSingletons [''NameKind]) $(genSingletons [''NameKind])

View File

@ -17,6 +17,7 @@ import qualified MiniJuvix.Syntax.Concrete.Scoped.Name as S
import MiniJuvix.Syntax.Concrete.Scoped.Scope import MiniJuvix.Syntax.Concrete.Scoped.Scope
import MiniJuvix.Syntax.Concrete.Scoped.Error import MiniJuvix.Syntax.Concrete.Scoped.Error
import MiniJuvix.Prelude import MiniJuvix.Prelude
import Data.Generics.Uniplate.Data
import qualified Data.List.NonEmpty as NonEmpty import qualified Data.List.NonEmpty as NonEmpty
import MiniJuvix.Syntax.Concrete.Scoped.Name (WhyInScope(BecauseDefined)) import MiniJuvix.Syntax.Concrete.Scoped.Name (WhyInScope(BecauseDefined))
import Test.Tasty.Patterns.Parser (ParseResult(Ambiguous)) import Test.Tasty.Patterns.Parser (ParseResult(Ambiguous))
@ -977,109 +978,98 @@ checkStatement s = case s of
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
-- Infix Expression -- Infix Expression
------------------------------------------------------------------------------- -------------------------------------------------------------------------------
makeExpressionTable2 ::
makeExpressionTable :: ExpressionAtoms 'Scoped -> [[P.Operator Parse Expression]]
forall r. makeExpressionTable2 atoms = [appOp] : symbolTable ++ [[functionOp]]
(Members '[State Scope] r) =>
Sem r [[P.Operator Parse Expression]]
makeExpressionTable = do
symbolTable <- mkSymbolTable . toList <$> gets _scopeSymbols
-- application has the highest precedence. Arrow has the lowest.
return $ [appOp] : symbolTable ++ [[functionOp]]
where where
-- TODO think what to do with qualified symbols symbolTable = mkSymbolTable names
mkSymbolTable :: [SymbolInfo] -> [[P.Operator Parse Expression]] names :: [S.Name]
mkSymbolTable = map (map snd) . groupSortOn fst . mapMaybe (getEntry >=> unqualifiedSymbolOp) names = [ s | s@S.Name' {} <- universeBi atoms ]
where mkSymbolTable :: [S.Name] -> [[P.Operator Parse Expression]]
getEntry :: SymbolInfo -> Maybe SymbolEntry mkSymbolTable = map (map snd) . groupSortOn fst . mapMaybe unqualifiedSymbolOp
getEntry (SymbolInfo m) = case toList m of where
[] -> impossible unqualifiedSymbolOp :: S.Name -> Maybe (Precedence, P.Operator Parse Expression)
[e] -> Just e unqualifiedSymbolOp S.Name' {..}
_ -> Nothing -- ambiguous symbol, will result in an error if found | S.SomeFixity Fixity {..} <- _nameFixity = Just $
unqualifiedSymbolOp :: SymbolEntry -> Maybe (Precedence, P.Operator Parse Expression) case fixityArity of
unqualifiedSymbolOp S.Name' {..} Unary u -> (fixityPrecedence, P.Postfix (unaryApp <$> parseSymbolId _nameId))
| S.SomeFixity Fixity {..} <- _nameFixity = Just $ where
case fixityArity of unaryApp :: S.Name -> Expression -> Expression
Unary u -> (fixityPrecedence, P.Postfix (unaryApp <$> parseSymbolId _nameId)) unaryApp funName arg = case u of
where AssocPostfix -> ExpressionPostfixApplication (PostfixApplication arg funName)
unaryApp :: S.Name -> Expression -> Expression Binary b -> (fixityPrecedence, infixLRN (binaryApp <$> parseSymbolId _nameId))
unaryApp funName arg = case u of where
AssocPostfix -> ExpressionPostfixApplication (PostfixApplication arg funName) binaryApp :: S.Name -> Expression -> Expression -> Expression
Binary b -> (fixityPrecedence, infixLRN (binaryApp <$> parseSymbolId _nameId)) binaryApp infixAppOperator infixAppLeft infixAppRight =
where ExpressionInfixApplication InfixApplication {..}
binaryApp :: S.Name -> Expression -> Expression -> Expression infixLRN :: Parse (Expression -> Expression -> Expression) -> P.Operator Parse Expression
binaryApp infixAppOperator infixAppLeft infixAppRight = infixLRN = case b of
ExpressionInfixApplication InfixApplication {..} AssocLeft -> P.InfixL
infixLRN :: Parse (Expression -> Expression -> Expression) -> P.Operator Parse Expression AssocRight -> P.InfixR
infixLRN = case b of AssocNone -> P.InfixN
AssocLeft -> P.InfixL | otherwise = Nothing
AssocRight -> P.InfixR parseSymbolId :: S.NameId -> Parse S.Name
AssocNone -> P.InfixN parseSymbolId uid = P.token getName mempty
| otherwise = Nothing where
parseSymbolId :: S.NameId -> Parse S.Name getName :: ExpressionAtom 'Scoped -> Maybe S.Name
parseSymbolId uid = P.token getName mempty getName s = case s of
where AtomIdentifier n'
getName :: ExpressionAtom 'Scoped -> Maybe S.Name | uid == S._nameId n' -> Just n'
getName s = case s of _ -> Nothing
AtomIdentifier n'
| uid == S._nameId n' -> Just n'
_ -> Nothing
-- Application by juxtaposition. -- Application by juxtaposition.
appOp :: P.Operator Parse Expression appOp :: P.Operator Parse Expression
appOp = P.InfixL (app <$ notFollowedByInfix) appOp = P.InfixL (app <$ notFollowedByInfix)
where where
notFollowedByInfix :: Parse () notFollowedByInfix :: Parse ()
notFollowedByInfix = P.notFollowedBy (P.token infixName mempty) notFollowedByInfix = P.notFollowedBy (P.token infixName mempty)
where where
infixName :: ExpressionAtom 'Scoped -> Maybe S.Name infixName :: ExpressionAtom 'Scoped -> Maybe S.Name
infixName s = case s of infixName s = case s of
AtomIdentifier n AtomIdentifier n
| S.hasFixity n -> Just n | S.hasFixity n -> Just n
_ -> Nothing _ -> Nothing
app :: Expression -> Expression -> Expression app :: Expression -> Expression -> Expression
app f x = app f x =
ExpressionApplication ExpressionApplication
Application Application
{ applicationFunction = f, { applicationFunction = f,
applicationParameter = x applicationParameter = x
}
-- Non-dependent function type: A → B
functionOp :: P.Operator Parse Expression
functionOp = P.InfixR (nonDepFun <$ P.single AtomFunArrow)
where
nonDepFun :: Expression -> Expression -> Expression
nonDepFun a b =
ExpressionFunction
Function
{ funParameter = param,
funReturn = b
}
where
param =
FunctionParameter
{ paramName = Nothing,
paramUsage = Nothing,
paramType = a
} }
-- Non-dependent function type: A → B
functionOp :: P.Operator Parse Expression
functionOp = P.InfixR (nonDepFun <$ P.single AtomFunArrow)
where
nonDepFun :: Expression -> Expression -> Expression
nonDepFun a b =
ExpressionFunction
Function
{ funParameter = param,
funReturn = b
}
where
param =
FunctionParameter
{ paramName = Nothing,
paramUsage = Nothing,
paramType = a
}
parseExpressionAtoms :: parseExpressionAtoms ::
Members '[Error ScopeError, State Scope] r => Members '[Error ScopeError, State Scope] r =>
ExpressionAtoms 'Scoped -> ExpressionAtoms 'Scoped ->
Sem r Expression Sem r Expression
parseExpressionAtoms a@(ExpressionAtoms sections) = do parseExpressionAtoms a@(ExpressionAtoms sections) = do
tbl <- makeExpressionTable
let parser :: Parse Expression
parser = runM (mkExpressionParser tbl) <* P.eof
res = P.parse parser filePath (toList sections)
case res of case res of
Left {} -> throw (ErrInfixParser Left {} -> throw (ErrInfixParser
InfixError { InfixError {_infixErrAtoms = a})
_infixErrAtoms = a
})
Right r -> return r Right r -> return r
where where
parser :: Parse Expression
parser = runM (mkExpressionParser tbl) <* P.eof
res = P.parse parser filePath (toList sections)
tbl = makeExpressionTable2 a
filePath = "" filePath = ""
-- | Monad for parsing expression sections. -- | Monad for parsing expression sections.
@ -1168,24 +1158,16 @@ parseTerm =
type ParsePat = P.Parsec () [PatternAtom 'Scoped] type ParsePat = P.Parsec () [PatternAtom 'Scoped]
makePatternTable :: makePatternTable ::
forall r. PatternAtom 'Scoped -> [[P.Operator ParsePat Pattern]]
(Members '[State Scope] r) => makePatternTable atom = [appOp] : operators
Sem r [[P.Operator ParsePat Pattern]]
makePatternTable = do
symbolTable <- mkSymbolTable . toList <$> gets _scopeSymbols
-- application has the highest precedence.
return $ [appOp] : symbolTable
where where
operators = mkSymbolTable names
names = [ s | s@S.Name' {} <- universeBi atom ]
-- TODO think what to do with qualified symbols -- TODO think what to do with qualified symbols
mkSymbolTable :: [SymbolInfo] -> [[P.Operator ParsePat Pattern]] mkSymbolTable :: [S.Name] -> [[P.Operator ParsePat Pattern]]
mkSymbolTable = map (map snd) . groupSortOn fst . mapMaybe (getEntry >=> unqualifiedSymbolOp) mkSymbolTable = map (map snd) . groupSortOn fst . mapMaybe unqualifiedSymbolOp
where where
getEntry :: SymbolInfo -> Maybe SymbolEntry unqualifiedSymbolOp :: S.Name -> Maybe (Precedence, P.Operator ParsePat Pattern)
getEntry (SymbolInfo m) = case toList m of
[] -> impossible
[e] -> Just e
_ -> Nothing -- if this symbol es found will result in an ambiguity error.
unqualifiedSymbolOp :: SymbolEntry -> Maybe (Precedence, P.Operator ParsePat Pattern)
unqualifiedSymbolOp S.Name' {..} unqualifiedSymbolOp S.Name' {..}
| S.SomeFixity Fixity {..} <- _nameFixity, | S.SomeFixity Fixity {..} <- _nameFixity,
_nameKind == S.KNameConstructor = Just $ _nameKind == S.KNameConstructor = Just $
@ -1314,12 +1296,13 @@ mkPatternParser table = embed @ParsePat pPattern
parsePatternAtom :: parsePatternAtom ::
Members '[Error ScopeError, State Scope] r => PatternAtom 'Scoped -> Sem r Pattern Members '[Error ScopeError, State Scope] r => PatternAtom 'Scoped -> Sem r Pattern
parsePatternAtom sec = do parsePatternAtom sec = do
tbl <- makePatternTable
let parser :: ParsePat Pattern
parser = runM (mkPatternParser tbl) <* P.eof
res = P.parse parser filePath [sec]
case res of case res of
Left {} -> throw (ErrInfixPattern (InfixErrorP sec)) Left {} -> throw (ErrInfixPattern (InfixErrorP sec))
Right r -> return r Right r -> return r
where where
tbl = makePatternTable sec
parser :: ParsePat Pattern
parser = runM (mkPatternParser tbl) <* P.eof
res = P.parse parser filePath [sec]
filePath = "tmp" filePath = "tmp"