Skip to content

Commit

Permalink
Extract stable and useful features from cp2k fprettify
Browse files Browse the repository at this point in the history
Examples and improved tester
add README.md
  • Loading branch information
pseewald committed Aug 26, 2016
1 parent b20ad4e commit c945d04
Show file tree
Hide file tree
Showing 11 changed files with 1,669 additions and 2,646 deletions.
54 changes: 54 additions & 0 deletions README.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,54 @@
# fprettify

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


## 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.
* All operators are surrounded by exactly one whitespace character, except for arithmetic operators.
* Removal of extraneous whitespace and consecutive blank lines.
* Works only for modern Fortran (Fortran 90 upwards).


## Requirements

Python 2.7 or Python 3.x


## Examples

Have a look at examples/fortran_after.f90 to see reformatted Fortran code.


## Installation

```
./setup install
```

For local installation, use `--user` option.


## Usage

```
fprettify file1, file2, ...
```
The default indent is 3. If you prefer something else, use `--indent=<n>` argument.

For editor integration, use
```
fprettify --no-report-errors
```

For more information, read
```
fprettify --help
```


## Trivia

fprettify is part of the coding conventions of [CP2K](https://www.cp2k.org/) and thus tested with a large code base. Compared with CP2K's internal version (cp2k branch), this version is reduced in functionality. It contains only stable and general features that don't rely on specific coding conventions.
257 changes: 257 additions & 0 deletions examples/fortran_after.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,257 @@
module prettify_selftest
implicit none
private
public :: dp, test_routine, &
test_function, test_type, str_function
integer, parameter :: dp = selected_real_kind(15, 307)
type test_type
real(kind=dp) :: r = 1.0d-3
integer :: i
end type test_type

contains

subroutine test_routine( &
r, i, j, k, l)
integer, intent(in) :: r, i, j, k
integer, intent(out) :: l

l = test_function(r, i, j, k)
end &
subroutine

pure function test_function(r, i, j, &
k) &
result(l)
integer, intent(in) :: r, i, j, k
integer :: l

l = r + i + j + k
end function
function &
str_function(a) result(l)
character(len=*) :: a
integer :: l

if (len(a) < 5) then
l = 0
else
l = 1
endif
end function

end module

program example_prog
use example, only: dp, test_routine, test_function, test_type,str_function

implicit none
integer :: r, i, j, k, l, my_integer, m
integer, dimension(5) :: arr
integer, dimension(20) :: big_arr
integer :: endif
type(test_type) :: t
real(kind=dp) :: r1, r2, r3, r4, r5, r6
integer, pointer :: point

point => null()

! 1) white space formatting !
!***************************!
! example 1.1
r = 1; i = -2; j = 3; k = 4; l = 5
r2 = 0.0_dp; r3 = 1.0_dp; r4 = 2.0_dp; r5 = 3.0_dp; r6 = 4.0_dp
r1 = -(r2**i*(r3 + r5*(-r4) - r6)) - 2.e+2
if (r .eq. 2 .and. r <= 5) i = 3
write (*, *) (merge(3, 1, i <= 2))
write (*, *) test_function(r, i, j, k)
t%r = 4.0_dp
t%i = str_function("t % i = ")

! example 1.2
my_integer = 2
i = 3
j = 5

big_arr = [1, 2, 3, 4, 5, &
6, 7, 8, 9, 10, &
11, 12, 13, 14, 15, &
16, 17, 18, 19, 20]

! example 1.3: disabling auto-formatter:
my_integer = 2 !&
i = 3 !&
j = 5 !&

!&<
my_integer = 2
i = 3
j = 5
!&>

big_arr = [ 1, 2, 3, 4, 5, & !&
6, 7, 8, 9, 10, & !&
11, 12, 13, 14, 15, & !&
16, 17, 18, 19, 20] !&

! example 1.4:

big_arr = [1, 2, 3, 4, 5,&
& 6, 7, 8, 9, 10, &
& 11, 12, 13, 14, 15,&
&16, 17, 18, 19, 20]

! 2) auto indentation for loops !
!*******************************!

! example 2.1
l = 0
do r = 1, 10
select case (r)
case (1)
do_label: do i = 1, 100
if (i <= 2) then
m = 0
do while (m < 4)
m = m + 1
do k = 1, 3
if (k == 1) l = l + 1
end do
enddo
endif
enddo do_label
case (2)
l = i + j + k
end select
enddo

! example 2.2
do m = 1, 2
do r = 1, 3
write (*, *) r
do k = 1, 4
do l = 1, 3
do i = 4, 5
do my_integer = 1, 1
do j = 1, 2
write (*, *) test_function(m, r, k, l) + i
enddo
enddo
enddo
enddo
enddo
enddo
enddo

! 3) auto alignment for linebreaks !
!************************************!

! example 3.1
l = test_function(1, 2, test_function(1, 2, 3, 4), 4) + 3*(2 + 1)

l = test_function(1, 2, test_function(1, 2, 3, 4), 4) + &
3*(2 + 1)

l = test_function(1, 2, &
test_function(1, 2, 3, 4), 4) + &
3*(2 + 1)

l = test_function(1, 2, &
test_function(1, 2, 3, &
4), 4) + &
3*(2 + 1)

! example 3.2
arr = [1, (/3, 4, 5/), 6] + [1, 2, 3, 4, 5]

arr = [1, (/3, 4, 5/), &
6] + [1, 2, 3, 4, 5]

arr = [1, (/3, 4, 5/), &
6] + &
[1, 2, 3, 4, 5]

arr = [1, (/3, 4, &
5/), &
6] + &
[1, 2, 3, 4, 5]

! example 3.3
l = test_function(1, 2, &
3, 4)

l = test_function( &
1, 2, 3, 4)

arr = [1, 2, &
3, 4, 5]
arr = [ &
1, 2, 3, 4, 5]

! 4) more complex formatting and tricky test cases !
!**************************************************!

! example 4.1
l = 0
do r = 1, 10
select case (r)
case (1)
do i = 1, 100; if (i <= 2) then ! comment
do j = 1, 5
do k = 1, 3
l = l + 1
! unindented comment
! indented comment
end do; enddo
elseif (.not. j == 4) then
my_integer = 4
else
write (*, *) " hello"
endif
enddo
case (2)
l = i + j + k
end select
enddo

! example 4.2
if ( &
l == &
111) &
then
do k = 1, 2
if (k == 1) &
l = test_function(1, &
test_function(r=4, i=5, &
j=6, k=test_function(1, 2*(3*(1 + 1)), str_function(")a!(b['(;=dfe"), &
9) + &
test_function(1, 2, 3, 4)), 9, 10) &
! test_function(1,2,3,4)),9,10) &
! +13*str_function('') + str_function('"')
+ 13*str_function('') + str_function('"')
end & ! comment
! comment
do
endif

! example 4.3
arr = [1, (/3, 4, &
5/), &
6] + &
[1, 2, 3, 4, 5]; arr = [1, 2, &
3, 4, 5]

! example 4.4
endif = 3
if (endif == 2) then
endif = 5
else if (endif == 3) then
write (*, *) endif
endif

! example 4.5
do i = 1, 2; if (.true.) then
write (*, *) "hello"
endif; enddo

end program
Loading

0 comments on commit c945d04

Please sign in to comment.