! PERFORM THE FREE-FLIGHT AND SCATTER PART WITHIN ONE TIME INTERVAL subroutine free_flight_scatterVar() ! common &/ran_var/iso &/scatt_par/emax,de,w(10,3),tau_max(3),max_scatt_mech(3) &/time_1/dt,dtau,tot_time ! &/variables/p(20000,7),ip(20000),energy(20000) &/particle_atr/kx,ky,kz,iv,e &/frequency/freq(10,3) use particles use scattering use simulation integer valley,i,j real ( kind = 8 ), dimension(DIM) :: Temp_wvk, Temp_pos ! carrier position and wave vector k integer :: Temp_valley,Temp_use, Temp_ScatMech, CountValley, Temp_nTBin, Temp_nAlBin, nBinComb !, Temp_valley_f 0709 real ( kind = 8 ) :: Temp_ene, Temp_tau real ( kind = 8 ):: timeFreeFlight1,timeFreeFlight2,timeDrift,timeNewFlight, dt_remain, err1 ! Reset counter for scattering frequency do i = 1,num_ScatMech do j = 1,num_Valley ScatMechFreq(i,j) = 0. enddo enddo do i = 1, num_maxCarriers ! num_Carriers ! loop for all carriers if (Par_use(i).eq.1) then ! Inverse mapping of particle atributes do j = 1,DIM !col_len = RCutoff_SiIn Temp_wvk(j) = Par_wvk(i,j) Temp_pos(j) = Par_pos(i,j) enddo Temp_tau = Par_tau(i) Temp_valley = Par_valley(i) Temp_ene = Par_ene(i) Temp_use = Par_use(i) Temp_nAlBin = Par_Al(i) timeFreeFlight1 = Temp_tau ! Initial free-flight of the carriers if(timeFreeFlight1.ge.time_step)then timeDrift = time_step else timeDrift = timeFreeFlight1 endif call drift(timeDrift,Temp_wvk,Temp_pos,Temp_ene,Temp_valley,Temp_nAlBin,Temp_use) ! Add 08/2013 for Al Content if(Temp_use.eq.0) goto 413 if(timeFreeFlight1.gt.time_step) goto 411 ! Free-flight and scatter part 412 timeFreeFlight2=timeFreeFlight1 Temp_nTBin = num_Bins do j = 1,num_Bins ! if ((Temp_pos(1).ge.(loc_bin(j)-0.5*BinSize)).and.(Temp_pos(1).lt.(loc_bin(j)+0.5*BinSize))) then Temp_nTBin = j endif enddo nBinComb = CombBin(Temp_nAlBin,Temp_nTBin) ! if ((Temp_ene.le.MaxE_eV).and.(Temp_ene.gt.0)) then else err1 = 1 ! for debugging endif CountValley = Temp_valley call TempVar_scatter_carrier(nBinComb,Temp_nAlBin,Temp_wvk,Temp_ene,Temp_valley,Temp_ScatMech) if (Temp_ScatMech.ne.0) then ! phonon counting 0709 TempVar_BinScatCount(Temp_nTBin,Temp_ScatMech,CountValley) = TempVar_BinScatCount(Temp_nTBin,Temp_ScatMech,CountValley) + 1 ! Phonon Simulation 11/2012 AllScatCount(Temp_ScatMech,CountValley) = AllScatCount(Temp_ScatMech,CountValley) + 1 BinScatCount(Temp_nTBin,Temp_ScatMech,CountValley) = BinScatCount(Temp_nTBin,Temp_ScatMech,CountValley) + 1 endif 229 call random_number(harvest = RandomNum) if(RandomNum.le.1e-6) goto 229 timeNewFlight=-(log(RandomNum))*TempVar_tau_max(nBinComb,Temp_valley) dt_remain = time_step - timeFreeFlight2 ! remaining time to scatter in dt-interval if(timeNewFlight.le.dt_remain)then timeDrift = timeNewFlight else timeDrift = dt_remain endif ! if ((Temp_ene.le.MaxE_eV).and.(Temp_ene.gt.0)) then else err1 = 1 ! for debugging endif call drift(timeDrift,Temp_wvk,Temp_pos,Temp_ene,Temp_valley,Temp_nAlBin,Temp_use) ! Add 08/2013 for Al Content if(Temp_use.eq.0) goto 413 ! if not use... timeFreeFlight2 = timeFreeFlight2 + timeNewFlight ! Update times timeFreeFlight1 = timeFreeFlight2 if(timeFreeFlight1.lt.time_step) goto 412 411 timeFreeFlight1 = timeFreeFlight1 - time_step Temp_tau = timeFreeFlight1 do j = 1,DIM !col_len = RCutoff_SiIn ! Map particle atributes Par_wvk(i,j) = Temp_wvk(j) Par_pos(i,j) = Temp_pos(j) enddo Par_tau(i) = Temp_tau Par_valley(i) = Temp_valley Par_Al(i) = Temp_nAlBin Par_ene(i) = Temp_ene ! if ((Par_ene(i).le.MaxE_eV).and.(Par_ene(i).gt.0)) then else err1 = 1 ! for debugging endif 413 Par_use(i) = Temp_use endif enddo return end