Git Product home page Git Product logo

fprettify's Introduction

fprettify

CI Coverage Status PyPI - License PyPI Code Climate

fprettify is an auto-formatter for modern Fortran code that imposes strict whitespace formatting, written in Python.

NOTE: I'm looking for help to maintain this repository, see #127.

Features

  • Auto-indentation.
  • Line continuations are aligned with the previous opening delimiter (, [ or (/ or with an assignment operator = or =>. If none of the above is present, a default hanging indent is applied.
  • Consistent amount of whitespace around operators and delimiters.
  • Removal of extraneous whitespace and consecutive blank lines.
  • Change letter case (upper case / lower case conventions) of intrinsics
  • Tested for editor integration.
  • By default, fprettify causes whitespace changes only and thus preserves revision history.
  • fprettify can handle cpp and fypp preprocessor directives.

Limitations

  • Works only for modern Fortran (Fortran 90 upwards).
  • Feature missing? Please create an issue.

Requirements

  • Python 3 (Python 2.7 no longer supported)
  • ConfigArgParse: optional, enables use of config file

Examples

Compare examples/*before.f90 (original Fortran files) with examples/*after.f90 (reformatted Fortran files) to see what fprettify does. A quick demonstration:

program demo
integer :: endif,if,elseif
integer,DIMENSION(2) :: function
endif=3;if=2
if(endif==2)then
endif=5
elseif=if+4*(endif+&
2**10)
elseif(endif==3)then
function(if)=endif/elseif
print*,endif
endif
end program

⇩⇩⇩⇩⇩⇩⇩⇩⇩⇩ fprettify ⇩⇩⇩⇩⇩⇩⇩⇩⇩⇩

program demo
   integer :: endif, if, elseif
   integer, DIMENSION(2) :: function
   endif = 3; if = 2
   if (endif == 2) then
      endif = 5
      elseif = if + 4*(endif + &
                       2**10)
   elseif (endif == 3) then
      function(if) = endif/elseif
      print *, endif
   endif
end program

Installation

The latest release can be installed using pip:

pip install --upgrade fprettify

Installation from source requires Python Setuptools:

pip install .

For local installation, use --user option.

If you use the Conda package manager, fprettify is available from the conda-forge channel:

conda install -c conda-forge fprettify

Command line tool

Autoformat file1, file2, ... inplace by

fprettify file1, file2, ...

The default indent is 3. If you prefer something else, use --indent n argument.

In order to apply fprettify recursively to an entire Fortran project instead of a single file, use the -r option.

For more options, read

fprettify -h

Editor integration

For editor integration, use

fprettify --silent

For instance, with Vim, use fprettify with gq by putting the following commands in your .vimrc:

autocmd Filetype fortran setlocal formatprg=fprettify\ --silent

Deactivation and manual formatting (experimental feature)

fprettify can be deactivated for selected lines: a single line followed by an inline comment starting with !& is not auto-formatted and consecutive lines that are enclosed between two comment lines !&< and !&> are not auto-formatted. This is useful for cases where manual alignment is preferred over auto-formatting. Furthermore, deactivation is necessary when non-standard Fortran syntax (such as advanced usage of preprocessor directives) prevents proper formatting. As an example, consider the following snippet of fprettify formatted code:

A = [-1, 10, 0, &
     0, 1000, 0, &
     0, -1, 1]

In order to manually align the columns, fprettify needs to be deactivated by

A = [-1,   10, 0, & !&
      0, 1000, 0, & !&
      0,   -1, 1]   !&

or, equivalently by

!&<
A = [-1,   10, 0, &
      0, 1000, 0, &
      0,   -1, 1]
!&>

Contributing / Testing

The testing mechanism allows you to easily test fprettify with any Fortran project of your choice. Simply clone or copy your entire project into fortran_tests/before and run python setup.py test. The directory fortran_tests/after contains the test output (reformatted Fortran files). If testing fails, please submit an issue!

fprettify's People

Contributors

awvwgk avatar blaylockbk avatar dbroemmel avatar dependabot[bot] avatar dev-zero avatar e-kwsm avatar ellio167 avatar gnikit avatar helmutwecke avatar implicitall avatar jhaiduce avatar meteokid avatar paulxicao avatar pseewald avatar quantifiedcode-bot avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

fprettify's Issues

indent nested loops

I suggest that each level of nested loops be indented. For example, fprettify run on

program foo
implicit none
integer :: i,j,k
do i=1,4
do j=1,3
do k=1,10
print*,i+j+k
end do
end do
end do
end program foo

gives

program foo
   implicit none
   integer :: i, j, k
   do i = 1, 4
   do j = 1, 3
   do k = 1, 10
      print *, i + j + k
   end do
   end do
   end do
end program foo

but I would like this:

program foo
   implicit none
   integer :: i, j, k
   do i = 1, 4
      do j = 1, 3
         do k = 1, 10
            print *, i + j + k
         end do
      end do
   end do
end program foo

Interfaces are broken

If I run this piece of code:

module m_metagga

    type t_realspace_potden
        real, allocatable  :: is(:,:), mt(:,:)
    end type t_realspace_potden

    public  :: calc_EnergyDen
    private :: calc_EnergyDen_auxillary_weights, t_realspace_potden, subtract_RS, multiply_RS

    interface operator (-)
        procedure subtract_RS
    end interface operator (-)

    interface operator (*)
        procedure multiply_RS
    end interface operator (*)
contains

[...]

end module m_metagga

I get

module m_metagga

   type t_realspace_potden
      real, allocatable  :: is(:,:), mt(:,:)
   end type t_realspace_potden

   public  :: calc_EnergyDen
   private :: calc_EnergyDen_auxillary_weights, t_realspace_potden, subtract_RS, multiply_RS

   interface operator (-)
      procedure subtract_RS
      end interface operator (-)

         interface operator (*)
            procedure multiply_RS
            end interface operator (*)
            contains

It seems end interface is ignored

Automaticall replace .EQ. with ==

Often times programmers use operators such as .EQ. and .LT. instead of == and <. I think the mathematical kind is much easier to understand.

This could also be an optional feature.

!$OMP indentation

Is it an expected behaviour that the OpenMP directives !$OMPare set to the first column whereas there are allowed to be in any column with free form sources?
If it's normal, would it be possible to have an option to let them follow the current indentation?

enums are ignored on indentation

Consider this (correctly) indented example of an enum:

module Class_atom
    use Class_helper
    use Constants
    use mpi
    implicit none

    enum, bind(c)  !> A or B site in graphene
        enumerator :: A_site, B_site, no_site
    end enum

fprettify turns this into:

module Class_atom
   use Class_helper
   use Constants
   use mpi
   implicit none

   enum, bind(c)  !> A or B site in graphene
   enumerator :: A_site, B_site, no_site
end enum

DO loop is not indented properly

DO 20 i=1,10
...
20 CONTINUE
CONTINUE

I expect this to be indented to:

   DO 20 I=1,10
      ...
20    CONTINUE
   CONTINUE

but instead the final line gets indented even though it does not belong to the loop.

The effect of this is that code that uses this looping style just gets indented progressively deeper.

more than one assignment on the same line

Dear @pseewald

I am using your great tool, thank you very much for sharing it.

I found a strange issue using fprettify on FLAP

→ fprettify -s flap_object_t.f90
ERROR: File flap_object_t.f90, line 6
    Fatal error occured
Traceback (most recent call last):
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 1137, in run
    whitespace=args.whitespace)
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 819, in reformat_inplace
    orig_filename=filename, **kwargs)
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 1009, in reformat_ffile
    stream.line_nr, manual_lines_indent)
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 291, in process_lines_of_fline
    f_line, lines, rel_ind_con, line_nr)
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 403, in process_lines_of_fline
    line, is_decl, rel_ind, self._line_nr + pos)
  File "/usr/lib/python2.7/site-packages/fprettify/__init__.py", line 483, in __align_line_continuations
    "found more than one assignment in the same Fortran line", filename, line_nr)
FprettifyInternalException: found more than one assignment in the same Fortran line

On the line raising the issue there are actually two assignment (aliasing):

use, intrinsic:: ISO_FORTRAN_ENV, only: stdout=>OUTPUT_UNIT, stderr=>ERROR_UNIT

Is this an intended behavior (not support multiple assignments)?

Cheers

various bugs

Formatting fails for the following constructs:

program test
end
print *,
read *,
operator(==)
reshape([real(8)::1, 2, 1, 3, 4, 1, 5, 7, 0], [3, 3])

Use statements are not indented

[Feature request] Support formatting options as modules

I've seen a code which mixes .gt. and > - awful!
Thought about contributing this... but stumbled across the longish __init__.py.

It's very difficult to find out where such a thing should be added. What I thought about was: plugins.

If there were a directory plugins, then adding a new formatting option would be as simple as:

  1. Write the needed code in plugins/mynewplugin.py, matching a predefined interface (inheriting an ABC [1] ?)
  2. Register that in __init__.py, possibly binding that to command line options (there may be dependencies between plugins)

For example, replacing .gt. with > could be as simple as a find-and-replace. This would make the code much clearer and much easier to contribute to.

[1] https://pymotw.com/3/abc/

tab instead of spaces

This tool is totally cool, however, can it alternatively use tab instead of spaces as indentation? then i don't has set the length of indent and it would work with any IDE. thanks.

Multiline string literal lines re-indented

the snippet:

      CHARACTER(len=*), PARAMETER      :: serialized_string = &
         "qtb_rng_gaussian                         1 F T F   0.0000000000000000E+00&
                          12.0                12.0                12.0&
                          12.0                12.0                12.0&
                          12.0                12.0                12.0&
                          12.0                12.0                12.0&
                          12.0                12.0                12.0&
                          12.0                12.0                12.0"

gets falsely re-indented to:

      CHARACTER(len=*), PARAMETER      :: serialized_string = &
                                          "qtb_rng_gaussian                         1 F T F   0.0000000000000000E+00 &
                                          12.0                12.0                12.0 &
                                          12.0                12.0                12.0 &
                                          12.0                12.0                12.0 &
                                          12.0                12.0                12.0 &
                                          12.0                12.0                12.0 &
                                          12.0                12.0                12.0"

which changes the content of the string.
So, if the next line of multiline string does not contain an ampersand, that line should not be touched (except of course for anything following the string).

Type-bound procedure named `write` gets space inserted

TYPE rng_stream_type
contains
  PROCEDURE, PASS(self), PUBLIC :: write
END TYPE rng_stream_type

subroutine foo()
   rng_stream_type :: t
   call t%write()
   !           ^
end subroutine foo

becomes:

TYPE rng_stream_type
contains
  PROCEDURE, PASS(self), PUBLIC :: write
END TYPE rng_stream_type

subroutine foo()
   rng_stream_type :: t
   call t%write ()
   !           ^
end subroutine foo

Not supported Fortran 2003 / 2008 constructs

SELECT TYPE (... => ...)
TYPE IS (...)
CLASS IS (...)
...
END SELECT
TYPE T
...
CONTAINS
...
END TYPE
TYPE, EXTENDS(...) :: ...
...
END TYPE
ENUM, BIND(C)
...
END ENUM

For all these, fprettify fails with an error

fprettify should allow labels

The following code:

program myprogram
10  format(i5)
end program

yields:

fprettify failed because of fixed format or f77 constructs.

The same happens when using statement labels, despite the fact that labels are defined in the Fortran90 standard.

nested loops

Fprettify changes the code

program main
integer :: i,j
do i=1,2
do j=1,3
print*,i,j,i*j
end do
end do
end program main

to

program main
   integer :: i, j
   do i = 1, 2
   do j = 1, 3
      print *, i, j, i*j
   end do
   end do
end program main

I would like each loop to be indented, not just the inner-most loop.

Align equation blocks

Often you will have blocks of equations in fortran and this is what fprettify does now:

            rou = ro/2
            rdru = rhdr(i, 1)/2
            rdtu = rhdt(i, 1)/2
            rdfu = rhdf(i, 1)/2
            rdrru = rhdrr(i, 1)/2
            rdttu = rhdtt(i, 1)/2
            rdffu = rhdff(i, 1)/2
            rdtfu = rhdtf(i, 1)/2
            rdrtu = rhdrt(i, 1)/2
            rdrfu = rhdrf(i, 1)/2

            rod = rou
            rdrd = rdru
            rdtd = rdtu
            rdfd = rdfu
            rdrrd = rdrru
            rdttd = rdttu
            rdffd = rdffu
            rdtfd = rdtfu
            rdrtd = rdrtu
            rdrfd = rdrfu

            rdr = rdru + rdrd
            rdt = rdtu + rdtd
            rdf = rdfu + rdfd
            drdr = rdrru + rdrrd
            rdtt = rdttu + rdttd
            rdff = rdffu + rdffd
            rdtf = rdtfu + rdtfd
            rdrt = rdrtu + rdrtd
            rdrf = rdrfu + rdrfd

My editor plugin does something like this:

            rou   = ro/2
            rdru  = rhdr(i,  1)/2
            rdtu  = rhdt(i,  1)/2
            rdfu  = rhdf(i,  1)/2
            rdrru = rhdrr(i, 1)/2
            rdttu = rhdtt(i, 1)/2
            rdffu = rhdff(i, 1)/2
            rdtfu = rhdtf(i, 1)/2
            rdrtu = rhdrt(i, 1)/2
            rdrfu = rhdrf(i, 1)/2

            rod   = rou
            rdrd  = rdru
            rdtd  = rdtu
            rdfd  = rdfu
            rdrrd = rdrru
            rdttd = rdttu
            rdffd = rdffu
            rdtfd = rdtfu
            rdrtd = rdrtu
            rdrfd = rdrfu

            rdr  = rdru  + rdrd
            rdt  = rdtu  + rdtd
            rdf  = rdfu  + rdfd
            drdr = rdrru + rdrrd
            rdtt = rdttu + rdttd
            rdff = rdffu + rdffd
            rdtf = rdtfu + rdtfd
            rdrt = rdrtu + rdrtd
            rdrf = rdrfu + rdrfd

I think this makes it easier to read. Maybe this could be an optional feature.

Whitespace before/after double colons

Is it possible to adjust whitespace before/after double colons? Example:

$ cat test.f90
subroutine a()
   integer::b
   integer  ::  c
end subroutine

I would like to have

$ fprettify -s test.f90
subroutine a()
   integer :: b
   integer :: c
end subroutine

which can't be done with the current version (v0.3.4).

Numbered do loop end not properly indented

Old Fortran construct for numbered do loops are not properly "de-dented"
This construct is still supported in more modern Fortran as far as I know.

Example 1, the end statement match the do loop

$ cat test.F90
subroutine a()
do 3 i=1,4
print *,i
3 continue
end

$ fprettify.py -s --strict-indent -- test.F90
subroutine a()
   do 3 i = 1, 4
      print *, i
3     continue
   end

Example 2, it never match the end of the ````do``` loop

$ cat test.F90
subroutine a()
do 3 i=1,4
print *,i
3 continue
end subroutine a

$ fprettify.py -s --strict-indent -- test.F90
subroutine a()
   do 3 i = 1, 4
      print *, i
3     continue
      end subroutine a

Expected result

subroutine a()
   do 3 i = 1, 4
      print *, i
3     continue
 end subroutine a

If the numbered do loop construct is not to be supported, it would be nice to throw an error/warning message.

Fortran continuation line

Fortran 77 continuation lines that has the following format gives me errors:
<5 spaces>code
<5 spaces>&code

e.g.
subroutine Test (arg1, arg2, arg3, arg4, arg5,
& arg6, arg7, arg8 )

Traceback (most recent call last):
File "/usr/local/lib/python2.7/dist-packages/fprettify/init.py", line 1417, in run
strip_comments=args.strip_comments)
File "/usr/local/lib/python2.7/dist-packages/fprettify/init.py", line 908, in reformat_inplace
orig_filename=filename, **kwargs)
File "/usr/local/lib/python2.7/dist-packages/fprettify/init.py", line 996, in reformat_ffile
lines, orig_filename, stream.line_nr)
File "/usr/local/lib/python2.7/dist-packages/fprettify/init.py", line 1228, in remove_pre_ampersands
"Bad continuation line format", filename, line_nr)
FprettifyParseException: Bad continuation line format

Any idea if this can be fixed ?

Support multiline strings

RIght now, multiline strings such as

"foo&
&bar"

trigger an error "multline strings not supported".

Problem with --enable-replacements --c-relations

I have some code that is badly reformatted when I specify --enable-replacements --c-relations

The code snippet:

$ cat test.F90
     if (G_yglob_8(1)  .lt. -near_pole_8 .or. yglob(1)  .lt. -near_pole_8 .or. &
          G_yglob_8(gnj).gt.  near_pole_8 .or. yglob(gnj).gt.  near_pole_8 ) then

Here are the results with and w/o the problematic options.

$ fprettify.py -s test.F90
     if (G_yglob_8(1) .lt. -near_pole_8 .or. yglob(1) .lt. -near_pole_8 .or. &
         G_yglob_8(gnj) .gt. near_pole_8 .or. yglob(gnj) .gt. near_pole_8) then

With the option set I get a False "line too long" warning and a "mangled" source code

$ fprettify.py -s --enable-replacements --c-relations test.F90
WARNING: File test.F90, line 3
    auto indentation failed due to chars limit, line should be split (limit: 132)

     if (G_yglob_8(1) < -near_pole_8 .or. yglob(1) < -near_pole_8 .or. G_yglob_8(gn &
                                                                                j) > near_pole_8 .or. yglob(gnj) > near_pole_8) then

With -l 512 the warning is gone but the source code is still "mangled"

$ fprettify.py -s -l 512 --enable-replacements --c-relations test.F90

     if (G_yglob_8(1) < -near_pole_8 .or. yglob(1) < -near_pole_8 .or. G_yglob_8(gn &
                                                                                 j) > near_pole_8 .or. yglob(gnj) > near_pole_8) then

Support for different file encodings

Nearly half of the files in my legacy fortran project have ANSI encoding, not UTF-8, and special characters in the comments are causing fprettify to fail. It would be helpful if fprettify could intelligently handle this, either by converting the file to utf-8 or by automatically figuring out which encoding to open() with.

Return nonzero value if errors occur

Return a non-zero value if errors occur during formatting. This would be useful when used in combination with make. Currently make cannot detected if fprettify fails because, e.g. a file not found error.

[Feature request] Impose whitespace formatting only on selected "classes"

Right now whitespace formatting can be turned on/off for everything and some options allow to add/remove whitespaces around "operators".
There is no option to leave whitespace "as-is" for selected "operators".

For example:

$cat test.F90
f(asd,   asd  ,asf+1,asf+ 1)

Would give:

$fprettify.py -s  test.F90
f(asd, asd, asf + 1, asf + 1)

$fprettify.py -s --whitespace-plusminus False  test.F90
f(asd, asd, asf+1, asf+1)

$fprettify.py -s  --disable-whitespace  test.F90
f(asd,   asd  ,asf+1,asf+ 1)

It would be nice to selectively choose what "operators" ['plusminus', 'intrinsics', 'logical', 'assignments', 'multdiv', 'relational', 'print', 'comma', 'type'] have their whitespaces modified and by how much (maybe allow different spacing before and after, useful for commas for example).

Comment is indented

I have a file that begins

      program swe
c

This is indented to

      program swe
         c

Which no longer compiles because the c is not in the leftmost column.

Improve testing

There are two different testing mechanisms in place:

  1. unit tests (hard-coded Fortran snippets)
  2. testing by cloning Fortran projects

For 1) non-default command line options can be tested, but because fprettify is called as an external scripts, there are problems with python versions and test coverage is not reported
For 2) we can test only with default options but test coverage works

Both mechanisms should be unified and both should call fprettify.run(). Then test coverage and non-default options should work.

Furthermore the testing procedure should be documented better.

[Feature request] Change case for keywords, labels, parameters

It would be nice to be able to make characters case uniform for at least keywords, labels and parameters. This would be configurable with options.

My preference for a default would be:

  • lowercase for keywords
  • uppercase for labels and parameters

I suppose it could as well be done for derived types, modules, subroutines and functions names.

I'll try to look into this.

Extend tests

Additionally to the expected checksums, we should test that:

  • fprettify is changing whitespace only
  • fprettify is idempotent (running twice does not change anything)
  • all command line arguments should be covered by unit tests

Note on idempotent: for testing, fprettify-formatted versions of external Fortran repositories are checked out. This naturally checks for idempotent and we don't need to run fprettify twice.

Issue with stop statement

Hi,
I came across the following bug in fprettify. While parsing a line containing a stop statement such as:

if (condition) stop 'A message'

fprettify removed the space between stop and 'A message'. I.e.

if (condition) stop'A message'

This then results in a compilation error when compiling with gfortran.
Hope this helps!
Ben

Several small changes

I made a few small changes which you may or may not find useful:

  • to allow for a config file instead of command options
  • to allow for longer line length
  • a fix to formatting real*8
  • an option to replace relational operations between Fortran and C-style (#30, #16)

I made those changes to separate branches, so could open a PR each or one for all. Do you have a preference? The first three are really short, the last one can probably be improved upon on how it's done.
I'm afraid I don't remember whether or not you have some CI magic in place to check the code or if I should run some checks first.

white spaces before comments, how to configure

Dear @pseewald

sorry for the stalking...

I found that the handling spaces before comments is somehow obscure for me, e.g. applying fprettify on a FLAP files I obtain

baseline code

module flap_utils_m
!-----------------------------------------------------------------------------------------------------------------------------------
!< FLAP utils.
!-----------------------------------------------------------------------------------------------------------------------------------
use penf
!-----------------------------------------------------------------------------------------------------------------------------------
...

pretty-formatted code

module flap_utils_m
!-----------------------------------------------------------------------------------------------------------------------------------
!< FLAP utils.
!-----------------------------------------------------------------------------------------------------------------------------------
   use penf
!-----------------------------------------------------------------------------------------------------------------------------------
...

Comparing the two versions the comments have not been touched, but this is not true for procedures contained into the module, e.g.

baseline code

contains
  elemental function count_substring(string, substring) result(No)
  !---------------------------------------------------------------------------------------------------------------------------------
  !< Count the number of occurences of a substring into a string.
  !---------------------------------------------------------------------------------------------------------------------------------
  character(*), intent(in) :: string    !< String.
  character(*), intent(in) :: substring !< Substring.
  integer(I4P)             :: No        !< Number of occurrences.
  integer(I4P)             :: c1        !< Counters.
  integer(I4P)             :: c2        !< Counters.
  !---------------------------------------------------------------------------------------------------------------------------------
...

pretty-formatted code

contains
   elemental function count_substring(string, substring) result(No)
      !---------------------------------------------------------------------------------------------------------------------------------
      !< Count the number of occurences of a substring into a string.
      !---------------------------------------------------------------------------------------------------------------------------------
      character(*), intent(in) :: string !< String.
      character(*), intent(in) :: substring !< Substring.
      integer(I4P)             :: No !< Number of occurrences.
      integer(I4P)             :: c1 !< Counters.
      integer(I4P)             :: c2 !< Counters.
      !---------------------------------------------------------------------------------------------------------------------------------
...

All the comments have been moved.

To me, it seems that only the comments starting at the very first character remain untouched, while the others are moved. This can be fine, but I would like to configure this behavior. In particular, I like that the inline comments after variables remain at the same relative distance they have, thus if you move variables the comment moves accordingly.

Cheers

Spaces around => in associate

After formatting the white spaces around the => operator in the associate construct were removed. I have all white-space options turned on, and --whitespaces set to 4.

Expected behavior:
Format to: associate(a => b)

Actual behavior
associate(a=>b)

Access operators % in the associate construct are formatted correctly.

remove_pre_ampersands regular expression fails to match code

The regular expression in remove_pre_ampersands, r'(\s*)&[\s]*(?:!.*)?$' does not match this code

             zeta(i,j,k)=+(v(i,j,k,n3)-(v(i-1,j,k,n3)*mask(i-1,j,k)
     &                   -slip*v(i,j,k,n3)*(1-mask(i-1,j,k))))/dx

The final non-capturing group of the regex looks for a sequence starting with an !. If no such sequence is found, then the line must terminate at the & or at whitespace following the &.

Missing features

  • sorting and alignment of use statements
  • sorting and alignment of variable declarations (and dummy arguments)
  • removal of unused variables / use statements
  • forall statement
  • where statement

Update: Sorting / cleanup of variables / dummy arguments / use statements can not easily be implement in a way that is safe with preprocessor (cpp, fypp) macros.

Better formatting of in-source arrays

The following is after formatting:

A = reshape((/ &
               1, 1, 1, 1, 1, &
               1, 1, 1, 1, 1, &
               1, 2, 4, 8, 16, &
               32, 64, 128, 256, 512, &
               1, 3, 9, 27, 81, &
               243, 729, 2187, 6561, 19683, &
               1, 4, 16, 64, 256, &
               1024, 4096, 16384, 65536, 262144, &
               1, 5, 25, 125, 625, &
               3125, 15625, 78125, 390625, 1953125, &
               1, 6, 36, 216, 1296, &
               7776, 46656, 279936, 1679616, 10077696, &
               1, 7, 49, 343, 2401, &
               16807, 117649, 823543, 5764801, 40353607, &
               1, 8, 64, 512, 4096, &
               32768, 262144, 2097152, 16777216, 134217728, &
               1, 9, 81, 729, 6561, &
               59049, 531441, 4782969, 43046721, 387420489, &
               1, 10, 100, 1000, 10000, &
               100000, 1000000, 10000000, 100000000, 1000000000 &
               /), shape(A))

It would be better if the numbers were vertically aligned rather than giving them the same spacing.

Problem with code-like string in comment

A comment in file

*  n(silica)=1.45  <--->    EPS(1)=2.1025D0
*  n(ZnS)=2.       <--->    EPS(1)=4.D0

lead to an error

$ fprettify chew_rad.f
ERROR: File chew_rad.f, line 193
    Fatal error occured
Traceback (most recent call last):
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 1417, in run
    strip_comments=args.strip_comments)
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 908, in reformat_inplace
    orig_filename=filename, **kwargs)
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 1015, in reformat_ffile
    stream.line_nr, manual_lines_indent)
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 335, in process_lines_of_fline
    f_line, lines, rel_ind_con, line_nr)
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 433, in process_lines_of_fline
    line, is_decl, rel_ind, self._line_nr + pos)
  File "/home/tig/.local/lib/python2.7/site-packages/fprettify/__init__.py", line 516, in __align_line_continuations
    "found more than one assignment in the same Fortran line", filename, line_nr)
FprettifyInternalException: found more than one assignment in the same Fortran line

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.