[skip sc] enforce interfaces (quick fix: declare as external)
This commit is contained in:
parent
5881d010b9
commit
b8c3d75700
|
@ -18,7 +18,7 @@ module CLI
|
|||
use parallelization
|
||||
use system_routines
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
integer, public, protected :: &
|
||||
CLI_restartInc = 0 !< Increment at which calculation starts
|
||||
|
|
|
@ -18,7 +18,7 @@ module HDF5_utilities
|
|||
use prec
|
||||
use parallelization
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -12,7 +12,7 @@ module IO
|
|||
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
character(len=*), parameter, public :: &
|
||||
|
|
|
@ -8,7 +8,7 @@ module LAPACK_interface
|
|||
|
||||
pure subroutine dgeev(jobvl,jobvr,n,a,lda,wr,wi,vl,ldvl,vr,ldvr,work,lwork,info)
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
character, intent(in) :: jobvl,jobvr
|
||||
integer, intent(in) :: n,lda,ldvl,ldvr,lwork
|
||||
|
@ -22,7 +22,7 @@ module LAPACK_interface
|
|||
|
||||
pure subroutine dgesv(n,nrhs,a,lda,ipiv,b,ldb,info)
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
integer, intent(in) :: n,nrhs,lda,ldb
|
||||
real(pReal), intent(inout), dimension(lda,n) :: a
|
||||
|
@ -33,7 +33,7 @@ module LAPACK_interface
|
|||
|
||||
pure subroutine dgetrf(m,n,a,lda,ipiv,info)
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
integer, intent(in) :: m,n,lda
|
||||
real(pReal), intent(inout), dimension(lda,n) :: a
|
||||
|
@ -43,7 +43,7 @@ module LAPACK_interface
|
|||
|
||||
pure subroutine dgetri(n,a,lda,ipiv,work,lwork,info)
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
integer, intent(in) :: n,lda,lwork
|
||||
real(pReal), intent(inout), dimension(lda,n) :: a
|
||||
|
@ -54,7 +54,7 @@ module LAPACK_interface
|
|||
|
||||
pure subroutine dsyev(jobz,uplo,n,a,lda,w,work,lwork,info)
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
character, intent(in) :: jobz,uplo
|
||||
integer, intent(in) :: n,lda,lwork
|
||||
|
|
|
@ -25,7 +25,7 @@ module DAMASK_interface
|
|||
use ifport, only: &
|
||||
CHDIR
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
logical, protected, public :: symmetricSolver
|
||||
|
@ -210,7 +210,7 @@ subroutine hypela2(d,g,e,de,s,t,dt,ngens,m,nn,kcus,matus,ndi,nshear,disp, &
|
|||
use materialpoint_Marc
|
||||
use OMP_LIB
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
integer, intent(in) :: & ! according to MSC.Marc 2012 Manual D
|
||||
ngens, & !< size of stress-strain law
|
||||
nn, & !< integration point number
|
||||
|
@ -382,7 +382,7 @@ subroutine flux(f,ts,n,time)
|
|||
use homogenization
|
||||
use discretization_Marc
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
real(pReal), dimension(6), intent(in) :: &
|
||||
ts
|
||||
integer, dimension(10), intent(in) :: &
|
||||
|
@ -409,7 +409,7 @@ subroutine uedinc(inc,incsub)
|
|||
use materialpoint_Marc
|
||||
use discretization_Marc
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
integer, intent(in) :: inc, incsub
|
||||
integer :: n, nqncomp, nqdatatype
|
||||
integer, save :: inc_written
|
||||
|
|
|
@ -17,7 +17,7 @@ module discretization_Marc
|
|||
use geometry_plastic_nonlocal
|
||||
use results
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
real(pReal), public, protected :: &
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
module element
|
||||
use IO
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
!---------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -23,7 +23,7 @@ module materialpoint_Marc
|
|||
use discretization
|
||||
use discretization_Marc
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
real(pReal), dimension (:,:,:), allocatable, private :: &
|
||||
|
|
|
@ -12,7 +12,7 @@ module YAML_parse
|
|||
use system_routines
|
||||
#endif
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
public :: &
|
||||
|
@ -24,7 +24,7 @@ module YAML_parse
|
|||
|
||||
subroutine to_flow_C(flow,length_flow,mixed) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_INT, C_CHAR, C_PTR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type(C_PTR), intent(out) :: flow
|
||||
integer(C_INT), intent(out) :: length_flow
|
||||
|
|
|
@ -11,7 +11,7 @@ module YAML_types
|
|||
use IO
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type, abstract, public :: tNode
|
||||
|
|
|
@ -9,7 +9,7 @@ module config
|
|||
use results
|
||||
use parallelization
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
class(tNode), pointer, public :: &
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
module constants
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
|
||||
real(pReal), parameter :: &
|
||||
|
|
|
@ -7,7 +7,7 @@ module discretization
|
|||
use prec
|
||||
use results
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
integer, public, protected :: &
|
||||
|
|
|
@ -9,7 +9,7 @@ module geometry_plastic_nonlocal
|
|||
use prec
|
||||
use results
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
|
||||
integer, protected :: &
|
||||
|
|
|
@ -30,7 +30,7 @@ program DAMASK_grid
|
|||
use grid_thermal_spectral
|
||||
use results
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type :: tLoadCase
|
||||
type(tRotation) :: rot !< rotation of BC
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
module FFTW3
|
||||
use, intrinsic :: ISO_C_binding
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
|
||||
include 'fftw3-mpi.f03'
|
||||
|
|
|
@ -8,7 +8,7 @@ module VTI
|
|||
use base64
|
||||
use IO
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
public :: &
|
||||
|
|
|
@ -7,7 +7,7 @@ module base64
|
|||
use prec
|
||||
use IO
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
character(len=*), parameter :: &
|
||||
|
|
|
@ -23,7 +23,7 @@ module discretization_grid
|
|||
use discretization
|
||||
use geometry_plastic_nonlocal
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
integer, dimension(3), public, protected :: &
|
||||
|
|
|
@ -22,7 +22,7 @@ module grid_damage_spectral
|
|||
use YAML_types
|
||||
use config
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type :: tNumerics
|
||||
|
|
|
@ -27,7 +27,7 @@ module grid_mechanical_FEM
|
|||
use discretization
|
||||
use discretization_grid
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type(tSolutionParams) :: params
|
||||
|
|
|
@ -26,7 +26,7 @@ module grid_mechanical_spectral_basic
|
|||
use homogenization
|
||||
use discretization_grid
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type(tSolutionParams) :: params
|
||||
|
|
|
@ -26,7 +26,7 @@ module grid_mechanical_spectral_polarisation
|
|||
use homogenization
|
||||
use discretization_grid
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type(tSolutionParams) :: params
|
||||
|
|
|
@ -25,7 +25,7 @@ module grid_thermal_spectral
|
|||
use YAML_types
|
||||
use config
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type :: tNumerics
|
||||
|
|
|
@ -22,7 +22,7 @@ module spectral_utilities
|
|||
use discretization
|
||||
use homogenization
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
module zlib
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
public :: &
|
||||
|
@ -15,7 +15,7 @@ module zlib
|
|||
|
||||
subroutine inflate_C(s_deflated,s_inflated,deflated,inflated) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_SIGNED_CHAR, C_INT64_T
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
integer(C_INT64_T), intent(in) :: s_deflated,s_inflated
|
||||
integer(C_SIGNED_CHAR), dimension(s_deflated), intent(in) :: deflated
|
||||
|
|
|
@ -18,7 +18,7 @@ module homogenization
|
|||
use results
|
||||
use lattice
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type :: tState
|
||||
|
|
|
@ -13,7 +13,7 @@ module lattice
|
|||
use math
|
||||
use rotations
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
|
|
@ -14,7 +14,7 @@ module material
|
|||
use discretization
|
||||
use YAML_types
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type, public :: tRotationContainer
|
||||
|
|
|
@ -31,7 +31,7 @@ module materialpoint
|
|||
use discretization_grid
|
||||
#endif
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
|
||||
contains
|
||||
|
|
|
@ -12,7 +12,7 @@ module math
|
|||
use YAML_types
|
||||
use LAPACK_interface
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
#if __INTEL_COMPILER >= 1900
|
||||
! do not make use of associated entities available to other modules
|
||||
|
|
|
@ -20,7 +20,7 @@ program DAMASK_mesh
|
|||
use FEM_Utilities
|
||||
use mesh_mechanical_FEM
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type :: tLoadCase
|
||||
real(pReal) :: time = 0.0_pReal !< length of increment
|
||||
|
|
|
@ -5,7 +5,7 @@
|
|||
module FEM_quadrature
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
integer, parameter :: &
|
||||
|
|
|
@ -21,7 +21,7 @@ module FEM_utilities
|
|||
use homogenization
|
||||
use FEM_quadrature
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
logical, public :: cutBack = .false. !< cut back of BVP solver in case convergence is not achieved or a material point is terminally ill
|
||||
|
@ -65,6 +65,11 @@ module FEM_utilities
|
|||
type(tComponentBC), allocatable, dimension(:) :: componentBC
|
||||
end type tFieldBC
|
||||
|
||||
external :: &
|
||||
PetscSectionGetFieldComponents, &
|
||||
PetscSectionGetFieldDof, &
|
||||
PetscSectionGetFieldOffset
|
||||
|
||||
public :: &
|
||||
FEM_utilities_init, &
|
||||
utilities_constitutiveResponse, &
|
||||
|
|
|
@ -25,7 +25,7 @@ module discretization_mesh
|
|||
use YAML_types
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
integer, public, protected :: &
|
||||
|
@ -52,6 +52,8 @@ module discretization_mesh
|
|||
real(pReal), dimension(:,:,:), allocatable :: &
|
||||
mesh_ipCoordinates !< IP x,y,z coordinates (after deformation!)
|
||||
|
||||
external :: &
|
||||
DMView ! ToDo: write interface
|
||||
public :: &
|
||||
discretization_mesh_init, &
|
||||
mesh_FEM_build_ipVolumes, &
|
||||
|
|
|
@ -26,7 +26,7 @@ module mesh_mechanical_FEM
|
|||
use homogenization
|
||||
use math
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
!--------------------------------------------------------------------------------------------------
|
||||
|
@ -67,6 +67,15 @@ module mesh_mechanical_FEM
|
|||
logical :: ForwardData
|
||||
real(pReal), parameter :: eps = 1.0e-18_pReal
|
||||
|
||||
external :: &
|
||||
PetscSectionGetNumFields, &
|
||||
PetscFESetQuadrature, &
|
||||
PetscFEGetDimension, &
|
||||
PetscFEDestroy, &
|
||||
PetscSectionGetDof, &
|
||||
PetscFEGetDualSpace, &
|
||||
PetscDualSpaceGetFunctional
|
||||
|
||||
public :: &
|
||||
FEM_mechanical_init, &
|
||||
FEM_mechanical_solution, &
|
||||
|
|
|
@ -18,7 +18,7 @@ module parallelization
|
|||
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
#ifndef PETSC
|
||||
|
|
|
@ -19,7 +19,7 @@ module phase
|
|||
use HDF5
|
||||
use HDF5_utilities
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type :: tState
|
||||
|
|
|
@ -8,7 +8,7 @@ module polynomials
|
|||
use YAML_parse
|
||||
use YAML_types
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
type, public :: tPolynomial
|
||||
|
|
|
@ -15,7 +15,7 @@ module prec
|
|||
use PETScSys
|
||||
#endif
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
public
|
||||
|
||||
! https://stevelionel.com/drfortran/2017/03/27/doctor-fortran-in-it-takes-all-kinds
|
||||
|
|
|
@ -12,7 +12,7 @@ subroutine quit(stop_id)
|
|||
#endif
|
||||
use HDF5
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
integer, intent(in) :: stop_id
|
||||
integer, dimension(8) :: dateAndTime
|
||||
integer :: err_HDF5
|
||||
|
|
|
@ -21,7 +21,7 @@ module results
|
|||
use DAMASK_interface
|
||||
#endif
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
integer(HID_T) :: resultsFile
|
||||
|
|
|
@ -50,7 +50,7 @@ module rotations
|
|||
use IO
|
||||
use math
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
real(pReal), parameter :: P = -1.0_pReal !< parameter for orientation conversion.
|
||||
|
@ -796,7 +796,7 @@ end function conjugateQuaternion
|
|||
subroutine selfTest()
|
||||
|
||||
type(tRotation) :: R
|
||||
real(pReal), dimension(4) :: qu, ax
|
||||
real(pReal), dimension(4) :: qu
|
||||
real(pReal), dimension(3) :: x, eu, v3
|
||||
real(pReal), dimension(3,3) :: om, t33
|
||||
real(pReal), dimension(3,3,3,3) :: t3333
|
||||
|
|
|
@ -6,7 +6,7 @@ module signals
|
|||
use prec
|
||||
use system_routines
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
logical, volatile, public, protected :: &
|
||||
|
|
|
@ -7,7 +7,7 @@ module system_routines
|
|||
|
||||
use prec
|
||||
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
private
|
||||
|
||||
public :: &
|
||||
|
@ -27,7 +27,7 @@ module system_routines
|
|||
|
||||
function setCWD_C(cwd) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_INT, C_CHAR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
integer(C_INT) :: setCWD_C
|
||||
character(kind=C_CHAR), dimension(*), intent(in) :: cwd
|
||||
|
@ -36,7 +36,7 @@ module system_routines
|
|||
subroutine getCWD_C(cwd, stat) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_INT, C_CHAR
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
character(kind=C_CHAR), dimension(pPathLen+1), intent(out) :: cwd ! NULL-terminated array
|
||||
integer(C_INT), intent(out) :: stat
|
||||
|
@ -45,7 +45,7 @@ module system_routines
|
|||
subroutine getHostName_C(hostname, stat) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_INT, C_CHAR
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
character(kind=C_CHAR), dimension(pStringLen+1), intent(out) :: hostname ! NULL-terminated array
|
||||
integer(C_INT), intent(out) :: stat
|
||||
|
@ -54,7 +54,7 @@ module system_routines
|
|||
subroutine getUserName_C(username, stat) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_INT, C_CHAR
|
||||
use prec
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
character(kind=C_CHAR), dimension(pStringLen+1), intent(out) :: username ! NULL-terminated array
|
||||
integer(C_INT), intent(out) :: stat
|
||||
|
@ -62,28 +62,28 @@ module system_routines
|
|||
|
||||
subroutine signalint_C(handler) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_FUNPTR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type(C_FUNPTR), intent(in), value :: handler
|
||||
end subroutine signalint_C
|
||||
|
||||
subroutine signalusr1_C(handler) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_FUNPTR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type(C_FUNPTR), intent(in), value :: handler
|
||||
end subroutine signalusr1_C
|
||||
|
||||
subroutine signalusr2_C(handler) bind(C)
|
||||
use, intrinsic :: ISO_C_Binding, only: C_FUNPTR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type(C_FUNPTR), intent(in), value :: handler
|
||||
end subroutine signalusr2_C
|
||||
|
||||
subroutine free_C(ptr) bind(C,name='free')
|
||||
use, intrinsic :: ISO_C_Binding, only: C_PTR
|
||||
implicit none
|
||||
implicit none(type,external)
|
||||
|
||||
type(C_PTR), value :: ptr
|
||||
end subroutine free_C
|
||||
|
|
Loading…
Reference in New Issue