"Par%xxxx" 修訂間的差異
出自 DDCC TCAD TOOL Manual
(已建立頁面,內容為 "The par is structure type defined in 2D-DDCC program Declear type(MODPAR) :: PAR The PAR has following variables defined by type (MODPAR) TYPE MODPAR re...") |
|||
行 1: | 行 1: | ||
− | The par is structure type defined in 2D-DDCC program |
+ | The par is structure type defined in 2D-DDCC program. It saves the regional input parameters read in by input file. |
+ | Therefore, it's value should roughly the same as the input expect some modification to the unit (Mostly converted into |
||
+ | cgs unit) |
||
+ | |||
Declear |
Declear |
||
type(MODPAR) :: PAR |
type(MODPAR) :: PAR |
||
− | The PAR has following variables defined by type (MODPAR) |
+ | The PAR has following variables defined by type (MODPAR) , I didn't list all of them |
TYPE MODPAR |
TYPE MODPAR |
||
− | real(DP), DIMENSION(:), POINTER :: impurity |
+ | real(DP), DIMENSION(:), POINTER :: impurity ! Impurity of fixed charge density |
− | real(DP), DIMENSION(:), POINTER :: xnc |
+ | real(DP), DIMENSION(:), POINTER :: xnc ! Nc |
− | real(DP), DIMENSION(:), POINTER :: xnv |
+ | real(DP), DIMENSION(:), POINTER :: xnv ! Nv of heavy hole |
− | + | real(DP), DIMENSION(:), POINTER :: xnvlh ! Nv of light hole |
|
− | real(DP), DIMENSION(:), POINTER :: |
+ | real(DP), DIMENSION(:), POINTER :: kappa ! Thermal conductivity |
− | real(DP), DIMENSION(:), POINTER :: |
+ | real(DP), DIMENSION(:), POINTER :: heatC ! Heat capacity |
− | real(DP), DIMENSION(:), POINTER :: |
+ | real(DP), DIMENSION(:), POINTER :: ni ! intrinsic carrier density |
− | real(DP), DIMENSION(:), POINTER :: |
+ | real(DP), DIMENSION(:), POINTER :: nisquare ! square of ! intrinsic carrier density |
− | real(DP), DIMENSION(:), POINTER :: |
+ | real(DP), DIMENSION(:), POINTER :: Gn |
− | real(DP), DIMENSION(:), POINTER :: Gn |
||
real(DP), DIMENSION(:), POINTER :: Gp |
real(DP), DIMENSION(:), POINTER :: Gp |
||
!real(DP), DIMENSION(:), POINTER :: expEt |
!real(DP), DIMENSION(:), POINTER :: expEt |
||
!real(DP), DIMENSION(:), POINTER :: niexpEt1 |
!real(DP), DIMENSION(:), POINTER :: niexpEt1 |
||
!real(DP), DIMENSION(:), POINTER :: niexpEt2 |
!real(DP), DIMENSION(:), POINTER :: niexpEt2 |
||
− | real(DP), DIMENSION(:,:), POINTER :: xy |
+ | real(DP), DIMENSION(:,:), POINTER :: xy ! define the region range parameters |
− | real(DP), DIMENSION(:,:,:), POINTER :: trixy |
+ | real(DP), DIMENSION(:,:,:), POINTER :: trixy ! define the triagular or special region parameters |
− | real(DP), DIMENSION(:), POINTER :: trispacing |
+ | real(DP), DIMENSION(:), POINTER :: trispacing ! periodic shape's period |
− | real(DP), DIMENSION(:), POINTER :: dope |
+ | real(DP), DIMENSION(:), POINTER :: dope ! doping density, + is for n-type doping, - is for p-type doping |
− | real(DP), DIMENSION(:), POINTER :: ea |
+ | real(DP), DIMENSION(:), POINTER :: ea ! Activation energy |
− | real(DP), DIMENSION(:), POINTER :: mun |
+ | real(DP), DIMENSION(:), POINTER :: mun ! electron mobility |
− | real(DP), DIMENSION(:), POINTER :: mup |
+ | real(DP), DIMENSION(:), POINTER :: mup ! hole mobility |
− | real(DP), DIMENSION(:), POINTER :: taun |
+ | real(DP), DIMENSION(:), POINTER :: taun ! non-radiative lifetime tau of electrons |
− | real(DP), DIMENSION(:), POINTER :: taup |
+ | real(DP), DIMENSION(:), POINTER :: taup ! non-radiative lifetime tau of holes |
− | real(DP), DIMENSION(:), POINTER :: trapNt |
+ | real(DP), DIMENSION(:), POINTER :: trapNt ! trap density |
− | real(DP), DIMENSION(:), POINTER :: trapEt |
+ | real(DP), DIMENSION(:), POINTER :: trapEt ! Position of trap energy |
− | real(DP), DIMENSION(:), POINTER :: trapdegenercy |
+ | real(DP), DIMENSION(:), POINTER :: trapdegenercy ! Trap degenercy |
− | real(DP), DIMENSION(:), POINTER :: traptaun |
+ | real(DP), DIMENSION(:), POINTER :: traptaun ! Trap taun |
− | real(DP), DIMENSION(:), POINTER :: traptaup |
+ | real(DP), DIMENSION(:), POINTER :: traptaup ! Trap taup |
− | real(DP), DIMENSION(:), POINTER :: recombine |
+ | real(DP), DIMENSION(:), POINTER :: recombine ! B coeficient for radiative remobination |
− | real(DP), DIMENSION(:), POINTER :: augerC |
+ | real(DP), DIMENSION(:), POINTER :: augerC ! Auger coefficient |
− | real(DP), DIMENSION(:), POINTER :: generation |
+ | real(DP), DIMENSION(:), POINTER :: generation ! generation rates |
+ | real(DP), DIMENSION(:), POINTER :: eg !bandgap |
||
+ | real(DP), DIMENSION(:,:), POINTER :: di ! dielectric constant Eps_r * eps_0 |
||
+ | real(DP), DIMENSION(:), POINTER :: Ecoff ! Band offset ratio |
||
+ | real(DP), DIMENSION(:,:), POINTER :: efmass ! effective mass of electron and holes |
||
+ | real(DP), DIMENSION(:,:), POINTER :: pe ! polarization charges. |
||
− | real(DP), DIMENSION(:), POINTER :: eg |
||
− | real(DP), DIMENSION(:,:), POINTER :: evprofile |
||
− | real(DP), DIMENSION(:,:,:), POINTER :: evprofileT |
||
− | real(DP), DIMENSION(:,:), POINTER :: di |
||
− | real(DP), DIMENSION(:), POINTER :: Ecoff |
||
− | real(DP), DIMENSION(:,:), POINTER :: efmass |
||
− | real(DP), DIMENSION(:,:), POINTER :: pe |
||
− | real(DP), DIMENSION(:,:), POINTER :: efmass |
||
− | real(DP), DIMENSION(:,:), POINTER :: pe |
||
− | real(DP), DIMENSION(:,:), POINTER :: alloyflucterm |
||
− | real(DP), DIMENSION(:), POINTER :: nsum,psum,radsum,generationsum,nonradsum,augersum,ndasum,Exsum,Exquenchsum,Exradsum |
||
− | real(DP) :: filestepsize |
||
− | real(DP) :: filestepsize2 |
||
real(DP) :: t ! temperature |
real(DP) :: t ! temperature |
||
− | real(DP) :: vg |
+ | real(DP) :: vg ! gate voltage |
− | real(DP) :: vgstart |
+ | real(DP) :: vgstart |
real(DP) :: vgstop |
real(DP) :: vgstop |
||
real(DP) :: vgstep |
real(DP) :: vgstep |
||
行 59: | 行 46: | ||
real(DP) :: vdfinal |
real(DP) :: vdfinal |
||
real(DP) :: vdstep |
real(DP) :: vdstep |
||
− | real(DP) :: vs |
+ | real(DP) :: vs ! source bias |
− | real(dp) :: vb |
+ | real(dp) :: vb ! base-bias |
− | real(dp) :: vref |
+ | real(dp) :: vref ! reference voltage |
− | real(DP) :: |
+ | real(DP) :: phib ! Schottky barrier of gate |
− | real(DP) :: phib |
||
− | real(DP) :: dvstart |
||
− | real(DP) :: dvstop |
||
− | real(DP) :: dvinitial |
||
real(DP) :: jd |
real(DP) :: jd |
||
real(DP) :: js |
real(DP) :: js |
||
行 77: | 行 64: | ||
real(DP) :: heatbndistance |
real(DP) :: heatbndistance |
||
real(DP) :: heatsource |
real(DP) :: heatsource |
||
− | real(DP) :: heat1 |
||
+ | |||
− | real(DP) :: heat2 |
||
− | real(DP) :: heat3 |
||
− | real(DP) :: rd |
||
− | real(DP) :: rs |
||
− | real(DP) :: Vdefshift |
||
− | real(DP) :: Vsefshift |
||
− | real(DP) :: Vgefshift |
||
− | |||
− | real(DP), DIMENSION(:), POINTER :: evfileTemperature |
||
− | |||
− | real(DP) :: tstepsize |
||
− | real(DP) :: initialtemp |
||
− | real(DP) :: constvbsource |
||
− | real(DP) :: constvbdrain |
||
− | real(DP) :: constvbbody |
||
− | real(DP) :: constvbbase |
||
− | real(DP) :: constvbvref |
||
− | real(DP) :: constvbgate |
||
− | integer(I4B) , DIMENSION(:), POINTER :: triperiodnum |
||
− | integer(I4B) , DIMENSION(:), POINTER :: triregiontype |
||
− | integer(I4B) , DIMENSION(:), POINTER :: gmshlinesurfnum ,gmshlinetype ,gmshsurfnum ,gmshsurftype ,gmshlinerecordmshline |
||
− | integer(I4B) , DIMENSION(:), POINTER :: triregiontype |
||
− | integer(I4B) , DIMENSION(:), POINTER :: gmshlinesurfnum ,gmshlinetype ,gmshsurfnum ,gmshsurftype ,gmshlinerecordmshline |
||
− | integer(I4B) , DIMENSION(:), POINTER :: alloyflucindex |
||
− | integer(I4B) :: tstepnum |
||
− | integer(I4B) :: n |
||
− | integer(I4B) :: evfilenum |
||
− | integer(I4B) :: evint |
||
− | integer(I4B) :: evint2 |
||
− | integer(I4B) :: filetype ! 1 for nonuniform, 2 for uniform |
||
− | integer(I4B) :: meshtype |
||
− | integer(I4B) :: savenum |
||
− | integer(I4B) :: ntrinum |
||
− | integer(I4B) :: gmshlineBoundaryNo , gmshsurfBoundaryNo |
||
− | character(100) :: inputmeshfile |
||
− | character(100) :: inputmeshset |
||
− | character(100) :: outfile |
||
− | character(100) :: initialfile |
||
− | character(100) :: dvfile |
||
− | character(100),DIMENSION(:),POINTER :: evfileT |
||
− | character(100) :: evfile |
||
− | character(100) :: fermitable |
||
END TYPE MODPAR |
END TYPE MODPAR |
於 2017年8月14日 (一) 20:37 的修訂
The par is structure type defined in 2D-DDCC program. It saves the regional input parameters read in by input file. Therefore, it's value should roughly the same as the input expect some modification to the unit (Mostly converted into cgs unit)
Declear type(MODPAR) :: PAR
The PAR has following variables defined by type (MODPAR) , I didn't list all of them
TYPE MODPAR
real(DP), DIMENSION(:), POINTER :: impurity ! Impurity of fixed charge density real(DP), DIMENSION(:), POINTER :: xnc ! Nc real(DP), DIMENSION(:), POINTER :: xnv ! Nv of heavy hole real(DP), DIMENSION(:), POINTER :: xnvlh ! Nv of light hole real(DP), DIMENSION(:), POINTER :: kappa ! Thermal conductivity real(DP), DIMENSION(:), POINTER :: heatC ! Heat capacity real(DP), DIMENSION(:), POINTER :: ni ! intrinsic carrier density real(DP), DIMENSION(:), POINTER :: nisquare ! square of ! intrinsic carrier density real(DP), DIMENSION(:), POINTER :: Gn real(DP), DIMENSION(:), POINTER :: Gp !real(DP), DIMENSION(:), POINTER :: expEt !real(DP), DIMENSION(:), POINTER :: niexpEt1 !real(DP), DIMENSION(:), POINTER :: niexpEt2 real(DP), DIMENSION(:,:), POINTER :: xy ! define the region range parameters real(DP), DIMENSION(:,:,:), POINTER :: trixy ! define the triagular or special region parameters real(DP), DIMENSION(:), POINTER :: trispacing ! periodic shape's period real(DP), DIMENSION(:), POINTER :: dope ! doping density, + is for n-type doping, - is for p-type doping real(DP), DIMENSION(:), POINTER :: ea ! Activation energy real(DP), DIMENSION(:), POINTER :: mun ! electron mobility real(DP), DIMENSION(:), POINTER :: mup ! hole mobility real(DP), DIMENSION(:), POINTER :: taun ! non-radiative lifetime tau of electrons real(DP), DIMENSION(:), POINTER :: taup ! non-radiative lifetime tau of holes real(DP), DIMENSION(:), POINTER :: trapNt ! trap density real(DP), DIMENSION(:), POINTER :: trapEt ! Position of trap energy real(DP), DIMENSION(:), POINTER :: trapdegenercy ! Trap degenercy real(DP), DIMENSION(:), POINTER :: traptaun ! Trap taun real(DP), DIMENSION(:), POINTER :: traptaup ! Trap taup real(DP), DIMENSION(:), POINTER :: recombine ! B coeficient for radiative remobination real(DP), DIMENSION(:), POINTER :: augerC ! Auger coefficient real(DP), DIMENSION(:), POINTER :: generation ! generation rates real(DP), DIMENSION(:), POINTER :: eg !bandgap real(DP), DIMENSION(:,:), POINTER :: di ! dielectric constant Eps_r * eps_0 real(DP), DIMENSION(:), POINTER :: Ecoff ! Band offset ratio real(DP), DIMENSION(:,:), POINTER :: efmass ! effective mass of electron and holes real(DP), DIMENSION(:,:), POINTER :: pe ! polarization charges.
real(DP) :: t ! temperature real(DP) :: vg ! gate voltage real(DP) :: vgstart real(DP) :: vgstop real(DP) :: vgstep real(DP) :: vd real(DP) :: vdfinal real(DP) :: vdstep real(DP) :: vs ! source bias real(dp) :: vb ! base-bias real(dp) :: vref ! reference voltage real(DP) :: phib ! Schottky barrier of gate real(DP) :: jd real(DP) :: js real(DP) :: jg real(DP) :: jb real(DP) :: jvbase real(DP) :: jvref real(DP) :: jpb real(DP) :: jpd real(DP) :: jps real(DP) :: jpg real(DP) :: jpvbase real(DP) :: jpvref real(DP) :: heatbndistance real(DP) :: heatsource END TYPE MODPAR