Program Convert_Linelist ! ! Convert linelists from atomic database format to spectrum synthetis format ! ! Compile with: pathf95 -o CONVERT_LINELIST -C Convert_Linelist.f90 ! Execute with: ./CONVERT_LINELIST input_linelist.dat ! ! History : ! 2010 10 26 TM creation ! 2010 11 16 TM Add Carina_UVES option to generate Linelist file for all the orders ! 2011 04 20 TM Add configuration namelists and modules ! 2011 05 15 TM Add criteria for MULTI: E_low and E_up must be lower than ionization ! energy given in the ABSDAT file of MULTI (for continuous opacity) ! 2013 06 05 TM Add of ion_min_rm and ion_max_rm criteria for removing different ionization ! stages of a same element (e.g. FeI and FeII) ! 2013 06 11 TM Add of the output option FORMATO to generate linelist of one atom ! USE UVES_ORDERS USE CONFIG USE VALD_FMT USE KALD_FMT USE MOOG_FMT USE MULTI_FMT USE FORMATO_FMT ! Implicit None ! ! PROGRAM PARAMETERS ! Character(len = 512) :: finp, fout, fnul Character(len = 256) :: line = '' Integer :: N = 0 ! Number of input lines Integer :: M = 0 ! Number of selected lines Integer :: M1 = 0 ! Number of selected lines if one_elt_only = .TRUE. Integer :: M2 = 0 ! Number of selected lines if one_elt_only = .FALSE. Integer, dimension(8) :: Itime Logical :: end_fin = .FALSE. ! Call Get_command_argument(1, finp) ! Call Date_and_time(values = Itime) ! Call INQU_FINPUT() Call INQU_CONFIG() Call READ_CONFIG() ! fout = Trim(fout_name) // '.dat' fnul = Trim(fout_name) // '.nul' ! Open(unit = 10, file = finp, status = 'old', position = 'rewind', iostat = ios) If(ios /= 0) STOP "PROGRAM CONVERT_LINELIST: PB-00" Open(unit = 20, file = fout, status = 'replace', iostat = ios) If(ios /= 0) STOP "PROGRAM CONVERT_LINELIST: PB-01" Open(unit = 30, file = fnul, status = 'replace', iostat = ios) If(ios /= 0) STOP "PROGRAM CONVERT_LINELIST: PB-02" ! Write(20, '(A, A," (",I0,2("-",I0),")",/)') Trim(fout_info)," -llc- TM", Itime(1), Itime(2), Itime(3) Write(30, '(A, A," (",I0,2("-",I0),")")') Trim(fnul_info)," -llc- TM", Itime(1), Itime(2), Itime(3) ! Write(*, *) Write(*, *) "Input database: ", Trim(finp_fmt) ! Do ! If (finp_fmt == 'VALD' .AND. fout_fmt == 'MOOG') Then Call READ_VALD(line, end_fin, N) IF (end_fin) EXIT Call WRITE_MOOG_FMT(line, M1, M2) Else If (finp_fmt == 'KALD' .AND. fout_fmt == 'MOOG') Then Call READ_KALD_FIX(line, end_fin, N) IF (end_fin) EXIT Call WRITE_MOOG_FMT(line, M1, M2) ! Work in progress Else If (finp_fmt == 'VALD' .AND. .NOT. short_fmt .AND. fout_fmt == 'MULTI' ) Then Call READ_VALD(line, end_fin, N) IF (end_fin) EXIT Call WRITE_MULTI_FMT(line, M1, M2) Else If (finp_fmt == 'KALD' .AND. fout_fmt == 'MULTI') Then Call READ_KALD_FIX(line, end_fin, N) If (end_fin) EXIT Call WRITE_MULTI_FMT(line, M1, M2) Else If (finp_fmt == 'KALD' .AND. fout_fmt == 'FORMATO') Then Call READ_KALD_FIX(line, end_fin, N) If (end_fin) EXIT Call WRITE_FORMATO_FMT(line, M1, M2) Else If (finp_fmt == 'VALD' .AND. fout_fmt == 'FORMATO') Then Call READ_VALD(line, end_fin, N) If (end_fin) EXIT Call WRITE_FORMATO_FMT(line, M1, M2) Else STOP "PROGRAM CONVERT_LINELIST: PB-03: CONFIGURATION NOT AVAILABLE." End If ! End Do ! Close(10) Close(20) Close(30) ! !--------------------------------------------------------------------- ! !If (finp_fmt == 'VALD' .AND. fout_fmt == 'MOOG') Then ! ! ! !If (UVES) CALL UVES_SPEC() !Else ! STOP "PROGRAM CONVERT_LINELIST: PB-10" !End If ! !--------------------------------------------------------------------- ! If (one_elt_only) Then M = M1 Else M = M2 End If ! Write(*, *) Write(*, *) "Lines read: ", N Write(*, *) "Lines selected: ", M Write(*, *) "Lines rejected: ", N-M Write(*, *) Write(*, *) "Output format: ", Trim(fout_fmt) Write(*, *) ! CONTAINS ! Subroutine INQU_FINPUT() Do Inquire(file = finp, exist = boo) If (boo) EXIT Write(*, '(A)') "Give a (correct) input file name in the current directory." Write(*, '(A)', advance = 'no') "Filename: " Read(*, '(A)') finp End Do End Subroutine INQU_FINPUT ! End Program Convert_Linelist