changed Line Ending to Unix style (LF)

This commit is contained in:
Philip Eisenlohr 2009-01-19 19:10:58 +00:00
parent abb2e3ef30
commit cbd7c279d4
14 changed files with 3157 additions and 3175 deletions

View File

@ -79,6 +79,7 @@
!
! *** Output to MARC output file ***
!$OMP CRITICAL (write2out)
write(6,*)
write(6,*) 'CPFEM Initialization'
write(6,*)
@ -100,6 +101,7 @@
write(6,*)
call flush(6)
!$OMP END CRITICAL (write2out)
return
!
END SUBROUTINE
@ -219,7 +221,6 @@
CPFEM_stress_bar(1:CPFEM_ngens,CPFEM_in,cp_en) = CPFEM_odd_stress
CPFEM_jaco_bar(1:CPFEM_ngens,1:CPFEM_ngens,CPFEM_in,cp_en) = CPFEM_odd_jacobian*math_identity2nd(CPFEM_ngens)
CPFEM_calc_done = .false.
case (4) ! do nothing since we can recycle the former results (MARC specialty)
case (5) ! record consistent tangent at beginning of new increment
CPFEM_jaco_knownGood = CPFEM_jaco_bar

View File

@ -240,8 +240,6 @@
CPFEM_stress(1:CPFEM_ngens) = CPFEM_stress_bar(1:CPFEM_ngens,CPFEM_in,cp_en)
CPFEM_jaco(1:CPFEM_ngens,1:CPFEM_ngens) = CPFEM_jaco_bar(1:CPFEM_ngens,1:CPFEM_ngens,CPFEM_in,cp_en)
if (debugger) write (6,'(a,/,6(6(f9.3,x)/))') 'stiffness / GPa',CPFEM_jaco(1:CPFEM_ngens,:)/1e9_pReal
!
return
!
@ -266,6 +264,7 @@
! use crystallite
use constitutive
implicit none
!
integer(pInt) cp_en,CPFEM_in,g,i,e
integer(pInt) el_start, el_end, ip_start, ip_end

View File

@ -12,6 +12,7 @@
logical :: lastIncConverged = .false.,outdatedByNewInc = .false., outdatedFFN1 = .false.
logical :: symmetricSolver = .false.
CONTAINS
!***********************************************************

View File

@ -600,14 +600,13 @@
write(6,*) 'MPIE Material Routine Ver. 0.0 by the coding team'
write(6,*)
write(6,*) msg
write(6,*)
call debug_info()
call flush(6)
call quit(9000+ID)
!$OMP END CRITICAL (write2out)
! ABAQUS returns in some cases
return

View File

@ -256,6 +256,7 @@
!**************************************************************************
! matrix multiplication 3x3
!**************************************************************************
PURE FUNCTION math_mul33x33(A,B)
use prec, only: pReal, pInt
@ -272,7 +273,6 @@
END FUNCTION
!**************************************************************************
! matrix multiplication 6x6
!**************************************************************************
@ -292,6 +292,7 @@
END FUNCTION
!**************************************************************************
! matrix multiplication 6x6
!**************************************************************************
@ -312,6 +313,7 @@
END FUNCTION
!**************************************************************************
! matrix multiplication 9x9
!**************************************************************************
@ -322,8 +324,10 @@
integer(pInt) i,j
real(pReal), dimension(9,9), intent(in) :: A,B
real(pReal), dimension(9,9) :: math_mul99x99
forall (i=1:9,j=1:9) math_mul99x99(i,j) = &
A(i,1)*B(1,j) + A(i,2)*B(2,j) + A(i,3)*B(3,j) + &
A(i,4)*B(4,j) + A(i,5)*B(5,j) + A(i,6)*B(6,j) + &
@ -976,16 +980,11 @@
real(pReal) noise,scatter,cosScatter
integer(pInt) i
if (noise==0.0) then
math_sampleGaussOri = center
return
endif
! Helming uses different distribution with Bessel functions
! therefore the gauss scatter width has to be scaled differently
scatter = 0.95_pReal * noise
@ -2058,4 +2057,3 @@ math_sampleFiberOri = math_RtoEuler(math_mul33x33(pRot,math_mul33x33(fRot,oRot))
END MODULE math

View File

@ -130,16 +130,11 @@
use math, only: invnrmMandel
implicit real(pReal) (a-h,o-z)
integer(pInt) computationMode
dimension e(*),de(*),t(*),dt(*),g(*),d(ngens,*),s(*), n(2),coord(ncrd,*),disp(ndeg,*),matus(2),dispt(ndeg,*),ffn(itel,*),&
frotn(itel,*),strechn(itel),eigvn(itel,*),ffn1(itel,*),frotn1(itel,*),strechn1(itel),eigvn1(itel,*),kcus(2)
! Marc common blocks are in fixed format so they have to be pasted in here
! Beware of changes in newer Marc versions -- these are from 2005r3
! concom is needed for inc, subinc, ncycle, lovl
@ -168,7 +163,6 @@
cptim,timinc,timinc_p,timinc_s,timincm,timinc_a,timinc_b,creept(33),icptim,icfte,icfst,&
icfeq,icftm,icetem,mcreep,jcreep,icpa,icftmp,icfstr,icfqcp,icfcpm,icrppr,icrcha,icpb,iicpmt,iicpa
if (inc == 0) then
cycleCounter = 4
else
@ -196,11 +190,11 @@
computationMode = 1 ! compute and age former results
outdatedByNewInc = .false.
endif
if (computationMode == 2 .and. outdatedFFN1) then
computationMode = 4 ! return odd results to force new vyvle
endif
theTime = cptim ! record current starting time
theInc = inc ! record current increment number
theCycle = ncycle ! record current cycle count
@ -208,7 +202,6 @@
call CPFEM_general(computationMode,ffn,ffn1,t(1),timinc,n(1),nn,s,mod(cycleCounter-4,4_pInt*ijaco)==0,d,ngens)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! Marc: 11, 22, 33, 12, 23, 13
forall(i=1:ngens) d(1:ngens,i) = invnrmMandel(i)*d(1:ngens,i)*invnrmMandel(1:ngens)
@ -254,6 +247,7 @@
v=CPFEM_results(mod(jpltcd-1_pInt, CPFEM_Nresults+constitutive_maxNresults)+1_pInt,&
(jpltcd-1_pInt)/(CPFEM_Nresults+constitutive_maxNresults)+1_pInt,&
nn, mesh_FEasCP('elem', m))
return
END SUBROUTINE
!

View File

@ -130,16 +130,11 @@
use math, only: invnrmMandel
implicit real(pReal) (a-h,o-z)
integer(pInt) computationMode
dimension e(*),de(*),t(*),dt(*),g(*),d(ngens,*),s(*), n(2),coord(ncrd,*),disp(ndeg,*),matus(2),dispt(ndeg,*),ffn(itel,*),&
frotn(itel,*),strechn(itel),eigvn(itel,*),ffn1(itel,*),frotn1(itel,*),strechn1(itel),eigvn1(itel,*),kcus(2)
! Marc common blocks are in fixed format so they have to be pasted in here
! Beware of changes in newer Marc versions -- these are from 2005r3
! concom is needed for inc, subinc, ncycle, lovl
@ -168,7 +163,6 @@
cptim,timinc,timinc_p,timinc_s,timincm,timinc_a,timinc_b,creept(33),icptim,icfte,icfst,&
icfeq,icftm,icetem,mcreep,jcreep,icpa,icftmp,icfstr,icfqcp,icfcpm,icrppr,icrcha,icpb,iicpmt,iicpa
if (inc == 0) then
cycleCounter = 4
else
@ -202,7 +196,6 @@
call CPFEM_general(computationMode,ffn,ffn1,t(1),timinc,n(1),nn,s,mod(cycleCounter-4,2_pInt*ijaco)==0,d,ngens)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! Marc: 11, 22, 33, 12, 23, 13
forall(i=1:ngens) d(1:ngens,i) = invnrmMandel(i)*d(1:ngens,i)*invnrmMandel(1:ngens)

View File

@ -130,7 +130,7 @@
use math, only: invnrmMandel
!
implicit none
!
! ** Start of generated type statements **
real(pReal) coord, d, de, disp, dispt, dt, e, eigvn, eigvn1, ffn, ffn1
real(pReal) frotn, frotn1, g
@ -183,7 +183,6 @@
computationMode = 4 ! return odd results to force new vyvle
endif
theTime = cptim ! record current starting time
theInc = inc ! record current increment number
theCycle = ncycle ! record current cycle count
@ -191,7 +190,6 @@
call CPFEM_general(computationMode,ffn,ffn1,t(1),timinc,n(1),nn,s,mod(cycleCounter-4,4_pInt*ijaco)==0,d,ngens)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! Marc: 11, 22, 33, 12, 23, 13
forall(i=1:ngens) d(1:ngens,i) = invnrmMandel(i)*d(1:ngens,i)*invnrmMandel(1:ngens)

View File

@ -17,6 +17,7 @@
! profile or multifrontal sparse, the latter seems
! to be faster!)
! - in case of ddm a symmetric solver has to be used
!********************************************************************
! Marc subroutines used:
! - hypela2
@ -124,7 +125,6 @@
!2 continue
!3 continue
!
use prec, only: pReal,pInt, ijaco
use FEsolving
use CPFEM, only: CPFEM_general
@ -186,7 +186,6 @@
call CPFEM_general(computationMode,ffn,ffn1,t(1),timinc,n(1),nn,s,mod(cycleCounter-4,2_pInt*ijaco)==0,d,ngens)
! Mandel: 11, 22, 33, SQRT(2)*12, SQRT(2)*23, SQRT(2)*13
! Marc: 11, 22, 33, 12, 23, 13
forall(i=1:ngens) d(1:ngens,i) = invnrmMandel(i)*d(1:ngens,i)*invnrmMandel(1:ngens)