Skip to content

Commit

Permalink
rename intrinsic to intr for consistency
Browse files Browse the repository at this point in the history
  • Loading branch information
JeffIrwin committed Oct 27, 2024
1 parent 54f6823 commit 5566bfc
Show file tree
Hide file tree
Showing 7 changed files with 13 additions and 13 deletions.
2 changes: 1 addition & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -107,7 +107,7 @@ set(LIB_SRC
${SRC_DIR}/parse_array.f90
${SRC_DIR}/parse_control.f90
${SRC_DIR}/parse_expr.f90
${SRC_DIR}/intrinsic_fns.f90
${SRC_DIR}/intr_fns.f90
${SRC_DIR}/parse_fn.f90
${SRC_DIR}/parse_misc.f90
${SRC_DIR}/parse.f90
Expand Down
2 changes: 1 addition & 1 deletion src/core.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ module syntran__core_m
use syntran__consts_m
use syntran__errors_m
use syntran__eval_m
use syntran__intrinsic_fns_m
use syntran__intr_fns_m
use syntran__parse_m
use syntran__types_m
use syntran__utils_m
Expand Down
2 changes: 1 addition & 1 deletion src/eval.f90
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ module syntran__eval_m
!********

type state_t
! Run time state
! Run time (eval time) state

logical :: quiet

Expand Down
8 changes: 4 additions & 4 deletions src/intrinsic_fns.f90 → src/intr_fns.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@

!===============================================================================

module syntran__intrinsic_fns_m
module syntran__intr_fns_m

use syntran__types_m

Expand All @@ -13,7 +13,7 @@ module syntran__intrinsic_fns_m

!===============================================================================

subroutine declare_intrinsic_fns(fns)
subroutine declare_intr_fns(fns)

type(fns_t), intent(out) :: fns

Expand Down Expand Up @@ -1000,7 +1000,7 @@ subroutine declare_intrinsic_fns(fns)
any_fn &
]

end subroutine declare_intrinsic_fns
end subroutine declare_intr_fns

!===============================================================================

Expand Down Expand Up @@ -1350,7 +1350,7 @@ end subroutine resolve_overload

!===============================================================================

end module syntran__intrinsic_fns_m
end module syntran__intr_fns_m

!===============================================================================

6 changes: 3 additions & 3 deletions src/parse_fn.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@

submodule (syntran__parse_m) syntran__parse_fn

use syntran__intrinsic_fns_m
use syntran__intr_fns_m

implicit none

Expand Down Expand Up @@ -101,7 +101,7 @@ recursive module function parse_fn_call(parser) result(fn_call)

end if

if (fn%is_intrinsic) fn_call%kind = fn_call_intr_expr
if (fn%is_intr) fn_call%kind = fn_call_intr_expr

fn_call%val = fn%type
if (has_rank) then
Expand Down Expand Up @@ -263,7 +263,7 @@ module function parse_fn_declaration(parser) result(decl)

identifier = parser%match(identifier_token)
fn_name_end = parser%peek_pos(0) - 1
fn%is_intrinsic = .false.
fn%is_intr = .false.

!print *, "parsing fn ", identifier%text

Expand Down
2 changes: 1 addition & 1 deletion src/syntran.f90
Original file line number Diff line number Diff line change
Expand Up @@ -343,7 +343,7 @@ subroutine init_state(state)

type(state_t), intent(inout) :: state

call declare_intrinsic_fns(state%fns)
call declare_intr_fns(state%fns)

state%returned = .false.

Expand Down
4 changes: 2 additions & 2 deletions src/types.f90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ module syntran__types_m
! the function parameters and body
type(syntax_node_t), allocatable :: node

logical :: is_intrinsic = .true.
logical :: is_intr = .true.

contains
procedure, pass(dst) :: copy => fn_copy
Expand Down Expand Up @@ -405,7 +405,7 @@ recursive subroutine fn_copy(dst, src)
dst%variadic_min = src%variadic_min
dst%variadic_type = src%variadic_type
dst%param_names = src%param_names
dst%is_intrinsic = src%is_intrinsic
dst%is_intr = src%is_intr

if (allocated(src%params)) then
if (allocated(dst%params)) deallocate(dst%params)
Expand Down

0 comments on commit 5566bfc

Please sign in to comment.