1 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2 ! Driver for stain0.f subroutine
3 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
8 Use Auxiliar_Procedures
14 !! GRID RESULTS OF STRAIN0
16 REAL, ALLOCATABLE
, DIMENSION(:,:,:) :: P_SPONT
,P_PIEZO
19 SUBROUTINE PIEZO(P_SPONT
,P_PIEZO
)
20 REAL,DIMENSION(:,:,:) :: P_SPONT
,P_PIEZO
24 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
28 ALLOCATE (P_SPONT(1:XDim
,1:YDim
,1:ZDim
),&
29 P_PIEZO(1:XDim
,1:YDim
,1:ZDim
) )
32 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
33 ! Quantum Dot Dimensions (A)
34 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
41 RD
= Rqd_Base
/RC
! RD = Rqd_Base normalized to RC
42 HD
= Hqd
/ZC
! HD = HQD normalized to ZC
44 D
=DWL
/ZC
! Wetting layer thick. normalized to ZC
46 CALL PIEZO(P_SPONT
,P_PIEZO
)
47 CALL NCPACK_PZ(P_SPONT
,P_PIEZO
)