-
Notifications
You must be signed in to change notification settings - Fork 57
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Store syntax aliases in serialized scoper infotable
- Loading branch information
1 parent
84b0e56
commit 97f3018
Showing
10 changed files
with
119 additions
and
78 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,78 @@ | ||
module Juvix.Compiler.Store.Scoped.Data.SymbolEntry where | ||
|
||
import Juvix.Compiler.Concrete.Data.ScopedName (HasNameKind) | ||
import Juvix.Compiler.Concrete.Data.ScopedName qualified as S | ||
import Juvix.Extra.Serialize | ||
import Juvix.Prelude | ||
|
||
newtype Alias = Alias | ||
{ _aliasName :: S.Name | ||
} | ||
deriving stock (Show, Eq, Ord, Generic) | ||
|
||
instance Serialize Alias | ||
|
||
-- | Either an alias or a symbol entry. | ||
data PreSymbolEntry | ||
= PreSymbolAlias Alias | ||
| PreSymbolFinal SymbolEntry | ||
deriving stock (Show, Eq, Ord, Generic) | ||
|
||
instance Serialize PreSymbolEntry | ||
|
||
-- | A symbol which is not an alias. | ||
newtype SymbolEntry = SymbolEntry | ||
{ _symbolEntry :: S.Name | ||
} | ||
deriving stock (Show, Eq, Ord, Generic) | ||
|
||
instance Hashable SymbolEntry | ||
|
||
instance Serialize SymbolEntry | ||
|
||
newtype ModuleSymbolEntry = ModuleSymbolEntry | ||
{ _moduleEntry :: S.Name | ||
} | ||
deriving stock (Show, Eq, Ord, Generic) | ||
|
||
instance Serialize ModuleSymbolEntry | ||
|
||
newtype FixitySymbolEntry = FixitySymbolEntry | ||
{ _fixityEntry :: S.Name | ||
} | ||
deriving stock (Show, Eq, Ord, Generic) | ||
|
||
instance Serialize FixitySymbolEntry | ||
|
||
makeLenses ''Alias | ||
makeLenses ''SymbolEntry | ||
makeLenses ''ModuleSymbolEntry | ||
makeLenses ''FixitySymbolEntry | ||
|
||
instance HasLoc Alias where | ||
getLoc = (^. aliasName . S.nameDefined) | ||
|
||
instance HasLoc PreSymbolEntry where | ||
getLoc = \case | ||
PreSymbolAlias a -> getLoc a | ||
PreSymbolFinal a -> getLoc a | ||
|
||
instance HasLoc SymbolEntry where | ||
getLoc = (^. symbolEntry . S.nameDefined) | ||
|
||
instance HasNameKind ModuleSymbolEntry where | ||
getNameKind (ModuleSymbolEntry s) = S.getNameKind s | ||
|
||
instance HasLoc ModuleSymbolEntry where | ||
getLoc (ModuleSymbolEntry s) = s ^. S.nameDefined | ||
|
||
symbolEntryNameId :: SymbolEntry -> NameId | ||
symbolEntryNameId = (^. symbolEntry . S.nameId) | ||
|
||
instance HasNameKind SymbolEntry where | ||
getNameKind = S.getNameKind . (^. symbolEntry) | ||
|
||
preSymbolName :: Lens' PreSymbolEntry S.Name | ||
preSymbolName f = \case | ||
PreSymbolAlias a -> PreSymbolAlias <$> traverseOf aliasName f a | ||
PreSymbolFinal a -> PreSymbolFinal <$> traverseOf symbolEntry f a |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1 @@ | ||
11 |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
module Package; | ||
|
||
import PackageDescription.V2 open; | ||
|
||
package : Package := defaultPackage {name := "test073"}; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
module SyntaxAlias; | ||
|
||
import Stdlib.Prelude open; | ||
|
||
syntax alias MyNat := Nat; |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,5 @@ | ||
module test073; | ||
|
||
import SyntaxAlias open; | ||
|
||
main : MyNat := 11; |