Skip to content

Commit

Permalink
v1800-2023: type parameters can now have a type restriction applied
Browse files Browse the repository at this point in the history
  • Loading branch information
MikePopoloski committed Mar 10, 2024
1 parent 776202b commit 50fe058
Show file tree
Hide file tree
Showing 24 changed files with 282 additions and 189 deletions.
4 changes: 2 additions & 2 deletions bindings/python/TypeBindings.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -246,10 +246,10 @@ void registerTypes(py::module_& m) {
.def_property_readonly("modport",
[](const VirtualInterfaceType& self) { return self.modport; });

EXPOSE_ENUM(m, ForwardTypedefCategory);
EXPOSE_ENUM(m, ForwardTypeRestriction);

py::class_<ForwardingTypedefSymbol, Symbol>(m, "ForwardingTypedefSymbol")
.def_readonly("category", &ForwardingTypedefSymbol::category)
.def_readonly("typeRestriction", &ForwardingTypedefSymbol::typeRestriction)
.def_readonly("visibility", &ForwardingTypedefSymbol::visibility)
.def_property_readonly("nextForwardDecl", [](const ForwardingTypedefSymbol& self) {
return self.getNextForwardDecl();
Expand Down
9 changes: 9 additions & 0 deletions include/slang/ast/SemanticFacts.h
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ class ASTSerializer;
class ASTContext;
class Scope;
class TimingControl;
class Type;
enum class SymbolKind;

#define LIFETIME(x) x(Automatic) x(Static)
Expand Down Expand Up @@ -102,6 +103,10 @@ SLANG_ENUM(ChargeStrength, CS)
SLANG_ENUM(DriveStrength, DS)
#undef DS

#define FTR(x) x(None) x(Enum) x(Struct) x(Union) x(Class) x(InterfaceClass)
SLANG_ENUM(ForwardTypeRestriction, FTR);
#undef FTR

/// A set of flags that control how assignments are checked.
enum class SLANG_EXPORT AssignFlags : uint8_t {
/// No special assignment behavior specified.
Expand Down Expand Up @@ -165,6 +170,10 @@ class SLANG_EXPORT SemanticFacts {
static std::pair<std::optional<DriveStrength>, std::optional<DriveStrength>> getDriveStrength(
const syntax::NetStrengthSyntax& syntax);

static ForwardTypeRestriction getTypeRestriction(syntax::ForwardTypeRestrictionSyntax& syntax);
static ForwardTypeRestriction getTypeRestriction(const Type& type);
static std::string_view getTypeRestrictionText(ForwardTypeRestriction typeRestriction);

static void populateTimeScale(TimeScale& timeScale, const Scope& scope,
const syntax::TimeUnitsDeclarationSyntax& syntax,
std::optional<SourceRange>& unitsRange,
Expand Down
5 changes: 4 additions & 1 deletion include/slang/ast/symbols/ParameterSymbols.h
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
//------------------------------------------------------------------------------
#pragma once

#include "slang/ast/SemanticFacts.h"
#include "slang/ast/symbols/ValueSymbol.h"
#include "slang/syntax/SyntaxFwd.h"

Expand Down Expand Up @@ -68,9 +69,10 @@ class SLANG_EXPORT ParameterSymbol : public ValueSymbol, public ParameterSymbolB
class SLANG_EXPORT TypeParameterSymbol : public Symbol, public ParameterSymbolBase {
public:
DeclaredType targetType;
ForwardTypeRestriction typeRestriction;

TypeParameterSymbol(const Scope& scope, std::string_view name, SourceLocation loc, bool isLocal,
bool isPort);
bool isPort, ForwardTypeRestriction typeRestriction);

static void fromSyntax(const Scope& scope, const syntax::TypeParameterDeclarationSyntax& syntax,
bool isLocal, bool isPort,
Expand All @@ -80,6 +82,7 @@ class SLANG_EXPORT TypeParameterSymbol : public Symbol, public ParameterSymbolBa

const Type& getTypeAlias() const { return *typeAlias; }
bool isOverridden() const;
void checkTypeRestriction() const;

void serializeTo(ASTSerializer& serializer) const;

Expand Down
15 changes: 4 additions & 11 deletions include/slang/ast/types/AllTypes.h
Original file line number Diff line number Diff line change
Expand Up @@ -428,36 +428,29 @@ class SLANG_EXPORT VirtualInterfaceType : public Type {
static bool isKind(SymbolKind kind) { return kind == SymbolKind::VirtualInterfaceType; }
};

#define CATEGORY(x) x(None) x(Enum) x(Struct) x(Union) x(Class) x(InterfaceClass)
SLANG_ENUM(ForwardTypedefCategory, CATEGORY);
#undef CATEGORY

/// A forward declaration of a user-defined type name. A given type name can have
/// an arbitrary number of forward declarations in the same scope, so each symbol
/// forms a linked list, headed by the actual type definition.
class SLANG_EXPORT ForwardingTypedefSymbol : public Symbol {
public:
ForwardTypedefCategory category;
ForwardTypeRestriction typeRestriction;
std::optional<Visibility> visibility;

ForwardingTypedefSymbol(std::string_view name, SourceLocation loc,
ForwardTypedefCategory category) :
ForwardTypeRestriction typeRestriction) :
Symbol(SymbolKind::ForwardingTypedef, name, loc),
category(category) {}
typeRestriction(typeRestriction) {}

static ForwardingTypedefSymbol& fromSyntax(
const Scope& scope, const syntax::ForwardTypedefDeclarationSyntax& syntax);

static ForwardingTypedefSymbol& fromSyntax(
const Scope& scope, const syntax::ForwardInterfaceClassTypedefDeclarationSyntax& syntax);

static ForwardingTypedefSymbol& fromSyntax(
const Scope& scope, const syntax::ClassPropertyDeclarationSyntax& syntax);

void addForwardDecl(const ForwardingTypedefSymbol& decl) const;
const ForwardingTypedefSymbol* getNextForwardDecl() const { return next; }

void checkType(ForwardTypedefCategory checkCategory, Visibility checkVisibility,
void checkType(ForwardTypeRestriction checkRestriction, Visibility checkVisibility,
SourceLocation declLoc) const;

void serializeTo(ASTSerializer& serializer) const;
Expand Down
1 change: 1 addition & 0 deletions include/slang/parsing/Parser.h
Original file line number Diff line number Diff line change
Expand Up @@ -274,6 +274,7 @@ class SLANG_EXPORT Parser : ParserBase, syntax::SyntaxFacts {
syntax::MemberSyntax* parseClockingItem();
syntax::MemberSyntax& parseClockingDeclaration(AttrList attributes);
syntax::MemberSyntax& parseDefaultDisable(AttrList attributes);
syntax::ForwardTypeRestrictionSyntax* parseTypeRestriction(bool isExpected);
syntax::MemberSyntax& parseVariableDeclaration(AttrList attributes);
syntax::DataDeclarationSyntax& parseDataDeclaration(AttrList attributes);
syntax::LocalVariableDeclarationSyntax& parseLocalVariableDeclaration();
Expand Down
11 changes: 11 additions & 0 deletions include/slang/syntax/SyntaxTree.h
Original file line number Diff line number Diff line change
Expand Up @@ -90,12 +90,23 @@ class SLANG_EXPORT SyntaxTree {
std::string_view name = "source",
std::string_view path = "");

/// Creates a syntax tree by guessing at what might be in the given source snippet.
/// @a text is the actual source code text.
/// @a options is a bag of lexer, preprocessor, and parser options.
/// @a name is an optional name to give to the loaded source buffer.
/// @a path is an optional path to give to the loaded source buffer.
/// @return the created and parsed syntax tree.
static std::shared_ptr<SyntaxTree> fromText(std::string_view text, const Bag& options,
std::string_view name = "source"sv,
std::string_view path = "");

/// Creates a syntax tree by guessing at what might be in the given source snippet.
/// @a text is the actual source code text.
/// @a sourceManager is the manager that owns all of the loaded source code.
/// @a name is an optional name to give to the loaded source buffer.
/// @a path is an optional path to give to the loaded source buffer.
/// @a options is an optional bag of lexer, preprocessor, and parser options.
/// @a library the source library to associated with the parsed tree
/// @return the created and parsed syntax tree.
static std::shared_ptr<SyntaxTree> fromText(std::string_view text, SourceManager& sourceManager,
std::string_view name = "source"sv,
Expand Down
1 change: 1 addition & 0 deletions scripts/diagnostics.txt
Original file line number Diff line number Diff line change
Expand Up @@ -504,6 +504,7 @@ error ConfigDupTop "config design specifies more than one top cell named '{}'"
error ConfigOverrideTop "config rule can't override a top cell with a different target"
error ConfigInstanceUnderOtherConfig "config instance rule applies to an instance that is within a hierarchy specified by another config"
error ConfigParamsForPrimitive "cannot provide parameter assignments for primitive instance"
error TypeRestrictionMismatch "type restriction '{}' does not match assigned type {}"
error FatalTask "$fatal encountered{}"
error ErrorTask "$error encountered{}"
error StaticAssert "static assertion failed{}"
Expand Down
14 changes: 6 additions & 8 deletions scripts/syntax.txt
Original file line number Diff line number Diff line change
Expand Up @@ -503,6 +503,10 @@ DataType type
separated_list<Declarator> declarators
token semi

ForwardTypeRestriction
token keyword1
token keyword2

TypedefDeclaration base=Member
token typedefKeyword
DataType type
Expand All @@ -512,14 +516,7 @@ token semi

ForwardTypedefDeclaration base=Member
token typedefKeyword
token keyword
token name
token semi

ForwardInterfaceClassTypedefDeclaration base=Member
token typedefKeyword
token interfaceKeyword
token classKeyword
ForwardTypeRestriction? typeRestriction
token name
token semi

Expand Down Expand Up @@ -608,6 +605,7 @@ EqualsTypeClause? assignment

TypeParameterDeclaration base=ParameterDeclarationBase
token typeKeyword
ForwardTypeRestriction? typeRestriction
separated_list<TypeAssignment> declarators

ParameterDeclarationStatement base=Member
Expand Down
6 changes: 6 additions & 0 deletions source/ast/ElabVisitors.h
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,12 @@ struct DiagnosticVisitor : public ASTVisitor<DiagnosticVisitor, false, false> {
symbol.getType();
}

void handle(const TypeParameterSymbol& symbol) {
if (!handleDefault(symbol))
return;
symbol.checkTypeRestriction();
}

void handle(const ContinuousAssignSymbol& symbol) {
if (!handleDefault(symbol))
return;
Expand Down
10 changes: 1 addition & 9 deletions source/ast/Scope.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -356,13 +356,6 @@ void Scope::addMembers(const SyntaxNode& syntax) {
getOrAddDeferredData().addForwardingTypedef(symbol);
break;
}
case SyntaxKind::ForwardInterfaceClassTypedefDeclaration: {
auto& symbol = ForwardingTypedefSymbol::fromSyntax(
*this, syntax.as<ForwardInterfaceClassTypedefDeclarationSyntax>());
addMember(symbol);
getOrAddDeferredData().addForwardingTypedef(symbol);
break;
}
case SyntaxKind::GenerateRegion:
for (auto member : syntax.as<GenerateRegionSyntax>().members)
addMembers(*member);
Expand Down Expand Up @@ -397,8 +390,7 @@ void Scope::addMembers(const SyntaxNode& syntax) {
case SyntaxKind::TypedefDeclaration:
addMember(TypeAliasType::fromSyntax(*this, cpd));
break;
case SyntaxKind::ForwardTypedefDeclaration:
case SyntaxKind::ForwardInterfaceClassTypedefDeclaration: {
case SyntaxKind::ForwardTypedefDeclaration: {
auto& symbol = ForwardingTypedefSymbol::fromSyntax(*this, cpd);
addMember(symbol);
getOrAddDeferredData().addForwardingTypedef(symbol);
Expand Down
57 changes: 57 additions & 0 deletions source/ast/SemanticFacts.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,8 @@
#include "slang/ast/ASTSerializer.h"
#include "slang/ast/Scope.h"
#include "slang/ast/TimingControl.h"
#include "slang/ast/symbols/ClassSymbols.h"
#include "slang/ast/types/Type.h"
#include "slang/diagnostics/DeclarationsDiags.h"
#include "slang/diagnostics/PreprocessorDiags.h"
#include "slang/syntax/AllSyntax.h"
Expand Down Expand Up @@ -200,6 +202,61 @@ StatementBlockKind SemanticFacts::getStatementBlockKind(const BlockStatementSynt
}
}

ForwardTypeRestriction SemanticFacts::getTypeRestriction(
syntax::ForwardTypeRestrictionSyntax& syntax) {
switch (syntax.keyword1.kind) {
case TokenKind::EnumKeyword:
return ForwardTypeRestriction::Enum;
case TokenKind::StructKeyword:
return ForwardTypeRestriction::Struct;
case TokenKind::UnionKeyword:
return ForwardTypeRestriction::Union;
case TokenKind::ClassKeyword:
return ForwardTypeRestriction::Class;
case TokenKind::InterfaceKeyword:
return ForwardTypeRestriction::InterfaceClass;
default:
return ForwardTypeRestriction::None;
}
}

ForwardTypeRestriction SemanticFacts::getTypeRestriction(const Type& type) {
auto& ct = type.getCanonicalType();
switch (ct.kind) {
case SymbolKind::PackedStructType:
case SymbolKind::UnpackedStructType:
return ForwardTypeRestriction::Struct;
case SymbolKind::PackedUnionType:
case SymbolKind::UnpackedUnionType:
return ForwardTypeRestriction::Union;
case SymbolKind::EnumType:
return ForwardTypeRestriction::Enum;
case SymbolKind::ClassType:
if (ct.as<ClassType>().isInterface)
return ForwardTypeRestriction::InterfaceClass;
return ForwardTypeRestriction::Class;
default:
return ForwardTypeRestriction::None;
}
}

std::string_view SemanticFacts::getTypeRestrictionText(ForwardTypeRestriction typeRestriction) {
switch (typeRestriction) {
case ForwardTypeRestriction::Enum:
return "enum"sv;
case ForwardTypeRestriction::Struct:
return "struct"sv;
case ForwardTypeRestriction::Union:
return "union"sv;
case ForwardTypeRestriction::Class:
return "class"sv;
case ForwardTypeRestriction::InterfaceClass:
return "interface class"sv;
default:
return ""sv;
}
}

void SemanticFacts::populateTimeScale(TimeScale& timeScale, const Scope& scope,
const TimeUnitsDeclarationSyntax& syntax,
std::optional<SourceRange>& unitsRange,
Expand Down
1 change: 0 additions & 1 deletion source/ast/Statements.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -581,7 +581,6 @@ std::span<const StatementBlockSymbol* const> Statement::createAndAddBlockItems(
case SyntaxKind::DataDeclaration:
case SyntaxKind::TypedefDeclaration:
case SyntaxKind::ForwardTypedefDeclaration:
case SyntaxKind::ForwardInterfaceClassTypedefDeclaration:
case SyntaxKind::PackageImportDeclaration:
case SyntaxKind::ParameterDeclarationStatement:
case SyntaxKind::LetDeclaration:
Expand Down
12 changes: 6 additions & 6 deletions source/ast/symbols/ClassSymbols.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -130,10 +130,10 @@ void ClassType::addForwardDecl(const ForwardingTypedefSymbol& decl) const {

void ClassType::checkForwardDecls() const {
if (firstForward) {
auto category = ForwardTypedefCategory::Class;
auto typeRestriction = ForwardTypeRestriction::Class;
if (isInterface)
category = ForwardTypedefCategory::InterfaceClass;
firstForward->checkType(category, Visibility::Public, location);
typeRestriction = ForwardTypeRestriction::InterfaceClass;
firstForward->checkType(typeRestriction, Visibility::Public, location);
}
}

Expand Down Expand Up @@ -909,10 +909,10 @@ void GenericClassDefSymbol::addForwardDecl(const ForwardingTypedefSymbol& decl)

void GenericClassDefSymbol::checkForwardDecls() const {
if (firstForward) {
auto category = ForwardTypedefCategory::Class;
auto typeRestriction = ForwardTypeRestriction::Class;
if (isInterface)
category = ForwardTypedefCategory::InterfaceClass;
firstForward->checkType(category, Visibility::Public, location);
typeRestriction = ForwardTypeRestriction::InterfaceClass;
firstForward->checkType(typeRestriction, Visibility::Public, location);
}
}

Expand Down
7 changes: 6 additions & 1 deletion source/ast/symbols/ParameterBuilder.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -145,8 +145,13 @@ const ParameterSymbolBase& ParameterBuilder::createParam(
std::tie(newInitializer, isFromConfig) = it->second;

if (decl.isTypeParam) {
auto typeRestriction = ForwardTypeRestriction::None;
if (decl.hasSyntax && decl.typeSyntax && decl.typeSyntax->typeRestriction)
typeRestriction = SemanticFacts::getTypeRestriction(*decl.typeSyntax->typeRestriction);

auto param = comp.emplace<TypeParameterSymbol>(newScope, decl.name, decl.location,
decl.isLocalParam, decl.isPortParam);
decl.isLocalParam, decl.isPortParam,
typeRestriction);
param->setAttributes(scope, decl.attributes);

auto& tt = param->targetType;
Expand Down
Loading

0 comments on commit 50fe058

Please sign in to comment.