only mechanics at the moment
will be extended, but most likely differently
This commit is contained in:
parent
eb834b635d
commit
5b66db8a39
|
@ -21,7 +21,6 @@ program DAMASK_mesh
|
||||||
use mesh_mechanical_FEM
|
use mesh_mechanical_FEM
|
||||||
|
|
||||||
implicit none
|
implicit none
|
||||||
integer :: nActiveFields = 0
|
|
||||||
|
|
||||||
type :: tLoadCase
|
type :: tLoadCase
|
||||||
real(pReal) :: time = 0.0_pReal !< length of increment
|
real(pReal) :: time = 0.0_pReal !< length of increment
|
||||||
|
@ -78,7 +77,7 @@ program DAMASK_mesh
|
||||||
|
|
||||||
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
|
type(tLoadCase), allocatable, dimension(:) :: loadCases !< array of all load cases
|
||||||
type(tSolutionState), allocatable, dimension(:) :: solres
|
type(tSolutionState), allocatable, dimension(:) :: solres
|
||||||
PetscInt :: faceSet, currentFaceSet, field, dimPlex
|
PetscInt :: faceSet, currentFaceSet, dimPlex
|
||||||
PetscErrorCode :: ierr
|
PetscErrorCode :: ierr
|
||||||
integer(kind(COMPONENT_UNDEFINED_ID)) :: ID
|
integer(kind(COMPONENT_UNDEFINED_ID)) :: ID
|
||||||
external :: &
|
external :: &
|
||||||
|
@ -101,8 +100,7 @@ program DAMASK_mesh
|
||||||
! reading basic information from load case file and allocate data structure containing load cases
|
! reading basic information from load case file and allocate data structure containing load cases
|
||||||
call DMGetDimension(geomMesh,dimPlex,ierr) !< dimension of mesh (2D or 3D)
|
call DMGetDimension(geomMesh,dimPlex,ierr) !< dimension of mesh (2D or 3D)
|
||||||
CHKERRA(ierr)
|
CHKERRA(ierr)
|
||||||
nActiveFields = 1
|
allocate(solres(1))
|
||||||
allocate(solres(nActiveFields))
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! reading basic information from load case file and allocate data structure containing load cases
|
! reading basic information from load case file and allocate data structure containing load cases
|
||||||
|
@ -124,32 +122,26 @@ program DAMASK_mesh
|
||||||
allocate(loadCases(N_def))
|
allocate(loadCases(N_def))
|
||||||
|
|
||||||
do i = 1, size(loadCases)
|
do i = 1, size(loadCases)
|
||||||
allocate(loadCases(i)%fieldBC(nActiveFields))
|
allocate(loadCases(i)%fieldBC(1))
|
||||||
field = 1
|
loadCases(i)%fieldBC(1)%ID = FIELD_MECH_ID
|
||||||
loadCases(i)%fieldBC(field)%ID = FIELD_MECH_ID
|
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
do i = 1, size(loadCases)
|
do i = 1, size(loadCases)
|
||||||
do field = 1, nActiveFields
|
loadCases(i)%fieldBC(1)%nComponents = dimPlex !< X, Y (, Z) displacements
|
||||||
select case (loadCases(i)%fieldBC(field)%ID)
|
allocate(loadCases(i)%fieldBC(1)%componentBC(loadCases(i)%fieldBC(1)%nComponents))
|
||||||
case(FIELD_MECH_ID)
|
do component = 1, loadCases(i)%fieldBC(1)%nComponents
|
||||||
loadCases(i)%fieldBC(field)%nComponents = dimPlex !< X, Y (, Z) displacements
|
|
||||||
allocate(loadCases(i)%fieldBC(field)%componentBC(loadCases(i)%fieldBC(field)%nComponents))
|
|
||||||
do component = 1, loadCases(i)%fieldBC(field)%nComponents
|
|
||||||
select case (component)
|
select case (component)
|
||||||
case (1)
|
case (1)
|
||||||
loadCases(i)%fieldBC(field)%componentBC(component)%ID = COMPONENT_MECH_X_ID
|
loadCases(i)%fieldBC(1)%componentBC(component)%ID = COMPONENT_MECH_X_ID
|
||||||
case (2)
|
case (2)
|
||||||
loadCases(i)%fieldBC(field)%componentBC(component)%ID = COMPONENT_MECH_Y_ID
|
loadCases(i)%fieldBC(1)%componentBC(component)%ID = COMPONENT_MECH_Y_ID
|
||||||
case (3)
|
case (3)
|
||||||
loadCases(i)%fieldBC(field)%componentBC(component)%ID = COMPONENT_MECH_Z_ID
|
loadCases(i)%fieldBC(1)%componentBC(component)%ID = COMPONENT_MECH_Z_ID
|
||||||
end select
|
end select
|
||||||
enddo
|
enddo
|
||||||
end select
|
do component = 1, loadCases(i)%fieldBC(1)%nComponents
|
||||||
do component = 1, loadCases(i)%fieldBC(field)%nComponents
|
allocate(loadCases(i)%fieldBC(1)%componentBC(component)%Value(mesh_Nboundaries), source = 0.0_pReal)
|
||||||
allocate(loadCases(i)%fieldBC(field)%componentBC(component)%Value(mesh_Nboundaries), source = 0.0_pReal)
|
allocate(loadCases(i)%fieldBC(1)%componentBC(component)%Mask (mesh_Nboundaries), source = .false.)
|
||||||
allocate(loadCases(i)%fieldBC(field)%componentBC(component)%Mask (mesh_Nboundaries), source = .false.)
|
|
||||||
enddo
|
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
|
||||||
|
@ -194,18 +186,14 @@ program DAMASK_mesh
|
||||||
ID = COMPONENT_MECH_Z_ID
|
ID = COMPONENT_MECH_Z_ID
|
||||||
end select
|
end select
|
||||||
|
|
||||||
do field = 1, nActiveFields
|
do component = 1, loadcases(currentLoadCase)%fieldBC(1)%nComponents
|
||||||
if (loadCases(currentLoadCase)%fieldBC(field)%ID == FIELD_MECH_ID) then
|
if (loadCases(currentLoadCase)%fieldBC(1)%componentBC(component)%ID == ID) then
|
||||||
do component = 1, loadcases(currentLoadCase)%fieldBC(field)%nComponents
|
loadCases(currentLoadCase)%fieldBC(1)%componentBC(component)%Mask (currentFaceSet) = &
|
||||||
if (loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%ID == ID) then
|
|
||||||
loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%Mask (currentFaceSet) = &
|
|
||||||
.true.
|
.true.
|
||||||
loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%Value(currentFaceSet) = &
|
loadCases(currentLoadCase)%fieldBC(1)%componentBC(component)%Value(currentFaceSet) = &
|
||||||
IO_floatValue(line,chunkPos,i+1)
|
IO_floatValue(line,chunkPos,i+1)
|
||||||
endif
|
endif
|
||||||
enddo
|
enddo
|
||||||
endif
|
|
||||||
enddo
|
|
||||||
end select
|
end select
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
|
@ -219,22 +207,17 @@ program DAMASK_mesh
|
||||||
print'(a,i0)', ' load case: ', currentLoadCase
|
print'(a,i0)', ' load case: ', currentLoadCase
|
||||||
if (.not. loadCases(currentLoadCase)%followFormerTrajectory) &
|
if (.not. loadCases(currentLoadCase)%followFormerTrajectory) &
|
||||||
print'(a)', ' drop guessing along trajectory'
|
print'(a)', ' drop guessing along trajectory'
|
||||||
do field = 1, nActiveFields
|
|
||||||
select case (loadCases(currentLoadCase)%fieldBC(field)%ID)
|
|
||||||
case(FIELD_MECH_ID)
|
|
||||||
print'(a)', ' Field '//trim(FIELD_MECH_label)
|
print'(a)', ' Field '//trim(FIELD_MECH_label)
|
||||||
|
|
||||||
end select
|
|
||||||
do faceSet = 1, mesh_Nboundaries
|
do faceSet = 1, mesh_Nboundaries
|
||||||
do component = 1, loadCases(currentLoadCase)%fieldBC(field)%nComponents
|
do component = 1, loadCases(currentLoadCase)%fieldBC(1)%nComponents
|
||||||
if (loadCases(currentLoadCase)%fieldBC(field)%componentBC(component)%Mask(faceSet)) &
|
if (loadCases(currentLoadCase)%fieldBC(1)%componentBC(component)%Mask(faceSet)) &
|
||||||
print'(a,i2,a,i2,a,f12.7)', ' Face ', mesh_boundaries(faceSet), &
|
print'(a,i2,a,i2,a,f12.7)', ' Face ', mesh_boundaries(faceSet), &
|
||||||
' Component ', component, &
|
' Component ', component, &
|
||||||
' Value ', loadCases(currentLoadCase)%fieldBC(field)% &
|
' Value ', loadCases(currentLoadCase)%fieldBC(1)% &
|
||||||
componentBC(component)%Value(faceSet)
|
componentBC(component)%Value(faceSet)
|
||||||
enddo
|
enddo
|
||||||
enddo
|
enddo
|
||||||
enddo
|
|
||||||
print'(a,f12.6)', ' time: ', loadCases(currentLoadCase)%time
|
print'(a,f12.6)', ' time: ', loadCases(currentLoadCase)%time
|
||||||
if (loadCases(currentLoadCase)%incs < 1) errorID = 835 ! non-positive incs count
|
if (loadCases(currentLoadCase)%incs < 1) errorID = 835 ! non-positive incs count
|
||||||
print'(a,i5)', ' increments: ', loadCases(currentLoadCase)%incs
|
print'(a,i5)', ' increments: ', loadCases(currentLoadCase)%incs
|
||||||
|
@ -247,12 +230,7 @@ program DAMASK_mesh
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! doing initialization depending on active solvers
|
! doing initialization depending on active solvers
|
||||||
call FEM_Utilities_init
|
call FEM_Utilities_init
|
||||||
do field = 1, nActiveFields
|
call FEM_mechanical_init(loadCases(1)%fieldBC(1))
|
||||||
select case (loadCases(1)%fieldBC(field)%ID)
|
|
||||||
case(FIELD_MECH_ID)
|
|
||||||
call FEM_mechanical_init(loadCases(1)%fieldBC(field))
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
|
|
||||||
if (worldrank == 0) then
|
if (worldrank == 0) then
|
||||||
open(newunit=statUnit,file=trim(getSolverJobName())//'.sta',form='FORMATTED',status='REPLACE')
|
open(newunit=statUnit,file=trim(getSolverJobName())//'.sta',form='FORMATTED',status='REPLACE')
|
||||||
|
@ -295,33 +273,16 @@ program DAMASK_mesh
|
||||||
'-',stepFraction, '/', subStepFactor**cutBackLevel
|
'-',stepFraction, '/', subStepFactor**cutBackLevel
|
||||||
flush(IO_STDOUT)
|
flush(IO_STDOUT)
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
call FEM_mechanical_forward(guess,timeinc,timeIncOld,loadCases(currentLoadCase)%fieldBC(1))
|
||||||
! forward fields
|
|
||||||
do field = 1, nActiveFields
|
|
||||||
select case (loadCases(currentLoadCase)%fieldBC(field)%ID)
|
|
||||||
case(FIELD_MECH_ID)
|
|
||||||
call FEM_mechanical_forward (&
|
|
||||||
guess,timeinc,timeIncOld,loadCases(currentLoadCase)%fieldBC(field))
|
|
||||||
|
|
||||||
end select
|
|
||||||
enddo
|
|
||||||
|
|
||||||
!--------------------------------------------------------------------------------------------------
|
!--------------------------------------------------------------------------------------------------
|
||||||
! solve fields
|
! solve fields
|
||||||
stagIter = 0
|
stagIter = 0
|
||||||
stagIterate = .true.
|
stagIterate = .true.
|
||||||
do while (stagIterate)
|
do while (stagIterate)
|
||||||
do field = 1, nActiveFields
|
solres(1) = FEM_mechanical_solution(incInfo,timeinc,timeIncOld,loadCases(currentLoadCase)%fieldBC(1))
|
||||||
select case (loadCases(currentLoadCase)%fieldBC(field)%ID)
|
if(.not. solres(1)%converged) exit
|
||||||
case(FIELD_MECH_ID)
|
|
||||||
solres(field) = FEM_mechanical_solution (&
|
|
||||||
incInfo,timeinc,timeIncOld,loadCases(currentLoadCase)%fieldBC(field))
|
|
||||||
|
|
||||||
end select
|
|
||||||
|
|
||||||
if(.not. solres(field)%converged) exit ! no solution found
|
|
||||||
|
|
||||||
enddo
|
|
||||||
stagIter = stagIter + 1
|
stagIter = stagIter + 1
|
||||||
stagIterate = stagIter < stagItMax &
|
stagIterate = stagIter < stagItMax &
|
||||||
.and. all(solres(:)%converged) &
|
.and. all(solres(:)%converged) &
|
||||||
|
|
|
@ -61,7 +61,7 @@ module FEM_utilities
|
||||||
type, public :: tFieldBC
|
type, public :: tFieldBC
|
||||||
integer(kind(FIELD_UNDEFINED_ID)) :: ID
|
integer(kind(FIELD_UNDEFINED_ID)) :: ID
|
||||||
integer :: nComponents = 0
|
integer :: nComponents = 0
|
||||||
type(tComponentBC), allocatable :: componentBC(:)
|
type(tComponentBC), allocatable, dimension(:) :: componentBC
|
||||||
end type tFieldBC
|
end type tFieldBC
|
||||||
|
|
||||||
public :: &
|
public :: &
|
||||||
|
|
Loading…
Reference in New Issue