Skip to content

Commit

Permalink
refactor: remove IntegerBOZ from ASR.asdl and subsequent changes
Browse files Browse the repository at this point in the history
  • Loading branch information
Pranavchiku committed Jul 12, 2024
1 parent 8d57583 commit bc450c8
Show file tree
Hide file tree
Showing 6 changed files with 6 additions and 28 deletions.
6 changes: 0 additions & 6 deletions src/lfortran/semantics/ast_common_visitor.h
Original file line number Diff line number Diff line change
Expand Up @@ -4107,12 +4107,6 @@ class CommonVisitor : public AST::BaseVisitor<Derived> {
} else {
throw SemanticError("int(...) must have 1 or 2 arguments", loc);
}
if (ASR::is_a<ASR::IntegerBOZ_t>(*args[0].m_value)) {
// Things like `int(b'01011101')` are skipped for now
// They are converted in comptime_eval. We should probably
// just convert them here instead.
return nullptr;
}
return LFortran::CommonVisitorMethods::comptime_intrinsic_int(args[0].m_value, arg1, al, loc, compiler_options);
} else {
return nullptr;
Expand Down
7 changes: 1 addition & 6 deletions src/lfortran/semantics/comptime_eval.h
Original file line number Diff line number Diff line change
Expand Up @@ -244,13 +244,8 @@ struct IntrinsicProcedures {
}
}

static ASR::expr_t *eval_int(Allocator &al, const Location &loc, Vec<ASR::expr_t*> &args, const CompilerOptions &compiler_options) {
static ASR::expr_t *eval_int(Allocator &al, const Location &loc, Vec<ASR::expr_t*> &args, const CompilerOptions &/*compiler_options*/) {
ASR::expr_t* int_expr = args[0];
if( int_expr->type == ASR::exprType::IntegerBOZ ) {
ASR::IntegerBOZ_t *boz_expr = ASR::down_cast<ASR::IntegerBOZ_t>(int_expr);
ASR::ttype_t* tmp_int_type = ASRUtils::TYPE(ASR::make_Integer_t(al, loc, compiler_options.po.default_integer_kind));
return ASR::down_cast<ASR::expr_t>(ASR::make_IntegerConstant_t(al, loc, boz_expr->m_v, tmp_int_type));;
}
ASR::ttype_t* int_type = ASRUtils::expr_type(int_expr);
int int_kind = ASRUtils::extract_kind_from_ttype_t(int_type);
if (ASR::is_a<ASR::Integer_t>(*int_type)) {
Expand Down
1 change: 0 additions & 1 deletion src/libasr/ASR.asdl
Original file line number Diff line number Diff line change
Expand Up @@ -89,7 +89,6 @@ expr
| UnionTypeConstructor(symbol dt_sym, expr* args, ttype type, expr? value)
| ImpliedDoLoop(expr* values, expr var, expr start, expr end, expr? increment, ttype type, expr? value)
| IntegerConstant(int n, ttype type, integerboz intboz_type)
| IntegerBOZ(int v, integerboz intboz_type, ttype? type)
| IntegerBitNot(expr arg, ttype type, expr? value)
| IntegerUnaryMinus(expr arg, ttype type, expr? value)
| IntegerCompare(expr left, cmpop op, expr right, ttype type, expr? value)
Expand Down
2 changes: 1 addition & 1 deletion src/libasr/asdl_cpp.py
Original file line number Diff line number Diff line change
Expand Up @@ -2604,7 +2604,7 @@ def make_visitor(self, name, fields):
return ASR::down_cast<ASR::Variable_t>(s)->m_value;
}""" \
% (name, name), 2, new_line=False)
elif name.endswith("Constant") or name == "IntegerBOZ":
elif name.endswith("Constant"):
self.emit("case ASR::exprType::%s: { return f; }"\
% (name), 2, new_line=False)
else:
Expand Down
15 changes: 3 additions & 12 deletions src/libasr/asr_utils.h
Original file line number Diff line number Diff line change
Expand Up @@ -1052,7 +1052,6 @@ static inline bool is_value_constant(ASR::expr_t *a_value) {
}
switch ( a_value->type ) {
case ASR::exprType::IntegerConstant:
case ASR::exprType::IntegerBOZ:
case ASR::exprType::UnsignedIntegerConstant:
case ASR::exprType::RealConstant:
case ASR::exprType::ComplexConstant:
Expand Down Expand Up @@ -1380,11 +1379,6 @@ static inline bool extract_value(ASR::expr_t* value_expr, T& value) {
value = (T) const_int->m_n;
break;
}
case ASR::exprType::IntegerBOZ: {
ASR::IntegerBOZ_t* int_boz = ASR::down_cast<ASR::IntegerBOZ_t>(value_expr);
value = (T) int_boz->m_v;
break;
}
case ASR::exprType::UnsignedIntegerConstant: {
ASR::UnsignedIntegerConstant_t* const_int = ASR::down_cast<ASR::UnsignedIntegerConstant_t>(value_expr);
value = (T) const_int->m_n;
Expand Down Expand Up @@ -5461,8 +5455,7 @@ static inline void Call_t_body(Allocator& al, ASR::symbol_t* a_name,
ASR::FunctionType_t* func_type = get_FunctionType(a_name);

for( size_t i = 0; i < n_args; i++ ) {
if( a_args[i].m_value == nullptr ||
ASR::is_a<ASR::IntegerBOZ_t>(*a_args[i].m_value) ) {
if( a_args[i].m_value == nullptr ) {
continue;
}
ASR::expr_t* arg = a_args[i].m_value;
Expand Down Expand Up @@ -5690,8 +5683,7 @@ static inline ASR::asr_t* make_IntrinsicElementalFunction_t_util(
ASR::ttype_t* a_type, ASR::expr_t* a_value) {

for( size_t i = 0; i < n_args; i++ ) {
if( a_args[i] == nullptr ||
ASR::is_a<ASR::IntegerBOZ_t>(*a_args[i]) ) {
if( a_args[i] == nullptr ) {
continue;
}
ASR::expr_t* arg = a_args[i];
Expand All @@ -5713,8 +5705,7 @@ static inline ASR::asr_t* make_IntrinsicArrayFunction_t_util(
ASR::ttype_t* a_type, ASR::expr_t* a_value) {

for( size_t i = 0; i < n_args; i++ ) {
if( a_args[i] == nullptr ||
ASR::is_a<ASR::IntegerBOZ_t>(*a_args[i]) ) {
if( a_args[i] == nullptr ) {
continue;
}
ASR::expr_t* arg = a_args[i];
Expand Down
3 changes: 1 addition & 2 deletions src/libasr/codegen/asr_to_fortran.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1355,6 +1355,7 @@ class ASRToFortranVisitor : public ASR::BaseVisitor<ASRToFortranVisitor>
}

void visit_IntegerConstant(const ASR::IntegerConstant_t &x) {
// TODO: handle IntegerBOZ
src = std::to_string(x.m_n);
int kind = ASRUtils::extract_kind_from_ttype_t(x.m_type);
if (kind != 4) {
Expand All @@ -1365,8 +1366,6 @@ class ASRToFortranVisitor : public ASR::BaseVisitor<ASRToFortranVisitor>
last_expr_precedence = Precedence::Ext;
}

// void visit_IntegerBOZ(const ASR::IntegerBOZ_t &x) {}

// void visit_IntegerBitNot(const ASR::IntegerBitNot_t &x) {}

void visit_IntegerUnaryMinus(const ASR::IntegerUnaryMinus_t &x) {
Expand Down

0 comments on commit bc450c8

Please sign in to comment.