|
| 1 | +module prettify_selftest |
| 2 | + implicit none |
| 3 | + private |
| 4 | + public :: dp, test_routine, & |
| 5 | + test_function, test_type, str_function |
| 6 | + integer, parameter :: dp = selected_real_kind(15, 307) |
| 7 | + type test_type |
| 8 | + real(kind=dp) :: r = 1.0d-3 |
| 9 | + integer :: i |
| 10 | + end type test_type |
| 11 | + |
| 12 | +contains |
| 13 | + |
| 14 | + subroutine test_routine( & |
| 15 | + r, i, j, k, l) |
| 16 | + integer, intent(in) :: r, i, j, k |
| 17 | + integer, intent(out) :: l |
| 18 | + |
| 19 | + l = test_function(r, i, j, k) |
| 20 | + end & |
| 21 | + subroutine |
| 22 | + |
| 23 | + pure function test_function(r, i, j, & |
| 24 | + k) & |
| 25 | + result(l) |
| 26 | + integer, intent(in) :: r, i, j, k |
| 27 | + integer :: l |
| 28 | + |
| 29 | + l = r + i + j + k |
| 30 | + end function |
| 31 | + function & |
| 32 | + str_function(a) result(l) |
| 33 | + character(len=*) :: a |
| 34 | + integer :: l |
| 35 | + |
| 36 | + if (len(a) < 5) then |
| 37 | + l = 0 |
| 38 | + else |
| 39 | + l = 1 |
| 40 | + endif |
| 41 | + end function |
| 42 | + |
| 43 | +end module |
| 44 | + |
| 45 | +program example_prog |
| 46 | + use example, only: dp, test_routine, test_function, test_type,str_function |
| 47 | + |
| 48 | + implicit none |
| 49 | + integer :: r, i, j, k, l, my_integer, m |
| 50 | + integer, dimension(5) :: arr |
| 51 | + integer, dimension(20) :: big_arr |
| 52 | + integer :: endif |
| 53 | + type(test_type) :: t |
| 54 | + real(kind=dp) :: r1, r2, r3, r4, r5, r6 |
| 55 | + integer, pointer :: point |
| 56 | + |
| 57 | + point => null() |
| 58 | + |
| 59 | +! 1) white space formatting ! |
| 60 | +!***************************! |
| 61 | +! example 1.1 |
| 62 | + r = 1; i = -2; j = 3; k = 4; l = 5 |
| 63 | + r2 = 0.0_dp; r3 = 1.0_dp; r4 = 2.0_dp; r5 = 3.0_dp; r6 = 4.0_dp |
| 64 | + r1 = -(r2**i*(r3 + r5*(-r4) - r6)) - 2.e+2 |
| 65 | + if (r .eq. 2 .and. r <= 5) i = 3 |
| 66 | + write (*, *) (merge(3, 1, i <= 2)) |
| 67 | + write (*, *) test_function(r, i, j, k) |
| 68 | + t%r = 4.0_dp |
| 69 | + t%i = str_function("t % i = ") |
| 70 | + |
| 71 | +! example 1.2 |
| 72 | + my_integer = 2 |
| 73 | + i = 3 |
| 74 | + j = 5 |
| 75 | + |
| 76 | + big_arr = [1, 2, 3, 4, 5, & |
| 77 | + 6, 7, 8, 9, 10, & |
| 78 | + 11, 12, 13, 14, 15, & |
| 79 | + 16, 17, 18, 19, 20] |
| 80 | + |
| 81 | +! example 1.3: disabling auto-formatter: |
| 82 | + my_integer = 2 !& |
| 83 | + i = 3 !& |
| 84 | + j = 5 !& |
| 85 | + |
| 86 | +!&< |
| 87 | + my_integer = 2 |
| 88 | + i = 3 |
| 89 | + j = 5 |
| 90 | +!&> |
| 91 | + |
| 92 | + big_arr = [ 1, 2, 3, 4, 5, & !& |
| 93 | + 6, 7, 8, 9, 10, & !& |
| 94 | + 11, 12, 13, 14, 15, & !& |
| 95 | + 16, 17, 18, 19, 20] !& |
| 96 | + |
| 97 | +! example 1.4: |
| 98 | + |
| 99 | + big_arr = [1, 2, 3, 4, 5,& |
| 100 | + & 6, 7, 8, 9, 10, & |
| 101 | + & 11, 12, 13, 14, 15,& |
| 102 | + &16, 17, 18, 19, 20] |
| 103 | + |
| 104 | +! 2) auto indentation for loops ! |
| 105 | +!*******************************! |
| 106 | + |
| 107 | +! example 2.1 |
| 108 | + l = 0 |
| 109 | + do r = 1, 10 |
| 110 | + select case (r) |
| 111 | + case (1) |
| 112 | + do_label: do i = 1, 100 |
| 113 | + if (i <= 2) then |
| 114 | + m = 0 |
| 115 | + do while (m < 4) |
| 116 | + m = m + 1 |
| 117 | + do k = 1, 3 |
| 118 | + if (k == 1) l = l + 1 |
| 119 | + end do |
| 120 | + enddo |
| 121 | + endif |
| 122 | + enddo do_label |
| 123 | + case (2) |
| 124 | + l = i + j + k |
| 125 | + end select |
| 126 | + enddo |
| 127 | + |
| 128 | +! example 2.2 |
| 129 | + do m = 1, 2 |
| 130 | + do r = 1, 3 |
| 131 | + write (*, *) r |
| 132 | + do k = 1, 4 |
| 133 | + do l = 1, 3 |
| 134 | + do i = 4, 5 |
| 135 | + do my_integer = 1, 1 |
| 136 | + do j = 1, 2 |
| 137 | + write (*, *) test_function(m, r, k, l) + i |
| 138 | + enddo |
| 139 | + enddo |
| 140 | + enddo |
| 141 | + enddo |
| 142 | + enddo |
| 143 | + enddo |
| 144 | + enddo |
| 145 | + |
| 146 | +! 3) auto alignment for linebreaks ! |
| 147 | +!************************************! |
| 148 | + |
| 149 | +! example 3.1 |
| 150 | + l = test_function(1, 2, test_function(1, 2, 3, 4), 4) + 3*(2 + 1) |
| 151 | + |
| 152 | + l = test_function(1, 2, test_function(1, 2, 3, 4), 4) + & |
| 153 | + 3*(2 + 1) |
| 154 | + |
| 155 | + l = test_function(1, 2, & |
| 156 | + test_function(1, 2, 3, 4), 4) + & |
| 157 | + 3*(2 + 1) |
| 158 | + |
| 159 | + l = test_function(1, 2, & |
| 160 | + test_function(1, 2, 3, & |
| 161 | + 4), 4) + & |
| 162 | + 3*(2 + 1) |
| 163 | + |
| 164 | +! example 3.2 |
| 165 | + arr = [1, (/3, 4, 5/), 6] + [1, 2, 3, 4, 5] |
| 166 | + |
| 167 | + arr = [1, (/3, 4, 5/), & |
| 168 | + 6] + [1, 2, 3, 4, 5] |
| 169 | + |
| 170 | + arr = [1, (/3, 4, 5/), & |
| 171 | + 6] + & |
| 172 | + [1, 2, 3, 4, 5] |
| 173 | + |
| 174 | + arr = [1, (/3, 4, & |
| 175 | + 5/), & |
| 176 | + 6] + & |
| 177 | + [1, 2, 3, 4, 5] |
| 178 | + |
| 179 | +! example 3.3 |
| 180 | + l = test_function(1, 2, & |
| 181 | + 3, 4) |
| 182 | + |
| 183 | + l = test_function( & |
| 184 | + 1, 2, 3, 4) |
| 185 | + |
| 186 | + arr = [1, 2, & |
| 187 | + 3, 4, 5] |
| 188 | + arr = [ & |
| 189 | + 1, 2, 3, 4, 5] |
| 190 | + |
| 191 | +! 4) more complex formatting and tricky test cases ! |
| 192 | +!**************************************************! |
| 193 | + |
| 194 | +! example 4.1 |
| 195 | + l = 0 |
| 196 | + do r = 1, 10 |
| 197 | + select case (r) |
| 198 | + case (1) |
| 199 | + do i = 1, 100; if (i <= 2) then ! comment |
| 200 | + do j = 1, 5 |
| 201 | + do k = 1, 3 |
| 202 | + l = l + 1 |
| 203 | +! unindented comment |
| 204 | + ! indented comment |
| 205 | + end do; enddo |
| 206 | + elseif (.not. j == 4) then |
| 207 | + my_integer = 4 |
| 208 | + else |
| 209 | + write (*, *) " hello" |
| 210 | + endif |
| 211 | + enddo |
| 212 | + case (2) |
| 213 | + l = i + j + k |
| 214 | + end select |
| 215 | + enddo |
| 216 | + |
| 217 | +! example 4.2 |
| 218 | + if ( & |
| 219 | + l == & |
| 220 | + 111) & |
| 221 | + then |
| 222 | + do k = 1, 2 |
| 223 | + if (k == 1) & |
| 224 | + l = test_function(1, & |
| 225 | + test_function(r=4, i=5, & |
| 226 | + j=6, k=test_function(1, 2*(3*(1 + 1)), str_function(")a!(b['(;=dfe"), & |
| 227 | + 9) + & |
| 228 | + test_function(1, 2, 3, 4)), 9, 10) & |
| 229 | + ! test_function(1,2,3,4)),9,10) & |
| 230 | + ! +13*str_function('') + str_function('"') |
| 231 | + + 13*str_function('') + str_function('"') |
| 232 | + end & ! comment |
| 233 | + ! comment |
| 234 | + do |
| 235 | + endif |
| 236 | + |
| 237 | +! example 4.3 |
| 238 | + arr = [1, (/3, 4, & |
| 239 | + 5/), & |
| 240 | + 6] + & |
| 241 | + [1, 2, 3, 4, 5]; arr = [1, 2, & |
| 242 | + 3, 4, 5] |
| 243 | + |
| 244 | +! example 4.4 |
| 245 | + endif = 3 |
| 246 | + if (endif == 2) then |
| 247 | + endif = 5 |
| 248 | + else if (endif == 3) then |
| 249 | + write (*, *) endif |
| 250 | + endif |
| 251 | + |
| 252 | +! example 4.5 |
| 253 | + do i = 1, 2; if (.true.) then |
| 254 | + write (*, *) "hello" |
| 255 | + endif; enddo |
| 256 | + |
| 257 | +end program |
0 commit comments