Skip to content

Commit

Permalink
v 1.7.3
Browse files Browse the repository at this point in the history
  • Loading branch information
shahramyalameha committed May 12, 2022
1 parent 823bdc7 commit 4991d27
Show file tree
Hide file tree
Showing 11 changed files with 1,205 additions and 839 deletions.
22 changes: 22 additions & 0 deletions soc/Eatools_bulk.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
!```````````````````````````````````````````````````````````````````````````````````````````````
! Copyright (c) 2018-2022 Shahram Yalameha <[email protected]> , <[email protected]>, `
! Please report bugs or suggestions to: [email protected] `
! `
!```````````````````````````````````````````````````````````````````````````````````````````````
! SUBROUTINE: fOR 3D MATERIAL, the core of the bulk Modulus method II calculation..

SUBROUTINE bulk_method(Pratio, sheainvar, bulk_m2)

DOUBLE PRECISION :: Pratio, sheainvar, bulk_m2




bulk_m2 = ( 2.d0 * sheainvar * (1.d0 + Pratio) ) / (3.0d0 * (1.0d0 - 2.0d0 * Pratio))






END SUBROUTINE bulk_method
1,899 changes: 1,088 additions & 811 deletions soc/Eatools_main.f90

Large diffs are not rendered by default.

10 changes: 5 additions & 5 deletions soc/Eatools_poi.f90
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@

SUBROUTINE CPratio(a1111,MinPratio,MaxPratio,AvePratio,&
vec1min,vec2min,vec3min,vec1max,vec2max,vec3max,&
theta,phi,k11,k12,k13,k22,k23,k33,Pratio)
theta,phi,k11,k12,k13,k22,k23,k33,Pratio)

DOUBLE PRECISION, PARAMETER :: pi=3.1415926535897932384626433832795d0
DOUBLE PRECISION, DIMENSION(6,6) :: S=0D0
Expand Down Expand Up @@ -72,19 +72,19 @@ SUBROUTINE CPratio(a1111,MinPratio,MaxPratio,AvePratio,&
+ k33*v33*S(3,3)


a1122 =a1122 &
a1122 =a1122 &
+(k11*v23+k23*v11)*S(1,4) &
+(k11*v13+k13*v11)*S(1,5) &
+(k11*v12+k12*v11)*S(1,6) &
+(k22*v23+k23*v22)*S(2,4) &
+(k22*v23+k23*v22)*S(2,4) &
+(k22*v13+k13*v22)*S(2,5) &
+(k22*v12+k12*v22)*S(2,6) &
+(k33*v23+k23*v33)*S(3,4) &
+(k33*v23+k23*v33)*S(3,4) &
+(k33*v13+k13*v33)*S(3,5) &
+(k33*v12+k12*v33)*S(3,6)+k23*v23*S(4,4) &
+(k23*v13+k13*v23)*S(4,5) &
+(k23*v12+k12*v23)*S(4,6)+k13*v13*S(5,5) &
+(k13*v12+k12*v13)*S(5,6)+k12*v12*S(6,6)
+(k13*v12+k12*v13)*S(5,6)+k12*v12*S(6,6)
Pratio = -a1122/a1111
IF (kk.EQ.0) THEN
MaxPratio=Pratio; MinPratio=Pratio;
Expand Down
2 changes: 1 addition & 1 deletion soc/Eatools_sh.f90
Original file line number Diff line number Diff line change
Expand Up @@ -65,7 +65,7 @@ SUBROUTINE CShear(Minsheainvar,Maxsheainvar,sheainvar_ave,phi,theta,k11,k12,k13,
!Maxsheainvar=Maxsheainvar*100D0
ENDIF
IF (sheainvar.LE.Minsheainvar)THEN
Minsheainvar = (sheainvar)
Minsheainvar = sheainvar
ENDIF
ENDIF
ave=ave+sheainvar
Expand Down
8 changes: 4 additions & 4 deletions soc/Eatools_welc.f90
Original file line number Diff line number Diff line change
Expand Up @@ -19,10 +19,10 @@ SUBROUTINE WELCOME()
WRITE(*,'(a)')" 45 6C 41 74 6F 6F 6C 73 "
WRITE(*,*)' Author : Shahram Yalameha '
WRITE(*,*)' Email : [email protected] '
WRITE(*,'(a)')' v1.7.2 '
WRITE(*,'(a)')' v1.7.3 '
WRITE(*,'(a)')' From '
WRITE(*,'(a)')' Elastic Tools Project '
WRITE(*,'(a)')'========= (c)2018 ==========='
WRITE(*,'(a)')'========= (c)2018-2022 =========='
WRITE(*,*)' '

!!!!
Expand All @@ -39,10 +39,10 @@ SUBROUTINE WELCOME()
WRITE(99,'(a)')" 45 6C 41 74 6F 6F 6C 73 "
WRITE(99,*)' Author : Shahram Yalameha '
WRITE(99,*)' Email : [email protected] '
WRITE(99,'(a)')' v1.7.2 '
WRITE(99,'(a)')' v1.7.3 '
WRITE(99,'(a)')' From '
WRITE(99,'(a)')' Elastic Tools Project '
WRITE(99,'(a)')'========= (c)2018 ==========='
WRITE(99,'(a)')'========= (c)2018-2022 =========='
WRITE(99,*)' '
WRITE(99,*)' '

Expand Down
18 changes: 9 additions & 9 deletions soc/Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -13,20 +13,20 @@

#---------------- compiler -----------------

#FC = ifort
FC = gfortran
FC = ifort
# FC = gfortran
#------------- compiler options ------------

#FOPT = -O1 -FR -mp1 -w -prec_div -pc80 -pad -ip -DINTEL_VML -traceback -assume buffered_io -I$(MKLROOT)/include # for ifort
#FGEN = -O1 -FR -mp1 -w -prec_div -pc80 -pad -ip -DINTEL_VML -traceback # for ifort
FOPT = -O1 -FR -mp1 -w -prec_div -pc80 -pad -ip -DINTEL_VML -traceback -assume buffered_io -I$(MKLROOT)/include # for ifort
FGEN = -O1 -FR -mp1 -w -prec_div -pc80 -pad -ip -DINTEL_VML -traceback # for ifort

FOPT = -ffree-form -O2 -ffree-line-length-none # for gfortran
FGEN = -ffree-form -O2 -ffree-line-length-none # for gfortran
# FOPT = -ffree-form -O2 -ffree-line-length-none # for gfortran
# FGEN = -ffree-form -O2 -ffree-line-length-none # for gfortran

#-------------- loader options -------------

LDFLAGS = $(FOPT) -lblas -llapack -lpthread # for gfortran
#LDFLAGS = $(FOPT) -L$(MKLROOT)/lib/$(MKL_TARGET_ARCH) -pthread -lmkl_lapack95_lp64 -lmkl_intel_lp64 -lmkl_intel_thread -lmkl_core -qopenmp -lpthread # for ifort
# LDFLAGS = $(FOPT) -lblas -llapack -lpthread # for gfortran
LDFLAGS = $(FOPT) -L$(MKLROOT)/lib/$(MKL_TARGET_ARCH) -pthread -lmkl_lapack95_lp64 -lmkl_intel_lp64 -lmkl_intel_thread -lmkl_core -qopenmp -lpthread # for ifort



Expand Down Expand Up @@ -57,7 +57,7 @@ OBJS = Eatools_main.o Eatools_2Dyoung.o Eatools_2Dpoisson.o Eatools_2Dshear.o
Eatools_3dPLcom.o Eatools_stability.o Eatools_db.o Eatools_3dPLsh.o Eatools_ang2car.o Eatools_dsyec3.o \
Eatools_dutester.o Eatools_proelast.o Eatools_sh.o Eatools_welc.o Eatools_pugh.o Eatools_3dPLpugh.o Eatools_hardness.o \
Eatools_km.o Eatools_wave_start.o Eatools_wave_vgvf.o Eatools_wave_rot.o Eatools_wave_cal.o Eatools_wave_main.o Eatools_2dcal_wave.o \
Eatools_pro_wave.o Eatools_2Dadv.o Eatools_api.o Eatools_3dslic.o
Eatools_pro_wave.o Eatools_2Dadv.o Eatools_api.o Eatools_3dslic.o Eatools_bulk.o help.o
OBJS1 = wrl_calylm.o wrl_colorsign.o wrl_end.o wrl_main.o \
wrl_mesh.o wrl_shape.o wrl_spherappear.o wrl_spher.o wrl_start.o wrl_setcolor.o

Expand Down
35 changes: 35 additions & 0 deletions soc/help.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,35 @@
SUBROUTINE help_me()
write(*,"(A)")"----------------------------------------------------------------------------------------------------------------------------------------"
write(*,"(A)")" ## Command-line Options: ##"
write(*,"(A)")"----------------------------------------------------------------------------------------------------------------------------------------"
write(*,"(A)")"Elatools.x -d [Integer] -m [Integer/String] -ewp [String] -ktc [String] -op [String]"
write(*,"(A)")" | | | | | "
write(*,"(A)")" | | | | ^ "
write(*,"(A)")" | | | | Type of 2D system "
write(*,"(A)")" | | | | 2D: def => Default option| adv => Advanced option"
write(*,"(A)")" | | | ^ "
write(*,"(A)")" | | | Calculate Min. thermal conductivity "
write(*,"(A)")" | | | 3D: y => Yes| n => No "
write(*,"(A)")" | | ^ "
write(*,"(A)")" | | Calculate elastic wave properties "
write(*,"(A)")" | | 3D: y => Yes| n => No "
write(*,"(A)")" | ^ "
write(*,"(A)")" | Output code "
write(*,"(A)")" | 3D: 1 => IRelast| 2 => Elast| 3 => AELAS| 4 => ElaStic| 5 => Cij file| 6 => offline Databank| 7 => online Databank "
write(*,"(A)")" | 2D: 1 => AELAS | 2 => IRelast2D| 3 => Cij-2D file "
write(*,"(A)")" ^"
write(*,"(A)")" System Type "
write(*,"(A)")" 3 => 3D sys. and 2 => 2D sys."
write(*,"(A)")""
write(*,"(A)")"----------------------------------------------------------------------------------------------------------------------------------------"

write(*,"(A)")" > Example for 3D system:"
write(*,"(A)")" Elatools.x -d 3 -m 5"
write(*,"(A)")" Elatools.x -d 3 -m 3 -ewp y"
write(*,"(A)")" Elatools.x -d 3 -m 1 -ewp y -ktc y"
write(*,"(A)")""
write(*,"(A)")" > Example for 2D system:"
write(*,"(A)")" Elatools.x -d 2 -m 2 -op def"
write(*,"(A)")" Elatools.x -d 2 -m 3 -op adv"

END SUBROUTINE
6 changes: 3 additions & 3 deletions soc/html_elayout.f90
Original file line number Diff line number Diff line change
Expand Up @@ -90,11 +90,11 @@ SUBROUTINE buttone_polar_web(max_value)
ChARACTER(len=30) :: title
ChARACTER(len=10) :: namepro
DOUBLE PRECISION :: max_value
if (namepro == "poi2d" ) title="Poisson\'s ratio"
if (namepro == "poi2d" .or. namepro == "2dpoi" ) title="Poisson\'s ratio"
if (namepro == "pugh2d" ) title="Pugh\'s ratio"
if (namepro == "young2d") title="Young\'s modulus"
if (namepro == "young2d" .or. namepro == "2dyoung") title="Young\'s modulus"
if (namepro == "bulk2d") title="Bulk modulus"
if (namepro == "shear2d") title="Shear modulus"
if (namepro == "shear2d" .or. namepro == "2dshear") title="Shear modulus"
if (namepro == "com2d" ) title="Linear compressibility"
if (namepro == "hard2d" ) title="Hardness"
if (namepro == "pp2d" ) title="P-mode of Phase velocity"
Expand Down
36 changes: 34 additions & 2 deletions soc/html_gerdata_polar.f90
Original file line number Diff line number Diff line change
Expand Up @@ -17,13 +17,44 @@ SUBROUTINE get_dataplotly_polar( namepro,rtheta, n_phif,n_thetaf,cutmesh,type_pr
VVP_i_x, VVP_P_y, VVP_SF_z,VVP_SS_k,&
VVG_i_x, VVG_P_y, VVG_SF_z,VVG_SS_k,&
VVF_i_x, VVF_P_y, VVF_SF_z,VVF_SS_k,&
km_x, km_y
km_x, km_y ,temp_x, temp_y

INTEGER, DIMENSION(190300,4) :: mesh=0
INTEGER :: n_phif, n_thetaf,cutmesh ,num_mesh,i,ii,argl,k,&
INTEGER :: n_phif, n_thetaf,cutmesh ,num_mesh,i,ii,argl,k,io,tem_i,&
start_new_reng,end_new_reng,rtheta
character(len=10) :: val='',namepro ,type_pro ! type_pro : max, min, neg


IF (namepro=="2dpoi" .OR. namepro=="2dshear" .OR. namepro=="2dyoung" .OR. namepro=="2dyou" .OR. namepro=="2dshe") THEN
tem_i=0
OPEN(12, file="young_2d_sys.dat")
DO
tem_i=tem_i + 1
READ(12,*, iostat = io ) temp_x, temp_y
if (io < 0) exit
ENDDO
Close(12)
!---------------------------------------------------
IF (namepro=="2dyoung") THEN
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! loop-READer
DO ii=1,tem_i+1
open(10, file="young_2d_sys.dat")
READ(10,*) young_x(ii),young_y(ii)
ENDDO
CLOSE(10)
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! end loop
If(type_pro=='max') THEN
If(rtheta==1) THEN
DO i=1,tem_i+1
WRITE(66,"(F23.15,A)") young_x(i),","
ENDDO
endif
Endif
ENDIF
!===========================================

ENDIF

!=============================================READ mesh
OPEN(69, file="MESH")
READ(69,*)n_phif,n_thetaf,cutmesh
Expand Down Expand Up @@ -517,4 +548,5 @@ SUBROUTINE get_dataplotly_polar( namepro,rtheta, n_phif,n_thetaf,cutmesh,type_pr
endif
Endif
ENDIF
!$============================================================================================
end SUBROUTINE
6 changes: 3 additions & 3 deletions soc/html_swin.f90
Original file line number Diff line number Diff line change
Expand Up @@ -27,12 +27,12 @@ SUBROUTINE swin_web(namepro)
if (namepro=="gs" )WRITE(66,"(3a)")"</style><title> Spatial dependence of Group-Slow velocity </title>"
if (namepro=="km" )WRITE(66,"(3a)")"</style><title> Spatial dependence of of Min. thermal conductivity </title>"
!---------------------------------------------
if (namepro=="young2d")WRITE(66,"(3a)")"</style><title> Orientation dependence of Young's modulus </title>"
if (namepro=="young2d" .or. namepro=="2dyoung")WRITE(66,"(3a)")"</style><title> Orientation dependence of Young's modulus </title>"
if (namepro=="bulk2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Bulk modulus </title>"
if (namepro=="pugh2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Pugh's ratio </title>"
if (namepro=="shear2d")WRITE(66,"(3a)")"</style><title> Orientation dependence of Shear modulus </title>"
if (namepro=="shear2d" .or. namepro=="2dshear")WRITE(66,"(3a)")"</style><title> Orientation dependence of Shear modulus </title>"
if (namepro=="com2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of linear compressibility </title>"
if (namepro=="poi2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Poisson's ratio </title>"
if (namepro=="poi2d" .or. namepro=="2dpoi" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Poisson's ratio </title>"
if (namepro=="hard2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Hardness </title>"
if (namepro=="pp2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Phase-P velocity </title>"
if (namepro=="ps2d" )WRITE(66,"(3a)")"</style><title> Orientation dependence of Phase-Fast velocity </title>"
Expand Down
2 changes: 1 addition & 1 deletion soc/wrl_main.f90
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ PROGRAM wrl_conv

DOUBLE PRECISION, DIMENSION(1910000) :: datapoints=0d0
DOUBLE PRECISION, DIMENSION(1910000) :: G_max,shminp,shminn,shavep,SINver,CO,comminp,pugh_max,pughminp,pughminn,pughavep,&
comminn,NPratio_max,pminp,pminn,pavep,paven,&
comminn,NPratio_max,pminp,pminn,pavep,paven,&
BINver,maxEVaLM1,maxEVaTM1,minEVaTM1,VVG_P,VVP_P,VV_P_PF,VVG_Sf,VVP_Sf,VV_Sf_PF,hardvar ,&
VVG_Ss,VVP_Ss,VV_Ss_PF,km
ChARACTER(len=7), dimension(10) :: arg_mane
Expand Down

0 comments on commit 4991d27

Please sign in to comment.