Skip to content

Commit

Permalink
fixities
Browse files Browse the repository at this point in the history
  • Loading branch information
janmasrovira committed Aug 24, 2023
1 parent 2fd076d commit 762b7fd
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 8 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -285,12 +285,12 @@ reserveInductiveSymbol ::
Sem r S.Symbol
reserveInductiveSymbol d = reserveSymbolSignatureOf SKNameInductive d (d ^. inductiveName)

-- | The NameKind assigned to the alias is irrelevant.
-- | The NameKind assigned to the alias is irrelevant. We assign it KNameFunction so it can have fixity.
reserveAliasSymbol ::
Members '[Error ScoperError, NameIdGen, State ScoperSyntax, State Scope, Reader BindingStrategy, InfoTableBuilder, State ScoperState] r =>
Symbol ->
Sem r S.Symbol
reserveAliasSymbol = reserveSymbolOf True SKNameLocal Nothing
reserveAliasSymbol = reserveSymbolOf True SKNameFunction Nothing

reserveProjectionSymbol ::
Members '[Error ScoperError, NameIdGen, State ScoperSyntax, State Scope, Reader BindingStrategy, InfoTableBuilder, State ScoperState] r =>
Expand Down Expand Up @@ -1701,7 +1701,7 @@ checkRecordPattern ::
Sem r (RecordPattern 'Scoped)
checkRecordPattern r = do
c' <- getNameOfKind KNameConstructor (r ^. recordPatternConstructor)
fields <- fromMaybeM (return (RecordNameSignature mempty)) (gets (^. scoperConstructorFields . at (c' ^. scopedIden . S.nameId)))
fields <- fromMaybeM (return (RecordNameSignature mempty)) (gets (^. scoperConstructorFields . at (c' ^. scopedIdenName . S.nameId)))
l' <-
if
| null (r ^. recordPatternItems) -> return []
Expand Down Expand Up @@ -2128,7 +2128,7 @@ checkIterator ::
Sem r (Iterator 'Scoped)
checkIterator iter = do
_iteratorName <- checkScopedIden (iter ^. iteratorName)
case _iteratorName ^. scopedIden . S.nameIterator of
case _iteratorName ^. scopedIdenName . S.nameIterator of
Just IteratorAttribs {..} -> do
case _iteratorAttribsInitNum of
Just n
Expand Down Expand Up @@ -2211,7 +2211,7 @@ checkParens e@(ExpressionAtoms as _) = case as of
p :| [] -> case p of
AtomIdentifier s -> do
scopedId <- checkScopedIden s
let scopedIdenNoFix = over scopedIden (set S.nameFixity Nothing) scopedId
let scopedIdenNoFix = over scopedIdenName (set S.nameFixity Nothing) scopedId
return (ExpressionParensIdentifier scopedIdenNoFix)
AtomIterator i -> ExpressionIterator . set iteratorParens True <$> checkIterator i
AtomCase c -> ExpressionCase . set caseParens True <$> checkCase c
Expand Down Expand Up @@ -2405,15 +2405,15 @@ makeExpressionTable (ExpressionAtoms atoms _) = [recordUpdate] : [appOpExplicit]
AssocNone -> P.InfixN
| otherwise = Nothing
where
S.Name' {..} = iden ^. scopedIden
S.Name' {..} = iden ^. scopedIdenName

parseSymbolId :: S.NameId -> Parse ScopedIden
parseSymbolId uid = P.token getIdentifierWithId mempty
where
getIdentifierWithId :: ExpressionAtom 'Scoped -> Maybe ScopedIden
getIdentifierWithId s = case s of
AtomIdentifier iden
| uid == iden ^. scopedIden . S.nameId -> Just iden
| uid == iden ^. scopedIdenName . S.nameId -> Just iden
_ -> Nothing

recordUpdate :: P.Operator Parse Expression
Expand Down Expand Up @@ -2600,7 +2600,7 @@ parseTerm =
identifierNoFixity :: ExpressionAtom 'Scoped -> Maybe ScopedIden
identifierNoFixity s = case s of
AtomIdentifier iden
| not (S.hasFixity (iden ^. scopedIden)) -> Just iden
| not (S.hasFixity (iden ^. scopedIdenName)) -> Just iden
_ -> Nothing

parseBraces :: Parse Expression
Expand Down
8 changes: 8 additions & 0 deletions tests/positive/Alias.juvix
Original file line number Diff line number Diff line change
Expand Up @@ -40,3 +40,11 @@ syntax operator || logical;
syntax alias or := ||;

or3 (a b c : Binary) : Binary := or (or a b) c;

type Pair :=
| mkPair Binary Binary;

syntax operator , pair;
syntax alias , := mkPair;

myPair : Pair := one , ⊥;

0 comments on commit 762b7fd

Please sign in to comment.