removed unnecsessary omp statements, removed one transpose in constitutitve

This commit is contained in:
Martin Diehl 2013-01-08 11:09:20 +00:00
parent ce7a0571fd
commit 19d86ca06a
6 changed files with 22 additions and 29 deletions

View File

@ -101,12 +101,10 @@ subroutine FE_init
character(len=1024) :: line character(len=1024) :: line
integer(pInt), dimension(1_pInt+2_pInt*maxNchunks) :: positions integer(pInt), dimension(1_pInt+2_pInt*maxNchunks) :: positions
#endif #endif
!$OMP CRITICAL (write2out)
write(6,*) write(6,*)
write(6,*) '<<<+- FEsolving init -+>>>' write(6,*) '<<<+- FEsolving init -+>>>'
write(6,*) '$Id$' write(6,*) '$Id$'
#include "compilation_info.f90" #include "compilation_info.f90"
!$OMP END CRITICAL (write2out)
modelName = getSolverJobName() modelName = getSolverJobName()
#ifdef Spectral #ifdef Spectral
@ -179,14 +177,12 @@ subroutine FE_init
if (allocated(calcMode)) deallocate(calcMode) if (allocated(calcMode)) deallocate(calcMode)
if (allocated(FEsolving_execIP)) deallocate(FEsolving_execIP) if (allocated(FEsolving_execIP)) deallocate(FEsolving_execIP)
#endif #endif
!$OMP CRITICAL (write2out)
if (iand(debug_level(debug_FEsolving),debug_levelBasic) /= 0_pInt) then if (iand(debug_level(debug_FEsolving),debug_levelBasic) /= 0_pInt) then
write(6,*) 'restart writing: ', restartWrite write(6,*) 'restart writing: ', restartWrite
write(6,*) 'restart reading: ', restartRead write(6,*) 'restart reading: ', restartRead
if (restartRead) write(6,*) 'restart Job: ', trim(modelName) if (restartRead) write(6,*) 'restart Job: ', trim(modelName)
write(6,*) write(6,*)
endif endif
!$OMP END CRITICAL (write2out)
end subroutine FE_init end subroutine FE_init

View File

@ -1602,7 +1602,6 @@ recursive function abaqus_assembleInputFile(unit1,unit2) result(createSuccess)
read(unit2,'(A300)',END=220) line read(unit2,'(A300)',END=220) line
positions = IO_stringPos(line,maxNchunks) positions = IO_stringPos(line,maxNchunks)
! call IO_lcInPlace(line)
if (IO_lc(IO_StringValue(line,positions,1_pInt))=='*include') then if (IO_lc(IO_StringValue(line,positions,1_pInt))=='*include') then
fname = trim(getSolverWorkingDirectoryName())//trim(line(9+scan(line(9:),'='):)) fname = trim(getSolverWorkingDirectoryName())//trim(line(9+scan(line(9:),'='):))
inquire(file=fname, exist=fexist) inquire(file=fname, exist=fexist)

View File

@ -730,9 +730,10 @@ end subroutine constitutive_TandItsTangent
!************************************************************************ !************************************************************************
pure subroutine constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, g, i, e) pure subroutine constitutive_hooke_TandItsTangent(T, dT_dFe, Fe, g, i, e)
use prec, only: p_vec use math, only : &
use math math_mul33x33, &
math_Mandel66to3333, &
math_transpose33
implicit none implicit none
!* Definition of variables !* Definition of variables
@ -744,19 +745,17 @@ integer(pInt) p, o
real(pReal), dimension(3,3), intent(out) :: T real(pReal), dimension(3,3), intent(out) :: T
real(pReal), dimension(3,3,3,3), intent(out) :: dT_dFe real(pReal), dimension(3,3,3,3), intent(out) :: dT_dFe
real(pReal), dimension(6,6) :: C_66 real(pReal), dimension(3,3) :: FeT
real(pReal), dimension(3,3,3,3) :: C real(pReal), dimension(3,3,3,3) :: C
!* get elasticity tensor !* get elasticity tensor
C_66 = constitutive_homogenizedC(g,i,e) C = math_Mandel66to3333(constitutive_homogenizedC(g,i,e))
C = math_Mandel66to3333(C_66)
T = 0.5_pReal*math_mul3333xx33(C,math_mul33x33(math_transpose33(Fe),Fe)-math_I3) FeT = math_transpose33(Fe)
T = 0.5_pReal*math_mul3333xx33(C,math_mul33x33(FeT,Fe)-math_I3)
do p=1_pInt,3_pInt; do o=1_pInt,3_pInt forall (o=1_pInt:3_pInt, p=1_pInt:3_pInt) dT_dFe(o,p,1:3,1:3) = math_mul33x33(C(o,p,1:3,1:3), FeT) ! dT*_ij/dFe_kl
dT_dFe(o,p,1:3,1:3) = math_mul33x33(C(o,p,1:3,1:3), math_transpose33(Fe)) ! dT*_ij/dFe_kl
enddo; enddo
end subroutine constitutive_hooke_TandItsTangent end subroutine constitutive_hooke_TandItsTangent

View File

@ -609,7 +609,7 @@ pure function constitutive_phenopowerlaw_homogenizedC(state,ipc,ip,el)
state ! state variables state ! state variables
matID = phase_plasticityInstance(material_phase(ipc,ip,el)) matID = phase_plasticityInstance(material_phase(ipc,ip,el))
constitutive_phenopowerlaw_homogenizedC = constitutive_phenopowerlaw_Cslip_66(:,:,matID) constitutive_phenopowerlaw_homogenizedC = constitutive_phenopowerlaw_Cslip_66(6,6,matID)
end function constitutive_phenopowerlaw_homogenizedC end function constitutive_phenopowerlaw_homogenizedC

View File

@ -1201,7 +1201,7 @@ pure function math_norm3(v)
real(pReal), dimension(3), intent(in) :: v real(pReal), dimension(3), intent(in) :: v
real(pReal) :: math_norm3 real(pReal) :: math_norm3
math_norm3 = sqrt(v(1)*v(1) + v(2)*v(2) + v(3)*v(3)) math_norm3 = sqrt(sum(v**2.0_pReal))
end function math_norm3 end function math_norm3

View File

@ -1,7 +1,7 @@
! Copyright 2011 Max-Planck-Institut fŸr Eisenforschung GmbH ! Copyright 2011 Max-Planck-Institut für Eisenforschung GmbH
! !
! This file is part of DAMASK, ! This file is part of DAMASK,
! the DŸsseldorf Advanced Material Simulation Kit. ! the Düsseldorf Advanced Material Simulation Kit.
! !
! DAMASK is free software: you can redistribute it and/or modify ! DAMASK is free software: you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by ! it under the terms of the GNU General Public License as published by
@ -19,11 +19,11 @@
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!* $Id$ !* $Id$
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
!> @author Franz Roters, Max-Planck-Institut fŸr Eisenforschung GmbH !> @author Franz Roters, Max-Planck-Institut für Eisenforschung GmbH
!! Philip Eisenlohr, Max-Planck-Institut fŸr Eisenforschung GmbH !! Philip Eisenlohr, Max-Planck-Institut für Eisenforschung GmbH
!! Christoph Koords, Max-Planck-Institut fŸr Eisenforschung GmbH !! Christoph Koords, Max-Planck-Institut für Eisenforschung GmbH
!! Martin Diehl, Max-Planck-Institut fŸr Eisenforschung GmbH !! Martin Diehl, Max-Planck-Institut für Eisenforschung GmbH
!! Krishna Komerla, Max-Planck-Institut fŸr Eisenforschung GmbH !! Krishna Komerla, Max-Planck-Institut für Eisenforschung GmbH
!> @brief Sets up the mesh for the solvers MSC.Marc, Abaqus and the spectral solver !> @brief Sets up the mesh for the solvers MSC.Marc, Abaqus and the spectral solver
!-------------------------------------------------------------------------------------------------- !--------------------------------------------------------------------------------------------------
@ -405,12 +405,11 @@ subroutine mesh_init(ip,element)
integer(pInt), parameter :: fileUnit = 222_pInt integer(pInt), parameter :: fileUnit = 222_pInt
integer(pInt) :: e, element, ip integer(pInt) :: e, element, ip
!$OMP CRITICAL (write2out)
write(6,*) write(6,*)
write(6,*) '<<<+- mesh init -+>>>' write(6,*) '<<<+- mesh init -+>>>'
write(6,*) '$Id$' write(6,*) '$Id$'
#include "compilation_info.f90" #include "compilation_info.f90"
!$OMP END CRITICAL (write2out)
if (allocated(mesh_mapFEtoCPelem)) deallocate(mesh_mapFEtoCPelem) if (allocated(mesh_mapFEtoCPelem)) deallocate(mesh_mapFEtoCPelem)
if (allocated(mesh_mapFEtoCPnode)) deallocate(mesh_mapFEtoCPnode) if (allocated(mesh_mapFEtoCPnode)) deallocate(mesh_mapFEtoCPnode)
if (allocated(mesh_node0)) deallocate(mesh_node0) if (allocated(mesh_node0)) deallocate(mesh_node0)