compiler complained
This commit is contained in:
parent
a64da06c43
commit
a0af685883
|
@ -1266,8 +1266,6 @@ subroutine lattice_init
|
||||||
debug_level, &
|
debug_level, &
|
||||||
debug_lattice, &
|
debug_lattice, &
|
||||||
debug_levelBasic
|
debug_levelBasic
|
||||||
use numerics, only: &
|
|
||||||
worldrank
|
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer(pInt), parameter :: FILEUNIT = 200_pInt
|
integer(pInt), parameter :: FILEUNIT = 200_pInt
|
||||||
|
|
|
@ -729,6 +729,8 @@ end subroutine material_parseHomogenization
|
||||||
!> @brief parses the microstructure part in the material configuration file
|
!> @brief parses the microstructure part in the material configuration file
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
subroutine material_parseMicrostructure(fileUnit,myPart)
|
subroutine material_parseMicrostructure(fileUnit,myPart)
|
||||||
|
use prec, only: &
|
||||||
|
dNeq
|
||||||
use IO
|
use IO
|
||||||
use mesh, only: &
|
use mesh, only: &
|
||||||
mesh_element, &
|
mesh_element, &
|
||||||
|
@ -738,7 +740,6 @@ subroutine material_parseMicrostructure(fileUnit,myPart)
|
||||||
character(len=*), intent(in) :: myPart
|
character(len=*), intent(in) :: myPart
|
||||||
integer(pInt), intent(in) :: fileUnit
|
integer(pInt), intent(in) :: fileUnit
|
||||||
|
|
||||||
|
|
||||||
integer(pInt), allocatable, dimension(:) :: chunkPos
|
integer(pInt), allocatable, dimension(:) :: chunkPos
|
||||||
integer(pInt) :: Nsections, section, constituent, e, i
|
integer(pInt) :: Nsections, section, constituent, e, i
|
||||||
character(len=65536) :: &
|
character(len=65536) :: &
|
||||||
|
@ -818,9 +819,10 @@ subroutine material_parseMicrostructure(fileUnit,myPart)
|
||||||
|
|
||||||
!sanity check
|
!sanity check
|
||||||
do section = 1_pInt, Nsections
|
do section = 1_pInt, Nsections
|
||||||
if (sum(microstructure_fraction(:,section)) /= 1.0_pReal) &
|
if (dNeq(sum(microstructure_fraction(:,section)),1.0_pReal)) &
|
||||||
call IO_error(153_pInt,ext_msg=microstructure_name(section))
|
call IO_error(153_pInt,ext_msg=microstructure_name(section))
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
end subroutine material_parseMicrostructure
|
end subroutine material_parseMicrostructure
|
||||||
|
|
||||||
|
|
||||||
|
|
33
src/mesh.f90
33
src/mesh.f90
|
@ -921,24 +921,22 @@ subroutine mesh_build_ipCoordinates
|
||||||
integer(pInt) :: e,t,g,c,i,n
|
integer(pInt) :: e,t,g,c,i,n
|
||||||
real(pReal), dimension(3) :: myCoords
|
real(pReal), dimension(3) :: myCoords
|
||||||
|
|
||||||
if (.not. allocated(mesh_ipCoordinates)) then
|
if (.not. allocated(mesh_ipCoordinates)) &
|
||||||
allocate(mesh_ipCoordinates(3,mesh_maxNips,mesh_NcpElems))
|
allocate(mesh_ipCoordinates(3,mesh_maxNips,mesh_NcpElems),source=0.0_pReal)
|
||||||
mesh_ipCoordinates = 0.0_pReal
|
|
||||||
endif
|
|
||||||
|
|
||||||
!$OMP PARALLEL DO PRIVATE(t,g,c,myCoords)
|
!$OMP PARALLEL DO PRIVATE(t,g,c,myCoords)
|
||||||
do e = 1_pInt,mesh_NcpElems ! loop over cpElems
|
do e = 1_pInt,mesh_NcpElems ! loop over cpElems
|
||||||
t = mesh_element(2_pInt,e) ! get element type
|
t = mesh_element(2_pInt,e) ! get element type
|
||||||
g = FE_geomtype(t) ! get geometry type
|
g = FE_geomtype(t) ! get geometry type
|
||||||
c = FE_celltype(g) ! get cell type
|
c = FE_celltype(g) ! get cell type
|
||||||
do i = 1_pInt,FE_Nips(g) ! loop over ips=cells in this element
|
do i = 1_pInt,FE_Nips(g) ! loop over ips=cells in this element
|
||||||
myCoords = 0.0_pReal
|
myCoords = 0.0_pReal
|
||||||
do n = 1_pInt,FE_NcellnodesPerCell(c) ! loop over cell nodes in this cell
|
do n = 1_pInt,FE_NcellnodesPerCell(c) ! loop over cell nodes in this cell
|
||||||
myCoords = myCoords + mesh_cellnode(1:3,mesh_cell(n,i,e))
|
myCoords = myCoords + mesh_cellnode(1:3,mesh_cell(n,i,e))
|
||||||
enddo
|
|
||||||
mesh_ipCoordinates(1:3,i,e) = myCoords / FE_NcellnodesPerCell(c)
|
|
||||||
enddo
|
enddo
|
||||||
|
mesh_ipCoordinates(1:3,i,e) = myCoords / real(FE_NcellnodesPerCell(c),pReal)
|
||||||
enddo
|
enddo
|
||||||
|
enddo
|
||||||
!$OMP END PARALLEL DO
|
!$OMP END PARALLEL DO
|
||||||
|
|
||||||
end subroutine mesh_build_ipCoordinates
|
end subroutine mesh_build_ipCoordinates
|
||||||
|
@ -955,7 +953,6 @@ pure function mesh_cellCenterCoordinates(ip,el)
|
||||||
real(pReal), dimension(3) :: mesh_cellCenterCoordinates !< x,y,z coordinates of the cell center of the requested IP cell
|
real(pReal), dimension(3) :: mesh_cellCenterCoordinates !< x,y,z coordinates of the cell center of the requested IP cell
|
||||||
integer(pInt) :: t,g,c,n
|
integer(pInt) :: t,g,c,n
|
||||||
|
|
||||||
|
|
||||||
t = mesh_element(2_pInt,el) ! get element type
|
t = mesh_element(2_pInt,el) ! get element type
|
||||||
g = FE_geomtype(t) ! get geometry type
|
g = FE_geomtype(t) ! get geometry type
|
||||||
c = FE_celltype(g) ! get cell type
|
c = FE_celltype(g) ! get cell type
|
||||||
|
@ -963,7 +960,7 @@ pure function mesh_cellCenterCoordinates(ip,el)
|
||||||
do n = 1_pInt,FE_NcellnodesPerCell(c) ! loop over cell nodes in this cell
|
do n = 1_pInt,FE_NcellnodesPerCell(c) ! loop over cell nodes in this cell
|
||||||
mesh_cellCenterCoordinates = mesh_cellCenterCoordinates + mesh_cellnode(1:3,mesh_cell(n,ip,el))
|
mesh_cellCenterCoordinates = mesh_cellCenterCoordinates + mesh_cellnode(1:3,mesh_cell(n,ip,el))
|
||||||
enddo
|
enddo
|
||||||
mesh_cellCenterCoordinates = mesh_cellCenterCoordinates / FE_NcellnodesPerCell(c)
|
mesh_cellCenterCoordinates = mesh_cellCenterCoordinates / real(FE_NcellnodesPerCell(c),pReal)
|
||||||
|
|
||||||
end function mesh_cellCenterCoordinates
|
end function mesh_cellCenterCoordinates
|
||||||
|
|
||||||
|
@ -1511,8 +1508,8 @@ function mesh_nodesAroundCentres(gDim,Favg,centres) result(nodes)
|
||||||
shift = sign(abs(iRes+diag-2_pInt*me)/(iRes+diag),iRes+diag-2_pInt*me)
|
shift = sign(abs(iRes+diag-2_pInt*me)/(iRes+diag),iRes+diag-2_pInt*me)
|
||||||
lookup = me-diag+shift*iRes
|
lookup = me-diag+shift*iRes
|
||||||
wrappedCentres(1:3,i+1_pInt, j+1_pInt, k+1_pInt) = &
|
wrappedCentres(1:3,i+1_pInt, j+1_pInt, k+1_pInt) = &
|
||||||
centres(1:3,lookup(1)+1_pInt,lookup(2)+1_pInt,lookup(3)+1_pInt) - &
|
centres(1:3,lookup(1)+1_pInt,lookup(2)+1_pInt,lookup(3)+1_pInt) &
|
||||||
math_mul33x3(Favg, shift*gDim)
|
- math_mul33x3(Favg, real(shift,pReal)*gDim)
|
||||||
endif
|
endif
|
||||||
enddo; enddo; enddo
|
enddo; enddo; enddo
|
||||||
|
|
||||||
|
|
|
@ -251,10 +251,8 @@ subroutine numerics_init
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! try to open the config file
|
! try to open the config file
|
||||||
fileExists: if(IO_open_file_stat(FILEUNIT,numerics_configFile)) then
|
fileExists: if(IO_open_file_stat(FILEUNIT,numerics_configFile)) then
|
||||||
mainProcess2: if (worldrank == 0) then
|
write(6,'(a,/)') ' using values from config file'
|
||||||
write(6,'(a,/)') ' using values from config file'
|
flush(6)
|
||||||
flush(6)
|
|
||||||
endif mainProcess2
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! read variables from config file and overwrite default parameters if keyword is present
|
! read variables from config file and overwrite default parameters if keyword is present
|
||||||
|
|
|
@ -57,7 +57,9 @@ subroutine DAMASK_interface_init()
|
||||||
tag
|
tag
|
||||||
integer :: &
|
integer :: &
|
||||||
i, &
|
i, &
|
||||||
|
#ifdef _OPENMP
|
||||||
threadLevel, &
|
threadLevel, &
|
||||||
|
#endif
|
||||||
worldrank = 0, &
|
worldrank = 0, &
|
||||||
worldsize = 0
|
worldsize = 0
|
||||||
integer, allocatable, dimension(:) :: &
|
integer, allocatable, dimension(:) :: &
|
||||||
|
|
Loading…
Reference in New Issue