module MPR06_ANALYZE use MTD_STRUCT implicit none private public :: COUNTLINES, ANALYZELINES, SYSLINES integer :: I,J,K,N,er contains !--------------------------------------------------------------- function COUNTLINES(S,N) ! S : structure des transitions indexées ! N : niveau considéré type(INDEXLINES), dimension(:), intent(in) :: S integer, intent(in) :: N integer :: COUNTLINES I = count(S%Nj==N) J = count(S%Ni==N) COUNTLINES = I + J ! print*,I,J,COUNTLINES end function COUNTLINES !--------------------------------------------------------------- subroutine ANALYZELINES(S1,level,S2) ! S1 : structure des transitions indexées ! level : niveau considéré ! S2 : structures des transitions concernant le niveau type(INDEXLINES), dimension(:), intent(in) :: S1 integer, intent(in) :: level type(INDEXLINES), dimension(:), intent(out) :: S2 J = 1 !print*,size(S1), SIZE(S2) do I = 1, size(S1) if (S1(I)%Nj==level.or.S1(I)%Ni==level) then S2(J) = S1(I) J = J + 1 end if end do end subroutine ANALYZELINES !---------------------------------------------------------------- subroutine SYSLINES(S1,S2,sys,S3,Nraie) ! S1 : structure des niveaux d'énergie sélectionnés ! S2 : structure des transitions indexées ! sys : type de recherche ! S3 : structure des transitions sélectionnées type(LEVELS), dimension(:), intent(in) :: S1 type(INDEXLINES),dimension(:), intent(in) :: S2 character(len=*), intent(in) :: sys type(INDEXLINES),dimension(:),allocatable,intent(out) :: S3 integer, optional, intent(in) :: Nraie integer :: N1,N2 type(INDEXLINES),dimension(:),allocatable :: S_temp N1 = size(S1) N2 = size(S2) allocate(S_temp(N2),stat=er) if (er/=0) stop "Erreur d'allocation d'un tableau de structure." if (sys == 'SYSTEM1') then J = 1 do I = 1,N2 ! boucle sur les transitions if (S1(S2(I)%Nj)%term < 300 .and. S1(S2(I)%Ni)%term < 300) then S_temp(J) = S2(I) J = J +1 end if end do print*,'Nombre de transitions dans le système de multiplicité 1 : ', J-1 end if if (sys == 'SYSTEM3') then J = 1 do I = 1,N2 ! boucle sur les transitions if (S1(S2(I)%Nj)%term >= 300 .and. S1(S2(I)%Ni)%term >= 300) then S_temp(J) = S2(I) J = J +1 end if end do print*,'Nombre de transitions dans le système de multiplicité 3 : ', J-1 end if if (sys == 'INTER') then J = 1 do I = 1,N2 ! boucle sur les transitions if ((S1(S2(I)%Nj)%term>=300 .and. S1(S2(I)%Ni)%term<300).OR.(S1(S2(I)%Nj)%term<300 .and. S1(S2(I)%Ni)%term>=300)) then S_temp(J) = S2(I) J = J +1 end if end do print*,"Nombre de transitions dans le système d'intercombinaison : ", J-1 end if if (sys == 'ONE_LINE') then J = 1 do I = 1,N2 ! boucle sur les transitions if (I==Nraie) then S_temp(J) = S2(I) J = J +1 end if end do print*,"Nombre de transitions dans le système d'intercombinaison : ", J-1 end if allocate(S3(J-1),stat=er) if (er/=0) stop "Erreur d'allocation d'un tableau de structure." S3 = S_temp(1:J-1) end subroutine SYSLINES end module MPR06_ANALYZE