avoid duplicated public/private statements

variables should be private
This commit is contained in:
Martin Diehl 2020-02-29 15:00:47 +01:00
parent 4d227fab2b
commit 18ccc49d6f
5 changed files with 28 additions and 39 deletions

View File

@ -40,7 +40,7 @@ module DAMASK_interface
implicit none implicit none
private private
logical, public :: symmetricSolver logical, protected, public :: symmetricSolver
character(len=*), parameter, public :: INPUTFILEEXTENSION = '.dat' character(len=*), parameter, public :: INPUTFILEEXTENSION = '.dat'
public :: & public :: &

View File

@ -77,20 +77,6 @@ module HDF5_utilities
module procedure HDF5_addAttribute_real_array module procedure HDF5_addAttribute_real_array
end interface HDF5_addAttribute end interface HDF5_addAttribute
!--------------------------------------------------------------------------------------------------
public :: &
HDF5_utilities_init, &
HDF5_openFile, &
HDF5_closeFile, &
HDF5_addAttribute, &
HDF5_closeGroup ,&
HDF5_openGroup, &
HDF5_addGroup, &
HDF5_read, &
HDF5_write, &
HDF5_setLink, &
HDF5_objectExists
contains contains

View File

@ -11,30 +11,31 @@ module prec
implicit none implicit none
public public
! https://software.intel.com/en-us/blogs/2017/03/27/doctor-fortran-in-it-takes-all-kinds ! https://software.intel.com/en-us/blogs/2017/03/27/doctor-fortran-in-it-takes-all-kinds
integer, parameter, public :: pReal = IEEE_selected_real_kind(15,307) !< number with 15 significant digits, up to 1e+-307 (typically 64 bit) integer, parameter :: pReal = IEEE_selected_real_kind(15,307) !< number with 15 significant digits, up to 1e+-307 (typically 64 bit)
#if(INT==8) #if(INT==8)
integer, parameter, public :: pInt = selected_int_kind(18) !< number with at least up to +-1e18 (typically 64 bit) integer, parameter :: pInt = selected_int_kind(18) !< number with at least up to +-1e18 (typically 64 bit)
#else #else
integer, parameter, public :: pInt = selected_int_kind(9) !< number with at least up to +-1e9 (typically 32 bit) integer, parameter :: pInt = selected_int_kind(9) !< number with at least up to +-1e9 (typically 32 bit)
#endif #endif
integer, parameter, public :: pLongInt = selected_int_kind(18) !< number with at least up to +-1e18 (typically 64 bit) integer, parameter :: pLongInt = selected_int_kind(18) !< number with at least up to +-1e18 (typically 64 bit)
integer, parameter, public :: pStringLen = 256 !< default string length integer, parameter :: pStringLen = 256 !< default string length
integer, parameter, public :: pPathLen = 4096 !< maximum length of a path name on linux integer, parameter :: pPathLen = 4096 !< maximum length of a path name on linux
real(pReal), parameter, public :: tol_math_check = 1.0e-8_pReal !< tolerance for internal math self-checks (rotation) real(pReal), parameter :: tol_math_check = 1.0e-8_pReal !< tolerance for internal math self-checks (rotation)
type, public :: group_float !< variable length datatype used for storage of state type :: group_float !< variable length datatype used for storage of state
real(pReal), dimension(:), pointer :: p real(pReal), dimension(:), pointer :: p
end type group_float end type group_float
type, public :: group_int type :: group_int
integer, dimension(:), pointer :: p integer, dimension(:), pointer :: p
end type group_int end type group_int
! http://stackoverflow.com/questions/3948210/can-i-have-a-pointer-to-an-item-in-an-allocatable-array ! http://stackoverflow.com/questions/3948210/can-i-have-a-pointer-to-an-item-in-an-allocatable-array
type, public :: tState type :: tState
integer :: & integer :: &
sizeState = 0, & !< size of state sizeState = 0, & !< size of state
sizeDotState = 0, & !< size of dot state, i.e. state(1:sizeDot) follows time evolution by dotState rates sizeDotState = 0, & !< size of dot state, i.e. state(1:sizeDot) follows time evolution by dotState rates
@ -57,7 +58,7 @@ module prec
RKCK45dotState RKCK45dotState
end type end type
type, extends(tState), public :: tPlasticState type, extends(tState) :: tPlasticState
logical :: & logical :: &
nonlocal = .false. nonlocal = .false.
real(pReal), pointer, dimension(:,:) :: & real(pReal), pointer, dimension(:,:) :: &
@ -65,22 +66,22 @@ module prec
accumulatedSlip !< accumulated plastic slip accumulatedSlip !< accumulated plastic slip
end type end type
type, public :: tSourceState type :: tSourceState
type(tState), dimension(:), allocatable :: p !< tState for each active source mechanism in a phase type(tState), dimension(:), allocatable :: p !< tState for each active source mechanism in a phase
end type end type
type, public :: tHomogMapping type :: tHomogMapping
integer, pointer, dimension(:,:) :: p integer, pointer, dimension(:,:) :: p
end type end type
real(pReal), private, parameter :: PREAL_EPSILON = epsilon(0.0_pReal) !< minimum positive number such that 1.0 + EPSILON /= 1.0. real(pReal), private, parameter :: PREAL_EPSILON = epsilon(0.0_pReal) !< minimum positive number such that 1.0 + EPSILON /= 1.0.
real(pReal), private, parameter :: PREAL_MIN = tiny(0.0_pReal) !< smallest normalized floating point number real(pReal), private, parameter :: PREAL_MIN = tiny(0.0_pReal) !< smallest normalized floating point number
integer, dimension(0), parameter, public :: & integer, dimension(0), parameter :: &
emptyIntArray = [integer::] emptyIntArray = [integer::]
real(pReal), dimension(0), parameter, public :: & real(pReal), dimension(0), parameter :: &
emptyRealArray = [real(pReal)::] emptyRealArray = [real(pReal)::]
character(len=pStringLen), dimension(0), parameter, public :: & character(len=pStringLen), dimension(0), parameter :: &
emptyStringArray = [character(len=pStringLen)::] emptyStringArray = [character(len=pStringLen)::]
private :: & private :: &

View File

@ -10,7 +10,7 @@ module quaternions
use IO use IO
implicit none implicit none
public private
real(pReal), parameter, public :: P = -1.0_pReal !< parameter for orientation conversion. real(pReal), parameter, public :: P = -1.0_pReal !< parameter for orientation conversion.
@ -95,9 +95,13 @@ module quaternions
interface aimag interface aimag
module procedure aimag__ module procedure aimag__
end interface aimag end interface aimag
private :: & public :: &
unitTest quaternions_init, &
assignment(=), &
conjg, aimag, &
log, exp, &
real
contains contains
@ -511,6 +515,7 @@ subroutine unitTest
q_2 = conjg(q_2) - inverse(q_2) q_2 = conjg(q_2) - inverse(q_2)
if(any(dNeq0(q_2%asArray(),1.0e-15_pReal))) call IO_error(0,ext_msg='inverse/conjg') if(any(dNeq0(q_2%asArray(),1.0e-15_pReal))) call IO_error(0,ext_msg='inverse/conjg')
endif endif
if(dNeq(dot_product(qu,qu),dot_product(q,q))) call IO_error(0,ext_msg='dot_product')
#if !(defined(__GFORTRAN__) && __GNUC__ < 9) #if !(defined(__GFORTRAN__) && __GNUC__ < 9)
if (norm2(aimag(q)) > 0.0_pReal) then if (norm2(aimag(q)) > 0.0_pReal) then

View File

@ -7,11 +7,8 @@ module thermal_isothermal
use material use material
implicit none implicit none
private public
public :: &
thermal_isothermal_init
contains contains
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------