Skip to content

Commit

Permalink
Got rid of all warning with Intel/Nvidia and Gnu
Browse files Browse the repository at this point in the history
On branch master

new file:   Const_Mod.f90
modified:   Foul_Mod.f90
modified:   Foul_Mod/Formatted_Write.f90
modified:   Foul_Mod/Integer_To_String.f90
modified:   Foul_Mod/Lower_Case.f90
modified:   Foul_Mod/Split_String.f90
modified:   Grid_Mod/Destroy_Grid.f90
modified:   Grid_Mod/Load_Grid.f90
modified:   In_Out_Mod.f90
modified:   In_Out_Mod/Constants.f90
modified:   In_Out_Mod/Legend.f90
modified:   In_Out_Mod/Plot_Bracket_Left.f90
modified:   In_Out_Mod/Plot_Bracket_Right.f90
modified:   In_Out_Mod/Plot_Circle.f90
deleted:    In_Out_Mod/Plot_Ring.f90
modified:   In_Out_Mod/Plot_Snippet.f90
modified:   In_Out_Mod/Plot_Sparse.f90
modified:   In_Out_Mod/Plot_Sparse_System.f90
modified:   In_Out_Mod/Plot_Square.f90
modified:   In_Out_Mod/Plot_Text.f90
modified:   Solvers_Mod/Check_Solution_Dense.f90
modified:   Solvers_Mod/Check_Solution_Sparse.f90
modified:   Solvers_Mod/Dense/Cholesky.f90
modified:   Solvers_Mod/Dense/Gauss.f90
modified:   Solvers_Mod/Dense/Gauss_Elimination.f90
modified:   Solvers_Mod/Dense/Ldlt.f90
modified:   Solvers_Mod/Dense/Lu.f90
modified:   Solvers_Mod/Dense/Lu_Factorization_Doolittle.f90
modified:   Solvers_Mod/Dense/Lu_Factorization_Gauss.f90
modified:   Solvers_Mod/Incomplete/Cholesky.f90
modified:   Solvers_Mod/Incomplete/Ldlt.f90
modified:   Solvers_Mod/Incomplete/Lu.f90
modified:   Solvers_Mod/Incomplete/Tflows_Ldlt.f90
modified:   Solvers_Mod/Sparse/Cg_Cholesky_Prec.f90
modified:   Solvers_Mod/Sparse/Cg_Diag_Prec.f90
modified:   Solvers_Mod/Sparse/Cg_Ldlt_Prec.f90
modified:   Solvers_Mod/Sparse/Cg_Lu_Prec.f90
modified:   Solvers_Mod/Sparse/Cg_No_Prec.f90
modified:   Solvers_Mod/Sparse/Cg_Tflows_Prec.f90
modified:   Sort_Mod.f90
new file:   Swap_Mod.f90
renamed:    Swap_Int.f90 -> Swap_Mod/Swap_Int.f90
new file:   Swap_Mod/Swap_Real.f90
modified:   grid.ini
modified:   makefile
modified:   makefile_explicit_dependencies
  • Loading branch information
Niceno committed Feb 23, 2024
1 parent c43565b commit 664691a
Show file tree
Hide file tree
Showing 46 changed files with 266 additions and 182 deletions.
57 changes: 57 additions & 0 deletions Const_Mod.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,57 @@
!==============================================================================!
module Const_Mod
!------------------------------------------------------------------------------!
implicit none
!==============================================================================!

! Standard string length
integer, parameter :: VL = 4
integer, parameter :: SL = 80 ! standard string length (like page width)
integer, parameter :: DL = 160 ! double string length (twice the page width)

! Double and single precision constants definitions
integer, parameter :: DP = 8 ! double precisions for real and long integer
integer, parameter :: SP = 4 ! single precisions for real and short integer

integer, parameter :: IP = sizeof(1)
integer, parameter :: LP = IP
integer, parameter :: RP = sizeof(1.0)

!----------------------------------------!
! A few handy mathematical constants !
!----------------------------------------!

! Big and small numbers in metric system to avoid ghost numbers
real, parameter :: YOTTA = 1.e+24 ! avoid ghost number 1.0e+24
real, parameter :: ZETTA = 1.e+21 ! avoid ghost number 1.0e+21
real, parameter :: EXA = 1.e+18 ! avoid ghost number 1.0e+18
real, parameter :: PETA = 1.e+15 ! avoid ghost number 1.0e+15
real, parameter :: TERA = 1.e+12 ! avoid ghost number 1.0e+12
real, parameter :: GIGA = 1.e+9 ! avoid ghost number 1.0e+9
real, parameter :: MEGA = 1.e+6 ! avoid ghost number 1.0e+6
real, parameter :: KILO = 1.e+3 ! avoid ghost number 1.0e+3
real, parameter :: MILI = 1.e-3 ! avoid ghost number 1.0e-3
real, parameter :: MICRO = 1.e-6 ! avoid ghost number 1.0e-6
real, parameter :: NANO = 1.e-9 ! avoid ghost number 1.0e-9
real, parameter :: PICO = 1.e-12 ! avoid ghost number 1.0e-12
real, parameter :: FEMTO = 1.e-15 ! avoid ghost number 1.0e-15
real, parameter :: ATTO = 1.e-18 ! avoid ghost number 1.0e-18
real, parameter :: ZEPTO = 1.e-21 ! avoid ghost number 1.0e-21
real, parameter :: YOCTO = 1.e-24 ! avoid ghost number 1.0e-24

real, parameter :: HUGE = PETA ! a very big (huge) number
real, parameter :: TINY = FEMTO ! a very small (tiny) number
integer, parameter :: HUGE_INT = 1073741824 ! big integer (this is 2^30)

! Euler's prime number (also the largest integer in 32 bit precision)
integer, parameter :: EULER = 2147483647 ! Euler's prime number 2^31 - 1

! Archimedes’ constant
real, parameter :: PI = 3.14159265359 ! Archimedes constant

! These are often used in turbulence models
real, parameter :: ONE_THIRD = 1.0 / 3.0 ! avoids frequent 1.0/3.0
real, parameter :: TWO_THIRDS = 1.0 - ONE_THIRD ! avoids frequent 2.0/3.0
real, parameter :: ONE_SIXTH = ONE_THIRD * 0.5 ! avoids frequent 1.0/6.0

end module
11 changes: 6 additions & 5 deletions Foul_Mod.f90
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
#include "Assert.h90"
#include "Unused.h90"

!==============================================================================!
! FOUL - The Fortran Output Library
Expand Down Expand Up @@ -69,11 +70,11 @@ module Foul_Mod

contains

include 'Foul_Mod/Formatted_Write.f90'
include 'Foul_Mod/Get_Escape_Sequence.f90'
include 'Foul_Mod/Integer_To_String.f90'
include 'Foul_Mod/Lower_Case.f90'
include 'Foul_Mod/Split_String.f90'
# include "Foul_Mod/Formatted_Write.f90"
# include "Foul_Mod/Get_Escape_Sequence.f90"
# include "Foul_Mod/Integer_To_String.f90"
# include "Foul_Mod/Lower_Case.f90"
# include "Foul_Mod/Split_String.f90"

end module Foul_Mod

17 changes: 11 additions & 6 deletions Foul_Mod/Formatted_Write.f90
Original file line number Diff line number Diff line change
Expand Up @@ -37,14 +37,19 @@ subroutine Formatted_Write(Foul, &
text_22, style_22, text_23, style_23, text_24, style_24, &
forward
!-----------------------------------[Locals]-----------------------------------!
integer :: output_string_count
integer :: output_lengths(512)
integer :: i
character(256) :: format_string
character (16) :: escape_sequence
character(256) :: output_strings(512)
integer :: output_string_count
integer, allocatable :: output_lengths(:)
integer :: i
character(256) :: format_string
character (16) :: escape_sequence
character(256), allocatable :: output_strings(:)
!------------------------[Avoid unused parent warning]-------------------------!
Unused(Foul)
!==============================================================================!

allocate(output_lengths(512))
allocate(output_strings(512))

output_string_count = 0
format_string = ''

Expand Down
18 changes: 10 additions & 8 deletions Foul_Mod/Integer_To_String.f90
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,14 @@ function Integer_To_String(Foul, integer_value, string_length)
!
! Output:
! Return value: String resulting from conversion
!------------------------------------------------------------------------------!
! 1 + floor(log10(real(abs(integer_value)))) =
! number of digits needed to represent integer_value
!
! int(sign(1, -integer_value) + 1) / 2) =
! 0, if integer_value is positive
! 1, if integer_value is negative
! (used to make room for sign)
!------------------------------------------------------------------------------!
implicit none
!---------------------------------[Arguments]----------------------------------!
Expand All @@ -21,14 +29,8 @@ function Integer_To_String(Foul, integer_value, string_length)
+ int((sign(1, -integer_value) + 1) / 2), &
string_length, 1)) :: Integer_To_String
character(16) :: string_buffer
!------------------------------------------------------------------------------!
! 1 + floor(log10(real(abs(integer_value)))) =
! number of digits needed to represent integer_value
!
! int(sign(1, -integer_value) + 1) / 2) =
! 0, if integer_value is positive
! 1, if integer_value is negative
! (used to make room for sign)
!------------------------[Avoid unused parent warning]-------------------------!
Unused(Foul)
!==============================================================================!

write(string_buffer, '(I16)') integer_value
Expand Down
2 changes: 2 additions & 0 deletions Foul_Mod/Lower_Case.f90
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,8 @@ subroutine Lower_Case(Foul, string)
character(*), intent(inout) :: string
!-----------------------------------[Locals]-----------------------------------!
integer :: i, character_code
!------------------------[Avoid unused parent warning]-------------------------!
Unused(Foul)
!==============================================================================!

do i = 1, len_trim(string)
Expand Down
18 changes: 10 additions & 8 deletions Foul_Mod/Split_String.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,23 +20,25 @@ subroutine Split_String(Foul, string, delimiter, substrings, substring_count)
character(*), intent(out) :: substrings(*)
integer, intent(out) :: substring_count
!-----------------------------------[Locals]-----------------------------------!
integer :: start_position, end_position
integer :: start_pos, end_pos
!------------------------[Avoid unused parent warning]-------------------------!
Unused(Foul)
!==============================================================================!

start_position = 1
start_pos = 1
substring_count = 0

do
end_position = index(string(start_position:), delimiter)
end_pos = index(string(start_pos:), delimiter)

substring_count = substring_count + 1

if (end_position == 0) then
substrings(substring_count) = string(start_position:)
EXIT
if(end_pos == 0) then
substrings(substring_count) = string(start_pos:)
exit
else
substrings(substring_count) = string(start_position : start_position + end_position - 2)
start_position = start_position + end_position
substrings(substring_count) = string(start_pos : start_pos + end_pos - 2)
start_pos = start_pos + end_pos
end if
end do

Expand Down
3 changes: 0 additions & 3 deletions Grid_Mod/Destroy_Grid.f90
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,6 @@ subroutine Destroy_Grid(Grid)
implicit none
!---------------------------------[Arguments]----------------------------------!
class(Grid_Type) :: Grid
!-----------------------------------[Locals]-----------------------------------!
integer :: s, c, c1, c2, e, n, t, i, j, k
real, allocatable :: visited(:)
!==============================================================================!

Grid % n_bnd_cells = 0
Expand Down
1 change: 1 addition & 0 deletions Grid_Mod/Load_Grid.f90
Original file line number Diff line number Diff line change
Expand Up @@ -18,6 +18,7 @@ subroutine Load_Grid(Grid, grid_name)
!-----------------------------------------!
! First check if the grid file exists !
!-----------------------------------------!
file_exists = .false.
inquire(file = grid_name, exist = file_exists)

!------------------------!
Expand Down
3 changes: 1 addition & 2 deletions In_Out_Mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@ module In_Out_Mod
! A suite of routines for input and output !
!------------------------------------------------------------------------------!
!----------------------------------[Modules]-----------------------------------!
use Const_Mod
use Foul_Mod
use Dense_Mod
use Sparse_Mod
Expand All @@ -33,7 +34,6 @@ module In_Out_Mod
procedure :: Plot_Dense
procedure :: Plot_Dense_System
procedure :: Plot_Header
procedure :: Plot_Ring
procedure :: Plot_Snippet
procedure :: Plot_Sparse
procedure :: Plot_Sparse_System
Expand Down Expand Up @@ -63,7 +63,6 @@ module In_Out_Mod
# include "In_Out_Mod/Plot_Dense.f90"
# include "In_Out_Mod/Plot_Dense_System.f90"
# include "In_Out_Mod/Plot_Header.f90"
# include "In_Out_Mod/Plot_Ring.f90"
# include "In_Out_Mod/Plot_Snippet.f90"
# include "In_Out_Mod/Plot_Sparse.f90"
# include "In_Out_Mod/Plot_Sparse_System.f90"
Expand Down
4 changes: 3 additions & 1 deletion In_Out_Mod/Constants.f90
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
!-------------------------!
! Xfig units for 1 cm !
!-------------------------!
integer, parameter :: CM = 450
integer, parameter :: CM = 450
integer, parameter :: CM_HALF = 225
integer, parameter :: CM_QUARTER = 112

!-----------------!
! Xfig colors !
Expand Down
2 changes: 2 additions & 0 deletions In_Out_Mod/Legend.f90
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@ subroutine Print_Legend(IO, row, max_val)
class(In_Out_Type) :: IO
integer, intent(in) :: row
real, intent(in) :: max_val
!------------------------[Avoid unused parent warning]-------------------------!
Unused(IO)
!==============================================================================!

if(row .eq. 1) then
Expand Down
2 changes: 1 addition & 1 deletion In_Out_Mod/Plot_Bracket_Left.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ subroutine Plot_Bracket_Left(IO, fu, rows, col, depth)
plot_x = (col) * CM
plot_y1 = (rows(1)) * CM
plot_yn = (rows(2)) * CM + CM
d = CM / 4 ! delta
d = CM_QUARTER

write(fu,'(a)', advance='no') ' 2' ! 1 polyline
write(fu,'(a)', advance='no') ' 1' ! 2 it is a polyline
Expand Down
2 changes: 1 addition & 1 deletion In_Out_Mod/Plot_Bracket_Right.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,7 @@ subroutine Plot_Bracket_Right(IO, fu, rows, col, depth)
plot_x = (col) * CM + CM
plot_y1 = (rows(1)) * CM
plot_yn = (rows(2)) * CM + CM
d = CM / 4 ! delta
d = CM_QUARTER

write(fu,'(a)', advance='no') ' 2' ! 1 polyline
write(fu,'(a)', advance='no') ' 1' ! 2 it is a polyline
Expand Down
30 changes: 16 additions & 14 deletions In_Out_Mod/Plot_Circle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -21,29 +21,31 @@ subroutine Plot_Circle(IO, fu, row, col, val, minv, maxv, depth)

! Scaling by circle size
rad = 135
if(IO % scale_by_size) then
rad = 15 + 150 * ( sqrt(abs(val)) / sqrt(maxa)) ! quadratic scaling
! rad = 50 + 100 * ( abs(val) / maxa) ! linear scaling
! rad = 50 + 100 * ( sqrt(abs(val)) / sqrt(maxa)) ! quadratic scaling
! rad = 10 + 140 * ( abs(val) / maxa) ! linear scaling
! rad = 10 + 140 * ( sqrt(abs(val)) / sqrt(maxa)) ! quadratic scaling
if(IO % scale_by_size .and. abs(val) > TINY) then
rad = int(15 + 150 * ( sqrt(abs(val)) / sqrt(maxa))) ! quadratic scaling
! rad = int(50 + 100 * ( abs(val) / maxa) ) ! linear scaling
! rad = int(50 + 100 * ( sqrt(abs(val)) / sqrt(maxa))) ! quadratic scaling
! rad = int(10 + 140 * ( abs(val) / maxa) ) ! linear scaling
! rad = int(10 + 140 * ( sqrt(abs(val)) / sqrt(maxa))) ! quadratic scaling
end if

! Scaling by color
if(val > 0) then
if(val > TINY) then
color = 58
if(IO % scale_by_color) color = 50 + 8 * (sqrt( val) / sqrt( maxv))
! if(IO % scale_by_color) color = 50 + 8 * ( val / maxv)
else
if(IO % scale_by_color) color = int(50 + 8 * (sqrt( val) / sqrt( maxv)))
! if(IO % scale_by_color) color = int(50 + 8 * ( val / maxv)
else if(val < -TINY) then
color = 78
if(IO % scale_by_color) color = 70 + 8 * (sqrt(-val) / sqrt(-minv))
! if(IO % scale_by_color) color = 70 + 8 * ( val / -minv)
if(IO % scale_by_color) color = int(70 + 8 * (sqrt(-val) / sqrt(-minv)))
! if(IO % scale_by_color) color = int(70 + 8 * ( val / -minv)
else
color = WHITE
end if

! Perform actual plotting of a circle
if(abs(val) > 1.0e-15) then
plot_x = CM/2 + col * CM
plot_y = CM/2 + row * CM
plot_x = CM_HALF + col * CM
plot_y = CM_HALF + row * CM
write(fu,'(a,es12.5)') '# ', val
write(fu,'(a)', advance='no') ' 1' ! 1 ellipse
write(fu,'(a)', advance='no') ' 3' ! 2 define with radii
Expand Down
43 changes: 0 additions & 43 deletions In_Out_Mod/Plot_Ring.f90

This file was deleted.

16 changes: 13 additions & 3 deletions In_Out_Mod/Plot_Snippet.f90
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,22 @@ subroutine Plot_Snippet(IO, inp_file_name, str_start, str_end)
character (80) :: read_line ! line as read from the file
character (80) :: proc_line ! processed line
character(512) :: out_file_name
integer :: n, iostat, pos, pos_io, pos_com, lc
integer :: n, iostat, pos, lc
logical :: processing, last_line, not_comment, out_exists
!------------------------[Avoid unused parent warning]-------------------------!
Unused(IO)
!==============================================================================!

!--------------------------------------------------------------------------!
! Fortran compiler does not provide full path to macro __FILE__ and it !
! therefore very difficult to use this function. One might use system !
! calls to find a particular file, but there may be several files with !
! the same name, residing in different directories. Hence, just return !
!--------------------------------------------------------------------------!
#ifdef __INTEL_COMPILER
return
#endif

! Print some useful message, be transparent, tell what you are doing
call Foul % Formatted_Write(' # Processing the file: ', &
'white', &
Expand Down Expand Up @@ -116,8 +126,8 @@ subroutine Plot_Snippet(IO, inp_file_name, str_start, str_end)

! Write the processed (worked) line out
write(9, '(a)', advance='no') '4 0 0 50 -1 12 22 0.0000 4 450 450 '
write(9, '(i9)', advance='no') CM / 2
write(9, '(i9)', advance='no') lc * CM - CM / 4
write(9, '(i9)', advance='no') CM_HALF
write(9, '(i9)', advance='no') lc * CM - CM_QUARTER
write(9, '(a)', advance='no') trim(proc_line)
write(9, '(a)') '\001'
end if
Expand Down
Loading

0 comments on commit 664691a

Please sign in to comment.