Changeset 3006


Ignore:
Timestamp:
Jul 21, 2023, 11:47:04 AM (16 months ago)
Author:
emillour
Message:

Mars PCM:
More code cleanup. Turn "nirdata.h" common into module "nirdata.F90" and
include "nir_leedat.F" (reading/loading of the data) in the module.
Also turn nirco2abs.F in a module.
EM

Location:
trunk/LMDZ.MARS
Files:
1 deleted
3 edited
1 moved

Legend:

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

    r3004 r3006  
    41114111specifically output for Grads in 1D).
    41124112Also turned lwi and lwflux into modules while at it.
     4113
     4114== 21/07/2023 == EM
     4115More code cleanup. Turn "nirdata.h" common into module "nirdata.F90" and
     4116include "nir_leedat.F" (reading/loading of the data) in the module.
     4117Also turn nirco2abs.F in a module.
  • trunk/LMDZ.MARS/libf/phymars/nirco2abs.F

    r2616 r3006  
     1      MODULE nirco2abs_mod
     2     
     3      IMPLICIT NONE
     4     
     5      CONTAINS
     6     
    17      SUBROUTINE nirco2abs(ngrid,nlayer,pplay,dist_sol,nq,pq,
    28     $     mu0,fract,declin,pdtnirco2)
     
    612       USE comcstfi_h, ONLY: pi
    713       USE time_phylmdz_mod, ONLY: daysec
     14       use nirdata_mod, only: npres, alfa, corgcm, oco21d, pres1d
    815       IMPLICIT NONE
    916c=======================================================================
     
    4956c
    5057      include "callkeys.h"
    51       include "nirdata.h"
    5258
    5359c-----------------------------------------------------------------------
     
    237243      END IF
    238244
    239       end
     245      END SUBROUTINE nirco2abs
    240246
    241247
     
    247253C escout(nlayer) on pressure grid p(nlayer).
    248254C
    249       real escout(nlayer),p(nlayer)
    250       real escin(nl),pin(nl),wm,wp
    251       integer nl,nlayer,n1,n,nm,np
     255      real,intent(out) :: escout(nlayer)
     256      real,intent(in) :: p(nlayer)
     257      integer,intent(in) :: nlayer
     258      real,intent(in) :: escin(nl)
     259      real,intent(in) :: pin(nl)
     260      integer,intent(in) :: nl
     261     
     262      real :: wm,wp
     263      integer :: n1,n,nm,np
     264     
    252265      do n1=1,nlayer
    253266         if(p(n1) .gt. 1500. .or. p(n1) .lt. 1.0e-13) then
     
    265278         endif
    266279      enddo
    267       end
     280     
     281      end subroutine interpnir
     282
     283      END MODULE nirco2abs_mod
  • trunk/LMDZ.MARS/libf/phymars/nirdata.F90

    r3004 r3006  
     1module nirdata_mod
    12
    2       integer npres                ! Number of pressures in NIR correction
    3       parameter (npres=42)         ! table
     3implicit none
    44
    5       common /NIRdata/ pres1d,corgcm,oco21d,alfa,p1999
    6 !$OMP THREADPRIVATE(/NIRdata/)
    7       real    pres1d(npres)
    8       real    corgcm(npres)
    9       real    oco21d(npres),alfa(npres),p1999(npres)
     5! Number of pressures in NIR correction table
     6integer,parameter :: npres=42   
     7
     8real,save,protected :: pres1d(npres)
     9real,save,protected :: corgcm(npres)
     10real,save,protected :: oco21d(npres)
     11real,save,protected :: alfa(npres)
     12real,save,protected :: p1999(npres)
     13!$OMP THREADPRIVATE(pres1d,corgcm,oco21d,alfa,p1999)
     14
     15contains
     16
     17  subroutine NIR_leedat
     18
     19!       reads parameters for NIR NLTE calculation   
     20
     21!       nov 2011    fgg+malv    first version               
     22!***********************************************************************
     23
     24    use datafile_mod, only: datadir
     25    USE mod_phys_lmdz_para, ONLY: is_master
     26    USE mod_phys_lmdz_transfert_para, ONLY: bcast
     27
     28    implicit none
     29
     30! local variables                               
     31
     32    integer :: ind
     33
     34    if (is_master) then
     35      open(43,file=trim(datadir)//'/NIRcorrection_feb2011.dat', &
     36             status='old')
     37      do ind=1,9
     38        read(43,*)
     39      enddo
     40     
     41      do ind=1,npres
     42         read(43,*)pres1d(ind),corgcm(ind),oco21d(ind),p1999(ind), &
     43              alfa(ind)
     44         !Tabulated pression to Pa
     45         pres1d(ind)=pres1d(ind)*100.
     46      enddo
     47      close(43)
     48
     49    endif !  if(is_master) then
     50
     51    call bcast(pres1d)
     52    call bcast(corgcm)
     53    call bcast(oco21d)
     54    call bcast(p1999)
     55    call bcast(alfa)
     56
     57  end subroutine NIR_leedat
     58
     59end module nirdata_mod
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3004 r3006  
    5656      use comsaison_h, only: dist_sol, declin, zls,
    5757     &                       mu0, fract, local_time
     58      use nirdata_mod, only: NIR_leedat
     59      use nirco2abs_mod, only: nirco2abs
    5860      use slope_mod, only: theta_sl, psi_sl
    5961      use conc_mod, only: rnew, cpnew, mmean
     
    109111     &                        major_slope,compute_meshgridavg,
    110112     &                        ini_comslope_h
    111       USE ioipsl_getincom, only: getin
    112113      use write_output_mod, only: write_output
    113114      IMPLICIT NONE
Note: See TracChangeset for help on using the changeset viewer.