Changeset 3942 for trunk/LMDZ.GENERIC


Ignore:
Timestamp:
Oct 29, 2025, 11:20:13 PM (8 weeks ago)
Author:
mturbet
Message:

remove startype options from ave_stelspec routine

Location:
trunk/LMDZ.GENERIC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.GENERIC/changelog.txt

    r3937 r3942  
    21172117Fix some initializations issues in start2archive: call conf_gcm() instead of
    21182118defrun_new() to ensure some defaults (like "timestart") are correctly set.
     2119
     2120== 29/10/2025 == MT
     2121Clean the ave_stelspec routine to remove the startype options
     2122Now stellar spectra should be specified with stelspec_file and t_stellar options in callphys.def
     2123Stellar spectra repository now updated in https://web.lmd.jussieu.fr/~lmdz/planets/generic/datagcm/stellar_spectra/
  • trunk/LMDZ.GENERIC/libf/phystd/ave_stelspec.F90

    r3893 r3942  
    1212!     Robin Wordsworth (2010).
    1313!     Generalized to very late spectral types (and Brown dwarfs) Jeremy Leconte (2012)
     14!     Modified to account for any stellar spectrum file (Lucas Teinturier and Martin Turbet, 2023-2025)
    1415!
    1516!     Called by
     
    2627      use radcommon_h, only: BWNV, DWNV, tstellar
    2728      use datafile_mod, only: datadir
    28       use callkeys_mod, only: stelbbody,stelTbb,startype
     29      use callkeys_mod, only: stelbbody,stelTbb
    2930      use ioipsl_getin_p_mod, only: getin_p
    3031
     
    3233
    3334      real*8 STELLAR(L_NSPECTV)
    34 !      integer startype
    3535
    3636      integer Nfine
     
    6868         end do
    6969         STELLAR(1:L_NSPECTV)=STELLAR(1:L_NSPECTV)/sum(STELLAR(1:L_NSPECTV))
    70       else
     70      else !stelbbody
     71         ! look for a " tstellar= ..." option in def files
     72         tstellar = -1. ! default
     73         call getin_p("tstellar",tstellar) ! default path
     74         if (tstellar.eq.-1.) then
     75           write(*,*)'Beware that startype is now deprecated, you should use '
     76           write(*,*)'stelspec_file and tstellar to define the input stellar spectrum.'
     77           write(*,*)'     '
     78           write(*,*)'Error: tstellar (effective stellar temperature) needs to be specified'
     79           write(*,*)'in callphys.def: tstellar=...'
     80           call abort_physic("ave_stelspec", "tstellar needs to be specified",1)
     81         end if
     82         
     83         write(*,*) "Input stellar temperature is:"
     84         write(*,*) "tstellar = ",tstellar
     85
    7186         ! load high resolution stellar data
    72          Select Case(startype)
    73            Case(1)
    74             file_id='/stellar_spectra/sol.txt'
    75             tstellar=5800.
    76             file_id_lam='/stellar_spectra/lam.txt'
    77             Nfine=5000
    78            Case(2)
    79             file_id='/stellar_spectra/gl581.txt'
    80             tstellar=3200.
    81             file_id_lam='/stellar_spectra/lam.txt'
    82             Nfine=5000
    83            Case(3)
    84             file_id='/stellar_spectra/adleo.txt'
    85             tstellar=3200.
    86             file_id_lam='/stellar_spectra/lam.txt'
    87             Nfine=5000
    88            Case(4)
    89             file_id='/stellar_spectra/gj644.txt'
    90             call abort_physic("GJ644", "Tstellar unknown", 1)
    91             file_id_lam='/stellar_spectra/lam.txt'
    92             Nfine=5000
    93            Case(5)
    94             file_id='/stellar_spectra/Wasp43_flux.txt'
    95             tstellar=4520.
    96             file_id_lam='/stellar_spectra/Wasp43_lambda.txt'
    97             Nfine=395562
    98            Case(6)
    99             file_id='/stellar_spectra/BD_Teff-1600K.txt'
    100             tstellar=1600.
    101             file_id_lam='/stellar_spectra/lamBD.txt'
    102             Nfine=5000
    103            Case(7)
    104             file_id='/stellar_spectra/BD_Teff-1000K.txt'
    105             tstellar=1000.
    106             file_id_lam='/stellar_spectra/lamBD.txt'
    107             Nfine=5000
    108            Case(8)
    109             file_id='/stellar_spectra/Flux_K5_Teff4700_logg4.5_Met-0.5_BTsettle.dat'
    110             tstellar=4700.
    111             file_id_lam='/stellar_spectra/lambda_K5_Teff4700_logg4.5_Met-0.5_BTsettle.dat'
    112             Nfine=3986
    113            Case(9)
    114             file_id='/stellar_spectra/Flux_TRAPPIST1.dat'
    115             tstellar=2550.
    116             file_id_lam='/stellar_spectra/lambda_TRAPPIST1.dat'
    117             Nfine=5000
    118            Case(10)
    119             file_id='/stellar_spectra/Flux_Proxima.dat'
    120             tstellar=3050.
    121             file_id_lam='/stellar_spectra/lambda_Proxima.dat'
    122             Nfine=5000
    123            Case(11)
    124             ! look for a " stelspec_file= ..." option in def files
    125             write(*,*) "Input stellar spectra files for radiative transfer is:"
    126             stelspec_file = "sun.txt" ! default
    127             call getin_p("stelspec_file",stelspec_file) ! default path
    128             write(*,*) " stelspec_file = ",trim(stelspec_file)
    129             write(*,*) 'Please use ',1,' and only ',1,' header line in ',trim(stelspec_file)
    130             ! look for a " tstellar= ..." option in def files
    131             write(*,*) "Input stellar temperature is:"
    132             tstellar = -1. ! default
    133             call getin_p("tstellar",tstellar) ! default path
    134             write(*,*) " tstellar = ",tstellar
    135             if (tstellar.eq.-1.) then
    136               write(*,*)'Error: with startype 11 tstellar need to be specified'
    137               write(*,*)'  Specified in callphys.def tstellar=...'
    138               call abort_physic("ave_stelspec", "startype 11 tstellar needs to be specified",1)
    139             end if
     87         ! look for a " stelspec_file= ..." option in def files
     88         stelspec_file = "None" ! default
     89         call getin_p("stelspec_file",stelspec_file) ! default path
     90         
     91         write(*,*) "Input stellar spectrum file is:"
     92         write(*,*) "stelspec_file = ",trim(stelspec_file)
     93         write(*,*) 'Please use ',1,' and only ',1,' header line in ',trim(stelspec_file)
     94
     95         ! Opening file
     96         file_path = trim(datadir)//'/stellar_spectra/'//stelspec_file
     97         print*, 'stellar flux : ', file_path
     98         OPEN(UNIT=110,FILE=file_path,STATUS='old',iostat=ios)
    14099   
    141             ! Opening file
    142             file_path = trim(datadir)//'/stellar_spectra/'//stelspec_file
    143             print*, 'stellar flux : ', file_path
    144             OPEN(UNIT=110,FILE=file_path,STATUS='old',iostat=ios)
    145    
    146             if (ios /= 0) THEN
    147               write(*,*)'Error: cannot open stelspec_file file ', trim(stelspec_file)
    148               write(*,*)'It should be in :',trim(datadir),'/stellar_spectra/'
    149               write(*,*)'1) You can change the data directory in callphys.def'
    150               write(*,*)'   with:'
    151               write(*,*)'   datadir=/path/to/the/directory'
    152               write(*,*)'2) You can change the input stelspec_file file name in'
    153               write(*,*)'   callphys.def with:'
    154               write(*,*)'   stelspec_file=filename'
    155               call abort_physic("ave_stelspec", "Unable to read stellar flux file", 1)
    156             end if
     100         if (ios /= 0) THEN
     101           write(*,*)'Beware that startype is now deprecated, you should use '
     102           write(*,*)'stelspec_file and tstellar to define the input stellar spectrum.'
     103           write(*,*)'     '
     104           write(*,*)'Error: cannot open stelspec_file file ', trim(stelspec_file)
     105           write(*,*)'It should be in :',trim(datadir),'/stellar_spectra/'
     106           write(*,*)'1) You can change the data directory in callphys.def'
     107           write(*,*)'   with:'
     108           write(*,*)'   datadir=/path/to/the/directory'
     109           write(*,*)'2) You can change the input stelspec_file file name in'
     110           write(*,*)'   callphys.def with:'
     111           write(*,*)'   stelspec_file=filename'
     112           write(*,*)'You can check the online repository to search for '
     113           write(*,*)'available stellar spectra here : '
     114           write(*,*)'https://web.lmd.jussieu.fr/~lmdz/planets/generic/datagcm/stellar_spectra/'
     115           call abort_physic("ave_stelspec", "Unable to read stellar flux file", 1)
     116         end if
    157117
    158             ! Get number of line in the file
    159             READ(110,*) ! skip header
    160             Nfine = 0
    161             do
    162               read(110,*,iostat=ios)
    163               if (ios<0) exit
    164               Nfine = Nfine + 1
    165             end do
    166             rewind(110) ! Rewind file after counting lines
    167             READ(110,*) ! skip header
    168            Case Default
    169             call abort_physic("ave_stelspec", "Unknown star type chosen", 1)
    170          End Select
     118         ! Get number of line in the file
     119         READ(110,*) ! skip first line header just in case
     120         Nfine = 0
     121         do
     122           read(110,*,iostat=ios)
     123           if (ios<0) exit
     124           Nfine = Nfine + 1
     125         end do
     126         rewind(110) ! Rewind file after counting lines
     127         READ(110,*) ! skip first line header just in case
    171128
    172129!$OMP MASTER
    173130         allocate(lam(Nfine),stel_f(Nfine))
    174131
    175       if (startype.eq.11) then
    176132         do ifine=1,Nfine
    177133           read(110,*) lam(ifine), stel_f(ifine) ! lam [um] stel_f [per unit of wavelength] (integrated and normalized by Fat1AU)
    178134         enddo
    179          close(110)
    180       else
    181          file_path_lam=TRIM(datadir)//TRIM(file_id_lam)
    182          open(110,file=file_path_lam,form='formatted',status='old',iostat=ios)
    183          if (ios.ne.0) then        ! file not found
    184            write(*,*) 'Error from ave_stelspec'
    185            write(*,*) 'Data file ',trim(file_id_lam),' not found.'
    186            write(*,*)'Check that your path to datagcm:',trim(datadir)
    187            write(*,*)' is correct. You can change it in callphys.def with:'
    188            write(*,*)' datadir = /absolute/path/to/datagcm'
    189            write(*,*)' Also check that there is a ',trim(file_id_lam),' there.'
    190            call abort_physic("ave_stelspec", "Unable to find file", 1)
    191          else
    192            do ifine=1,Nfine
    193              read(110,*) lam(ifine)
    194            enddo
    195            close(110)
    196          endif
    197135
    198 
    199          ! load high resolution wavenumber data
    200          file_path=TRIM(datadir)//TRIM(file_id)
    201          open(111,file=file_path,form='formatted',status='old',iostat=ios)
    202          if (ios.ne.0) then        ! file not found
    203            write(*,*) 'Error from ave_stelspec'
    204            write(*,*) 'Data file ',trim(file_id),' not found.'
    205            write(*,*)'Check that your path to datagcm:',trim(datadir)
    206            write(*,*)' is correct. You can change it in callphys.def with:'
    207            write(*,*)' datadir = /absolute/path/to/datagcm'
    208            write(*,*)' Also check that there is a ',trim(file_id),' there.'
    209            call abort_physic("ave_stelspec", "Unable to find file", 1)
    210          else
    211            do ifine=1,Nfine
    212              read(111,*) stel_f(ifine)
    213            enddo
    214            close(111)
    215          endif
    216       end if
    217136!$OMP END MASTER
    218137!$OMP BARRIER
     
    243162!$OMP END MASTER
    244163!$OMP BARRIER         
    245       endif
     164      endif !stelbbody
    246165
    247166      end subroutine ave_stelspec
  • trunk/LMDZ.GENERIC/libf/phystd/callkeys_mod.F90

    r3922 r3942  
    101101      integer,save :: iaervar
    102102      integer,save :: iradia
    103       integer,save :: startype
    104103      integer,save :: versH2H2cia
    105104      character(64),save :: H2orthopara_mixture
    106105      integer,save :: nlayaero
    107 !$OMP THREADPRIVATE(iddist,iaervar,iradia,startype,versH2H2cia,H2orthopara_mixture,nlayaero)
     106!$OMP THREADPRIVATE(iddist,iaervar,iradia,versH2H2cia,H2orthopara_mixture,nlayaero)
    108107      integer,dimension(:),allocatable,save :: aeronlay_choice
    109108!$OMP THREADPRIVATE(aeronlay_choice)
  • trunk/LMDZ.GENERIC/libf/phystd/inifis_mod.F90

    r3930 r3942  
    684684     if (is_master) write(*,*)trim(rname)//": tplanet = ",tplanet
    685685
    686      if (is_master) write(*,*)trim(rname)//": Which star?"
    687      startype=1 ! default value = Sol
    688      call getin_p("startype",startype)
    689      if (is_master) write(*,*)trim(rname)//": startype = ",startype
    690 
    691686     if (is_master) write(*,*)trim(rname)//": Value of stellar flux at 1 AU?"
    692687     Fat1AU=1356.0 ! default value = Sol today
Note: See TracChangeset for help on using the changeset viewer.