program bug
character(len=*),parameter :: chars(2)= [ '" ', ''' ']
write(*,*)chars
end program bug
(test1) urbanjs@venus:~/github/_scratch$ lfortran fmt xx.f90
program bug
character(len=*), parameter :: chars(2) = ['" ', "'' "]
write(*, *) chars
end program bug
in this one it is changing single quote to double quote delimiters for strings but not taking into account that a single quote doubled inside of single quotes should just become a single quote if placed in double quotes.
There are some subtle things about complex numbers. I have to edit this post because Discourse is not allowing more than two posts without an answer in-between, so this is
a third one.
program bug
COMPLEX*16 C
DOUBLE PRECISION ABS1
! .. Statement Function definitions ..
ABS1( C ) = ABS( DBLE( C ) ) + ABS( DIMAG( C ) )
write(*,*)abs1((10.0d0,20.0d0))
end program bug
program bug
complex(16) :: C
double precision :: ABS1
! .. Statement Function definitions ..
ABS1(C) = ABS(DBLE(C)) + ABS(DIMAG(C))
write(*, *) abs1((10.0d0, 20.0d0))
end program bug
besides the obvious issue, converting the non-standard COMPLEX*16 to COMPLEX(16) is not a sure bet
If these ones are fixed it would fix multiple cases that I found. Haven’t verified it yet, but if the issue with the label at the end of the case applies to other named structures and blocks that will be a bunch of the remaining ones.
As far as the comments now being included it would be nice if they were colored to distinguish them from the code. Typically I think blue is used for the comments.
Something more feasible for an actual AST interpretation of the code and a compiler put that a basic colorizer could not do would be to have an option to add INTENT and/or PURE and ELEMENTAL and maybe automatic interfaces; even if just routines with no externals for something down the road.
________________________________________________
function base2_fdo(x) result(str)
! return string representing number as a binary number. Fixed-length string: do concurrent
integer, intent(in) :: x
character(len=max(1,bit_size(x)-leadz(x))) :: str
integer :: n, i
if (x == 0) then
str(1:1) = '0'
return
endif
n = len(str)
str = repeat('0',n)
do concurrent (i = 0:n-1, btest(x,i))
str(n-i:n-i) = '1'
end do
end function base2_fdo
function base2_fdo(x) result(str)
! return string representing number as a binary number. Fixed-length string: do concurrent
integer, intent(in) :: x
character(len=max(1, bit_size(x) - leadz(x))) :: str
integer :: n, i
if (x == 0) then
str(1:1) = "0"
return
end if
n = len(str)
str = repeat("0", n)
do concurrent (i = 0:n - 1)btest(x, i)
str(n - i:n - i) = "1"
end do
end function base2_fdo
----------------------------------------------------------------------------------------
just to confirm the ending label is removed from IF and not just SELECT
program bug
LABEL: if(0.eq.0)then
endif LABEL
end program bug
program bug
LABEL: if (0 == 0) then
end if
end program bug
This may be related to the previous issue with quotes, but is distinct enough to mention it
program bug
use,intrinsic :: iso_c_binding
implicit none
integer(C_INT),parameter :: KEY_C3 = INT(O'540',C_INT) ! lower right of keypad
end program bug
program bug
use, intrinsic :: iso_c_binding
implicit none
integer(C_INT), parameter :: KEY_C3 = INT("O'540'", C_INT) ! lower right of keypad
end program bug
_______________________________________________
So that is from over 690 000, source lines. I do not currently have time available for more but pretty sure that is over 90/100 of the issues I could find so that is very encouraging. A compiler vendor gave me a “Hulk Smash” tee-shirt once for having the most bug submittals from any customer, makes me feel like I still have the touch :> So from experience this is looking exciting, I hope this list does not appear to come across negatively.