renamed interface from "mpie_interface" to "DAMASK_interface"
This commit is contained in:
parent
75192789e8
commit
fa98133f8e
|
@ -60,7 +60,7 @@ subroutine CPFEM_initAll(Temperature,element,IP)
|
||||||
use crystallite, only: crystallite_init
|
use crystallite, only: crystallite_init
|
||||||
use homogenization, only: homogenization_init
|
use homogenization, only: homogenization_init
|
||||||
use IO, only: IO_init
|
use IO, only: IO_init
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: element, & ! FE element number
|
integer(pInt), intent(in) :: element, & ! FE element number
|
||||||
|
@ -92,7 +92,7 @@ subroutine CPFEM_initAll(Temperature,element,IP)
|
||||||
call crystallite_init(Temperature) ! (have to) use temperature of first IP for whole model
|
call crystallite_init(Temperature) ! (have to) use temperature of first IP for whole model
|
||||||
call homogenization_init(Temperature)
|
call homogenization_init(Temperature)
|
||||||
call CPFEM_init()
|
call CPFEM_init()
|
||||||
call mpie_interface_init()
|
call DAMASK_interface_init()
|
||||||
CPFEM_init_done = .true.
|
CPFEM_init_done = .true.
|
||||||
CPFEM_init_inProgress = .false.
|
CPFEM_init_inProgress = .false.
|
||||||
else ! loser, loser...
|
else ! loser, loser...
|
||||||
|
@ -299,7 +299,7 @@ subroutine CPFEM_general(mode, ffn, ffn1, Temperature, dt, element, IP, cauchySt
|
||||||
materialpoint_postResults
|
materialpoint_postResults
|
||||||
use IO, only: IO_write_jobBinaryFile, &
|
use IO, only: IO_write_jobBinaryFile, &
|
||||||
IO_warning
|
IO_warning
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
|
|
@ -40,7 +40,7 @@
|
||||||
#include "prec.f90"
|
#include "prec.f90"
|
||||||
|
|
||||||
|
|
||||||
MODULE mpie_interface
|
MODULE DAMASK_interface
|
||||||
|
|
||||||
character(len=64), parameter :: FEsolver = 'Abaqus'
|
character(len=64), parameter :: FEsolver = 'Abaqus'
|
||||||
character(len=4), parameter :: InputFileExtension = '.inp'
|
character(len=4), parameter :: InputFileExtension = '.inp'
|
||||||
|
@ -49,7 +49,7 @@ character(len=4), parameter :: LogFileExtension = '.log'
|
||||||
CONTAINS
|
CONTAINS
|
||||||
|
|
||||||
!--------------------
|
!--------------------
|
||||||
subroutine mpie_interface_init()
|
subroutine DAMASK_interface_init()
|
||||||
!--------------------
|
!--------------------
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) '<<<+- DAMASK_abaqus init -+>>>'
|
write(6,*) '<<<+- DAMASK_abaqus init -+>>>'
|
||||||
|
|
|
@ -40,7 +40,7 @@
|
||||||
#include "prec.f90"
|
#include "prec.f90"
|
||||||
|
|
||||||
|
|
||||||
MODULE mpie_interface
|
MODULE DAMASK_interface
|
||||||
|
|
||||||
character(len=64), parameter :: FEsolver = 'Abaqus'
|
character(len=64), parameter :: FEsolver = 'Abaqus'
|
||||||
character(len=4), parameter :: InputFileExtension = '.inp'
|
character(len=4), parameter :: InputFileExtension = '.inp'
|
||||||
|
@ -49,7 +49,7 @@ character(len=4), parameter :: LogFileExtension = '.log'
|
||||||
CONTAINS
|
CONTAINS
|
||||||
|
|
||||||
!--------------------
|
!--------------------
|
||||||
subroutine mpie_interface_init()
|
subroutine DAMASK_interface_init()
|
||||||
!--------------------
|
!--------------------
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) '<<<+- DAMASK_abaqus init -+>>>'
|
write(6,*) '<<<+- DAMASK_abaqus init -+>>>'
|
||||||
|
|
|
@ -58,7 +58,7 @@
|
||||||
#include "prec.f90"
|
#include "prec.f90"
|
||||||
|
|
||||||
|
|
||||||
MODULE mpie_interface
|
MODULE DAMASK_interface
|
||||||
|
|
||||||
character(len=64), parameter :: FEsolver = 'Marc'
|
character(len=64), parameter :: FEsolver = 'Marc'
|
||||||
character(len=4), parameter :: InputFileExtension = '.dat'
|
character(len=4), parameter :: InputFileExtension = '.dat'
|
||||||
|
@ -66,12 +66,12 @@ character(len=4), parameter :: LogFileExtension = '.log'
|
||||||
|
|
||||||
CONTAINS
|
CONTAINS
|
||||||
|
|
||||||
subroutine mpie_interface_init()
|
subroutine DAMASK_interface_init()
|
||||||
|
|
||||||
|
|
||||||
!$OMP CRITICAL (write2out)
|
!$OMP CRITICAL (write2out)
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) '<<<+- mpie_cpfem_marc init -+>>>'
|
write(6,*) '<<<+- DAMASK_marc init -+>>>'
|
||||||
write(6,*) '$Id$'
|
write(6,*) '$Id$'
|
||||||
write(6,*)
|
write(6,*)
|
||||||
!$OMP END CRITICAL (write2out)
|
!$OMP END CRITICAL (write2out)
|
||||||
|
|
|
@ -43,7 +43,7 @@
|
||||||
program DAMASK_spectral
|
program DAMASK_spectral
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
|
|
||||||
use spectral_interface
|
use DAMASK_interface
|
||||||
use prec, only: pInt, pReal
|
use prec, only: pInt, pReal
|
||||||
use IO
|
use IO
|
||||||
use math
|
use math
|
||||||
|
|
|
@ -20,7 +20,7 @@
|
||||||
!* $Id$
|
!* $Id$
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
|
|
||||||
MODULE spectral_interface
|
MODULE DAMASK_interface
|
||||||
use prec, only: pInt, pReal
|
use prec, only: pInt, pReal
|
||||||
character(len=64), parameter :: FEsolver = 'Spectral'
|
character(len=64), parameter :: FEsolver = 'Spectral'
|
||||||
character(len=5), parameter :: InputFileExtension = '.geom'
|
character(len=5), parameter :: InputFileExtension = '.geom'
|
||||||
|
@ -32,10 +32,10 @@ CONTAINS
|
||||||
! initialize interface module
|
! initialize interface module
|
||||||
!
|
!
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
subroutine spectral_interface_init()
|
subroutine DAMASK_interface_init()
|
||||||
|
|
||||||
write(6,*)
|
write(6,*)
|
||||||
write(6,*) '<<<+- spectral_interface init -+>>>'
|
write(6,*) '<<<+- DAMASK_spectral init -+>>>'
|
||||||
write(6,*) '$Id$'
|
write(6,*) '$Id$'
|
||||||
write(6,*)
|
write(6,*)
|
||||||
|
|
||||||
|
|
|
@ -40,10 +40,10 @@
|
||||||
! - make sure the file "material.config" exists in the working
|
! - make sure the file "material.config" exists in the working
|
||||||
! directory. For further configuration use "numerics.config"
|
! directory. For further configuration use "numerics.config"
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
program mpie_spectral
|
program DAMASK_spectral
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
|
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
use prec, only: pInt, pReal
|
use prec, only: pInt, pReal
|
||||||
use IO
|
use IO
|
||||||
use math
|
use math
|
||||||
|
@ -582,7 +582,7 @@ program mpie_spectral
|
||||||
close(538)
|
close(538)
|
||||||
call sfftw_destroy_plan(plan_fft(1)); call sfftw_destroy_plan(plan_fft(2))
|
call sfftw_destroy_plan(plan_fft(1)); call sfftw_destroy_plan(plan_fft(2))
|
||||||
|
|
||||||
end program mpie_spectral
|
end program DAMASK_spectral
|
||||||
|
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
! quit subroutine to satisfy IO_error
|
! quit subroutine to satisfy IO_error
|
||||||
|
|
18
code/IO.f90
18
code/IO.f90
|
@ -69,7 +69,7 @@ endsubroutine
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
recursive function IO_abaqus_assembleInputFile(unit1,unit2) result(createSuccess)
|
recursive function IO_abaqus_assembleInputFile(unit1,unit2) result(createSuccess)
|
||||||
use prec
|
use prec
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(len=300) line,fname
|
character(len=300) line,fname
|
||||||
|
@ -152,7 +152,7 @@ end function
|
||||||
logical function IO_open_file(unit,relPath)
|
logical function IO_open_file(unit,relPath)
|
||||||
|
|
||||||
use prec, only: pInt
|
use prec, only: pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
character(len=*), parameter :: pathSep = achar(47)//achar(92) ! forward and backward slash
|
||||||
|
@ -178,7 +178,7 @@ end function
|
||||||
logical function IO_open_inputFile(unit)
|
logical function IO_open_inputFile(unit)
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
use prec, only: pReal, pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: unit
|
integer(pInt), intent(in) :: unit
|
||||||
|
@ -210,7 +210,7 @@ end function
|
||||||
logical function IO_open_logFile(unit)
|
logical function IO_open_logFile(unit)
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
use prec, only: pReal, pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: unit
|
integer(pInt), intent(in) :: unit
|
||||||
|
@ -233,7 +233,7 @@ end function
|
||||||
logical function IO_open_jobFile(unit,newExt)
|
logical function IO_open_jobFile(unit,newExt)
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
use prec, only: pReal, pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: unit
|
integer(pInt), intent(in) :: unit
|
||||||
|
@ -257,7 +257,7 @@ end function
|
||||||
logical function IO_write_jobBinaryFile(unit,newExt,recMultiplier)
|
logical function IO_write_jobBinaryFile(unit,newExt,recMultiplier)
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
use prec, only: pReal, pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: unit
|
integer(pInt), intent(in) :: unit
|
||||||
|
@ -288,7 +288,7 @@ end function
|
||||||
logical function IO_read_jobBinaryFile(unit,newExt,jobName,recMultiplier)
|
logical function IO_read_jobBinaryFile(unit,newExt,jobName,recMultiplier)
|
||||||
|
|
||||||
use prec, only: pReal, pInt
|
use prec, only: pReal, pInt
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
integer(pInt), intent(in) :: unit
|
integer(pInt), intent(in) :: unit
|
||||||
|
@ -974,7 +974,7 @@ endfunction
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
function IO_countContinousIntValues (unit)
|
function IO_countContinousIntValues (unit)
|
||||||
|
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
use prec, only: pReal,pInt
|
use prec, only: pReal,pInt
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
@ -1032,7 +1032,7 @@ endfunction
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
function IO_continousIntValues (unit,maxN,lookupName,lookupMap,lookupMaxN)
|
function IO_continousIntValues (unit,maxN,lookupName,lookupMap,lookupMaxN)
|
||||||
|
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
use prec, only: pReal,pInt
|
use prec, only: pReal,pInt
|
||||||
implicit none
|
implicit none
|
||||||
|
|
||||||
|
|
|
@ -261,7 +261,7 @@
|
||||||
!***********************************************************
|
!***********************************************************
|
||||||
subroutine mesh_init (ip,element)
|
subroutine mesh_init (ip,element)
|
||||||
|
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
use prec, only: pInt
|
use prec, only: pInt
|
||||||
use IO, only: IO_error,IO_open_InputFile,IO_abaqus_hasNoPart
|
use IO, only: IO_error,IO_open_InputFile,IO_abaqus_hasNoPart
|
||||||
use FEsolving, only: parallelExecution, FEsolving_execElem, FEsolving_execIP, calcMode, lastMode
|
use FEsolving, only: parallelExecution, FEsolving_execElem, FEsolving_execIP, calcMode, lastMode
|
||||||
|
|
|
@ -43,10 +43,10 @@
|
||||||
! - make sure the file "material.config" exists in the working
|
! - make sure the file "material.config" exists in the working
|
||||||
! directory
|
! directory
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
program mpie_spectral
|
program DAMASK_spectral
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
|
|
||||||
use mpie_interface
|
use DAMASK_interface
|
||||||
use prec, only: pInt, pReal
|
use prec, only: pInt, pReal
|
||||||
use IO
|
use IO
|
||||||
use math
|
use math
|
||||||
|
@ -54,7 +54,7 @@ program mpie_spectral
|
||||||
use numerics, only: relevantStrain, rTol_crystalliteStress
|
use numerics, only: relevantStrain, rTol_crystalliteStress
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
include 'fftw3.f' !header file for fftw3 (declaring variables). Library file is also needed
|
include 'include/fftw3.f' !header file for fftw3 (declaring variables). Library file is also needed
|
||||||
|
|
||||||
! variables to read from loadcase and mesh file
|
! variables to read from loadcase and mesh file
|
||||||
real(pReal), dimension(9) :: valuevector ! stores information temporarily from loadcase file
|
real(pReal), dimension(9) :: valuevector ! stores information temporarily from loadcase file
|
||||||
|
@ -610,7 +610,7 @@ do i=1,3; do m = 1,3; do n = 1,3
|
||||||
call dfftw_destroy_plan(plan_fft(i,m,n))
|
call dfftw_destroy_plan(plan_fft(i,m,n))
|
||||||
enddo; enddo; enddo
|
enddo; enddo; enddo
|
||||||
|
|
||||||
end program mpie_spectral
|
end program DAMASK_spectral
|
||||||
|
|
||||||
!********************************************************************
|
!********************************************************************
|
||||||
! quit subroutine to satisfy IO_error
|
! quit subroutine to satisfy IO_error
|
||||||
|
|
Loading…
Reference in New Issue