Changeset 2443 for trunk


Ignore:
Timestamp:
Jan 15, 2021, 5:41:46 PM (4 years ago)
Author:
abierjon
Message:

Mars GCM:
Changes in aeroptical.F90 :

  • add the flag nf90_64bit_offset when creating the output file. Without it, the program couldn't deal with large files (concat) with multiple aerosols
  • modify the code structure to make it a bit less memory-intensive
  • add topdust in computed aerosol opacities
  • add the possibility to compute absorption opacities, instead of extinction : the user must specify 'ext' or 'abs' in aeroptical.def
  • update the description of aeroptical in util/README

+ adapt simu_MCS to take into account aeroptical output variables when choosing

the binning reference

+ add outputs for topdust in physiq_mod

AB

Location:
trunk/LMDZ.MARS
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/README

    r2440 r2443  
    32523252with Solar longitude as the Time variable (for localtime, the check on long_name
    32533253attribute is still compliant with files from previous versions)
     3254
     3255== 15/01/2021 == AB
     3256Changes in aeroptical.F90 :
     3257- add the flag nf90_64bit_offset when creating the output file. Without it, the
     3258  program couldn't deal with large files (concat) with multiple aerosols
     3259- modify the code structure to make it a bit less memory-intensive
     3260- add topdust in computed aerosol opacities
     3261- add the possibility to compute absorption opacities, instead of extinction :
     3262  the user must specify 'ext' or 'abs' in aeroptical.def
     3263- update the description of aeroptical in util/README
     3264
     3265+ adapt simu_MCS to take into account aeroptical output variables when choosing
     3266  the binning reference
     3267+ add outputs for topdust in physiq_mod
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r2442 r2443  
    31673167
    31683168           if (rdstorm) then  ! writediagfi tendencies stormdust tracers
    3169              call WRITEDIAGFI(ngrid,'reffdust','reffdust',
    3170      &                        'm',3,rdust*ref_r0)
    31713169             call WRITEDIAGFI(ngrid,'reffstormdust','reffstormdust',
    31723170     &                        'm',3,rstormdust*ref_r0)
     
    32263224
    32273225           if (slpwind) then
     3226             call WRITEDIAGFI(ngrid,'refftopdust','refftopdust',
     3227     &                        'm',3,rtopdust*ref_r0)
     3228             call WRITEDIAGFI(ngrid,'topdustq','top Dust mass mr',
     3229     &                        'kg/kg',3,pq(:,:,igcm_topdust_mass))
     3230             call WRITEDIAGFI(ngrid,'topdustN','top Dust number',
     3231     &                        'part/kg',3,pq(:,:,igcm_topdust_number))
    32283232             select case (trim(dustiropacity))
    32293233              case ("tes")
  • trunk/LMDZ.MARS/util/README

    r2435 r2443  
    191191--------------------------------------------------------------------
    192192
    193 Program to compute opacities [1/km] of all aerosols from dust, water ice
    194 and stormdust present in the input file, at a wavelength given by the user.
     193Program to compute opacities [1/km] of all aerosols from dust, water ice,
     194stormdust and topdust present in the input file, at a wavelength given by the user.
    195195Computation is made from the aerosol mass mixing ratios and effective radius,
    196196associated with air density (rho) and files containing the aerosol
    197197optical properties (generally present in the GCM datadir/ directory).
     198The user have to precise the type of opacity : extinction or absorption.
    198199
    199200NB : water ice effective radius is known to be a bit inaccurate in the GCM,
     
    202203input : diagfi.nc  / concat.nc / stats.nc kind of files
    203204
    204 output file is : name_of_input_file_OPA.nc
     205output file is :
     206 name_of_input_file_OPAext.nc for extinction opacities
     207 name_of_input_file_OPAabs.nc for absorption opacities
     208
    205209aeroptical.e < aeroptical.def
  • trunk/LMDZ.MARS/util/aeroptical.F90

    r2435 r2443  
    88! This program takes as inputs a GCM output file (diagfi,stats,concat) that
    99! contains:
    10 !      - the Mass Mixing Ratios of dust (dustq), water ice (h2o_ice)
    11 !                                 & stormdust (rdsdustq)
    12 !      - their effective radius (reffdust, reffice(*), reffstormdust)
     10!      - the Mass Mixing Ratios of dust (dustq), water ice (h2o_ice),
     11!                               stormdust (rdsdustq) & topdust (topdustq)
     12!      - their effective radius (reffdust, reffice(*),
     13!                           reffstormdust, refftopdust)
    1314!      - the atmospheric density (rho)
    1415! as well as a wavelength to calibrate the opacities, and the directory
     
    1718! It outputs a netcdf file containing the opacities [1/km] of the dust,
    1819! water ice and stormdust aerosols calibrated at the prescribed wavelength.
    19 !
     20! The type of opacity (extinction or absorption) is given by the user.
    2021!
    2122! (*) due to a high uncertainty of reffice in the GCM, the value is asked
     
    4647integer :: ierr                               ! [netcdf] subroutine returned error code
    4748character(len=256) :: error_text              ! text to display in case of error
    48 integer :: tmpvarid                           ! temporarily stores a variable ID number
    4949integer :: lonlen,latlen,altlen,timelen       ! nb of grid points along longitude,latitude,altitude,time
    5050integer :: GCM_layers                         ! number of GCM layers
     
    5252
    5353logical,dimension(:),allocatable :: aerok     ! to know if the needed fields are in the GCM file
    54 real,dimension(:,:,:,:,:),allocatable :: mmr  ! aerosols mass mixing ratios [kg/kg]
    55 real,dimension(:,:,:,:,:),allocatable :: reff ! aerosols effective radii [m]
     54integer,dimension(:),allocatable :: mmrvarid  ! stores a MMR variable ID number
     55integer,dimension(:),allocatable :: reffvarid ! stores a reff variable ID number
     56integer :: tmpvarid                           ! temporarily stores a variable ID number
     57real,dimension(:,:,:,:),allocatable :: mmr    ! aerosols mass mixing ratios [kg/kg]
     58real,dimension(:,:,:,:),allocatable :: reff   ! aerosols effective radii [m]
    5659real :: reffwice_val                          ! value given by the user for reffwice (0 if read in the GCM file) [m]
    5760real,dimension(:,:,:,:),allocatable :: rho    ! atmospheric density [kg.m-3]
    5861integer :: naerkind                           ! nb of aerosols to consider
    59 integer :: iaer                               ! aerosol kind index (1=dust, 2=water ice, 3=stormdust) ! + NEW AER?
     62integer :: iaer                               ! aerosol kind index (1=dust,2=water ice,3=stormdust,4=topdust) ! + NEW AER?
    6063integer :: ilon,ilat,ialt,it                  ! Loop indices for coordinates
    6164
    6265
    6366! Output file
    64 character(len=128) :: outfile                    ! name of the netcdf output file
    65 integer :: outfid                                ! [netcdf] file ID number
     67character(len=128) :: outfile                  ! name of the netcdf output file
     68integer :: outfid                              ! [netcdf] file ID number
    6669integer :: latdimout,londimout,altdimout,timedimout
    67                                                  ! latdimout: stores latitude dimension ID number
    68                                                  ! londimout: stores longitude dimension ID number
    69                                                  ! altdimout: stores altitude dimension ID number
    70                                                  ! timedimout: stores time dimension ID number
    71 integer :: tmpvaridout                           ! temporarily stores a variable ID number
    72 
    73 real :: wvl_val                                  ! reference wavelength of the output opacities (given by the user) [m]
    74 integer :: varshape(4)                           ! stores a variable shape (of dimensions' IDs)
    75 character(len=16) :: tmpvarname                  ! temporarily stores a variable name
    76 real,dimension(:,:,:,:,:),allocatable :: opa_aer ! Aerosols opacities [1/km]
    77 real,dimension(:),allocatable :: missval         ! Value to put in outfile when the reff is out of bounds
    78                                                  ! or when there is a mising value in input file
     70                                               ! latdimout: stores latitude dimension ID number
     71                                               ! londimout: stores longitude dimension ID number
     72                                               ! altdimout: stores altitude dimension ID number
     73                                               ! timedimout: stores time dimension ID number
     74integer :: tmpvaridout                         ! temporarily stores a variable ID number
     75
     76real :: wvl_val                                ! reference wavelength of the output opacities (given by the user) [m]
     77character(len=3) :: opatype                    ! opacity type : extinction (ext) or absorption (abs) (given by the user)
     78integer :: varshape(4)                         ! stores a variable shape (of dimensions' IDs)
     79character(len=16) :: tmpvarname                ! temporarily stores a variable name
     80real,dimension(:,:,:,:),allocatable :: opa_aer ! Aerosols opacities [1/km]
     81real,dimension(:),allocatable :: missval       ! Value to put in outfile when the reff is out of bounds
     82                                               ! or when there is a mising value in input file
    7983
    8084
     
    8387character(len=128) :: optpropfile          ! name of the ASCII optical properties file
    8488logical :: file_ok                         ! to know if the file can be opened
    85 integer :: file_unit = 60                  !
     89integer :: file_unit = 60                  ! ASCII file ID
    8690
    8791integer :: jfile                           ! ASCII file scan index
     
    96100real,dimension(:),allocatable :: radiusdyn ! Particle size axis [m]
    97101real,dimension(:,:),allocatable :: Qext    ! Extinction efficiency coefficient [/]
     102real,dimension(:,:),allocatable :: omeg    ! Single scattering albedo [/]
    98103
    99104
     
    103108real,dimension(2) :: reffQext            ! Qext after reff interpolation
    104109real :: Qext_val                         ! Qext after both interpolations
     110real,dimension(2) :: reffomeg            ! omeg after reff interpolation
     111real :: omeg_val                         ! omeg after both interpolations
    105112real,dimension(:),allocatable :: rho_aer ! Density of the aerosols [kg.m-3]
    106113
     
    132139READ(*,'(a)') datadir
    133140
     141! Ask the type of opacity that has to be computed
     142write(*,*)""
     143WRITE(*,*) "Do you want to compute extinction or absorption opacities ? (ext/abs)"
     144READ(*,*) opatype
     145if ((trim(opatype).ne."ext").and.(trim(opatype).ne."abs")) then
     146  write(*,*) "opatype = "//opatype
     147  write(*,*) "Error: the opacity type must be ext or abs"
     148  stop
     149endif
     150
    134151!===============================================================================
    135152! 1. GCM FILE & OUTPUT FILE INITIALIZATIONS
     
    149166!==========================================================================
    150167! --> 1.1.2 Creation of the outfile
    151 outfile=gcmfile(1:index(gcmfile, ".nc")-1)//"_OPA.nc"
    152 
    153 ierr=NF90_CREATE(outfile,nf90_clobber,outfid) ! NB: clobber mode=overwrite any dataset with the same file name !
     168if (opatype.eq."ext") then
     169  outfile=gcmfile(1:index(gcmfile, ".nc")-1)//"_OPAext.nc"
     170else ! opatype.eq."abs"
     171  outfile=gcmfile(1:index(gcmfile, ".nc")-1)//"_OPAabs.nc"
     172endif
     173
     174 
     175ierr=NF90_CREATE(outfile,IOR(nf90_clobber,nf90_64bit_offset),outfid)
     176! NB: clobber mode=overwrite any dataset with the same file name !
     177! 64bit_offset enables the creation of large netcdf files with variables>2GB
    154178error_text="Error: could not create file "//trim(outfile)
    155179call status_check(ierr,error_text)
     
    171195
    172196!==========================================================================
    173 ! 1.2 GCM file variables
     197! 1.2 GCM aerosols
    174198!==========================================================================
    175199
    176200! Number of aerosols
    177 naerkind = 3 ! dust, water ice, stormdust ! + NEW AER?
    178 
    179 ! Length allocation of the variables
    180 allocate(mmr(naerkind,lonlen,latlen,altlen,timelen))
    181 allocate(reff(naerkind,lonlen,latlen,altlen,timelen))
     201naerkind = 4 ! dust, water ice, stormdust, topdust ! + NEW AER?
     202
     203! Variables length allocation
     204allocate(mmrvarid(naerkind))
     205allocate(reffvarid(naerkind))
    182206
    183207! Initialize missing value
     
    194218! DUST MASS MIXING RATIO
    195219! Check that the GCM file contains that variable
    196 ierr=nf90_inq_varid(gcmfid,"dustq",tmpvarid)
     220ierr=nf90_inq_varid(gcmfid,"dustq",mmrvarid(1))
    197221error_text="Failed to find variable dustq in "//trim(gcmfile)&
    198222            //" We'll skip the dust aerosol."
    199223if (ierr.ne.nf90_noerr) then
    200224  write(*,*)trim(error_text)
    201   aerok(1)=.false.
    202 else
    203   ! Load datasets
    204   ierr=NF90_GET_VAR(gcmfid,tmpvarid,mmr(1,:,:,:,:))
    205   error_text="Failed to load dust mass mixing ratio"
    206   call status_check(ierr,error_text)
    207   write(*,*) "Dust mass mixing ratio loaded from "//trim(gcmfile)
    208   ! Get missing value
    209   ierr=nf90_get_att(gcmfid,tmpvarid,"missing_value",missval(1))
    210   if (ierr.ne.nf90_noerr) then
    211     missval(1) = 1.e+20
    212   endif
     225  aerok(1)=.false.
    213226endif
    214227
     
    216229if (aerok(1)) then
    217230  ! Check that the GCM file contains that variable
    218   ierr=nf90_inq_varid(gcmfid,"reffdust",tmpvarid)
     231  ierr=nf90_inq_varid(gcmfid,"reffdust",reffvarid(1))
    219232  error_text="Failed to find variable reffdust in "//trim(gcmfile)&
    220233              //" We'll skip the dust aerosol."
     
    222235    write(*,*)trim(error_text)
    223236    aerok(1)=.false.
    224   else
    225     ! Load datasets
    226     ierr=NF90_GET_VAR(gcmfid,tmpvarid,reff(1,:,:,:,:))
    227     error_text="Failed to load dust effective radius"
    228     call status_check(ierr,error_text)
    229     write(*,*) "Dust effective radius loaded from "//trim(gcmfile)
    230237  endif
    231238endif
     
    236243! WATER ICE MASS MIXING RATIO
    237244! Check that the GCM file contains that variable
    238 ierr=nf90_inq_varid(gcmfid,"h2o_ice",tmpvarid)
     245ierr=nf90_inq_varid(gcmfid,"h2o_ice",mmrvarid(2))
    239246error_text="Failed to find variable h2o_ice in "//trim(gcmfile)&
    240247            //" We'll skip the water ice aerosol."
     
    242249  write(*,*)trim(error_text)
    243250  aerok(2)=.false.
    244 else
    245   ! Load datasets
    246   ierr=NF90_GET_VAR(gcmfid,tmpvarid,mmr(2,:,:,:,:))
    247   error_text="Failed to load water ice mass mixing ratio"
    248   call status_check(ierr,error_text)
    249   write(*,*) "Water ice mass mixing ratio loaded from "//trim(gcmfile)
    250   ! Get missing value
    251   ierr=nf90_get_att(gcmfid,tmpvarid,"missing_value",missval(2))
    252   if (ierr.ne.nf90_noerr) then
    253     missval(2) = 1.e+20
    254   endif
    255251endif
    256252
     
    259255  IF (reffwice_val.eq.0) THEN
    260256    ! Check that the GCM file contains that variable
    261     ierr=nf90_inq_varid(gcmfid,"reffice",tmpvarid)
     257    ierr=nf90_inq_varid(gcmfid,"reffice",reffvarid(2))
    262258    error_text="Failed to find variable reffice in "//trim(gcmfile)&
    263259                //" We'll skip the water ice aerosol."
     
    265261      write(*,*)trim(error_text)
    266262      aerok(2)=.false.
    267     else
    268       ! Load datasets
    269       ierr=NF90_GET_VAR(gcmfid,tmpvarid,reff(2,:,:,1,:)) ! reffice is actually a GCM
    270                                                          ! surface (column-averaged) variable
    271       error_text="Failed to load water ice effective radius"
    272       call status_check(ierr,error_text)
    273       do ialt=2,altlen
    274         reff(2,:,:,ialt,:) = reff(2,:,:,1,:) ! build up along altitude axis
    275       enddo
    276       write(*,*) "Water ice effective radius loaded from "//trim(gcmfile)
    277263    endif
    278   ELSE ! if reffwice_val/=0
    279     reff(2,:,:,:,:) = reffwice_val
    280     write(*,*) "Water ice effective radius loaded from the user input"
    281264  ENDIF
    282265endif
    283 
    284 ! Check if there is still at least one aerosol to compute
    285 IF (.NOT.ANY(aerok)) THEN
    286   write(*,*) "Neither dust nor water ice are found in the file. Better stop now..."
    287   stop
    288 ENDIF
    289266
    290267!==========================================================================
     
    293270! STORMDUST MASS MIXING RATIO
    294271! Check that the GCM file contains that variable
    295 ierr=nf90_inq_varid(gcmfid,"rdsdustq",tmpvarid)
     272ierr=nf90_inq_varid(gcmfid,"rdsdustq",mmrvarid(3))
    296273error_text="Failed to find variable rdsdustq in "//trim(gcmfile)&
    297274            //" We'll skip the stormdust aerosol."
     
    299276  write(*,*)trim(error_text)
    300277  aerok(3)=.false.
    301 else
    302   ! Load datasets
    303   ierr=NF90_GET_VAR(gcmfid,tmpvarid,mmr(3,:,:,:,:))
    304   error_text="Failed to load stormdust mass mixing ratio"
    305   call status_check(ierr,error_text)
    306   write(*,*) "Stormdust mass mixing ratio loaded from "//trim(gcmfile)
    307   ! Get missing value
    308   ierr=nf90_get_att(gcmfid,tmpvarid,"missing_value",missval(3))
    309   if (ierr.ne.nf90_noerr) then
    310     missval(3) = 1.e+20
    311   endif
    312278endif
    313279
     
    315281if (aerok(3)) then
    316282  ! Check that the GCM file contains that variable
    317   ierr=nf90_inq_varid(gcmfid,"reffstormdust",tmpvarid)
     283  ierr=nf90_inq_varid(gcmfid,"reffstormdust",reffvarid(3))
    318284  error_text="Failed to find variable reffstormdust in "//trim(gcmfile)&
    319               //" We'll skip the dust aerosol."
     285              //" We'll skip the stormdust aerosol."
    320286  if (ierr.ne.nf90_noerr) then
    321287    write(*,*)trim(error_text)
    322288    aerok(3)=.false.
    323   else
    324     ! Load datasets
    325     ierr=NF90_GET_VAR(gcmfid,tmpvarid,reff(3,:,:,:,:))
    326     error_text="Failed to load stormdust effective radius"
    327     call status_check(ierr,error_text)
    328     write(*,*) "Stormdust effective radius loaded from "//trim(gcmfile)
    329289  endif
    330290endif
    331291
    332 
    333 !==========================================================================
    334 ! --> 1.2.4 + NEW AER?
    335 
    336 
    337 !==========================================================================
    338 ! --> 1.2.5 ATMOSPHERIC DENSITY
     292!==========================================================================
     293! --> 1.2.4 TOPDUST
     294
     295! TOPDUST MASS MIXING RATIO
     296! Check that the GCM file contains that variable
     297ierr=nf90_inq_varid(gcmfid,"topdustq",mmrvarid(4))
     298error_text="Failed to find variable topdustq in "//trim(gcmfile)&
     299            //" We'll skip the topdust aerosol."
     300if (ierr.ne.nf90_noerr) then
     301  write(*,*)trim(error_text)
     302  aerok(4)=.false.
     303endif
     304
     305! TOPDUST EFFECTIVE RADIUS
     306if (aerok(4)) then
     307  ! Check that the GCM file contains that variable
     308  ierr=nf90_inq_varid(gcmfid,"refftopdust",reffvarid(4))
     309  error_text="Failed to find variable refftopdust in "//trim(gcmfile)&
     310              //" We'll skip the topdust aerosol."
     311  if (ierr.ne.nf90_noerr) then
     312    write(*,*)trim(error_text)
     313    aerok(4)=.false.
     314  endif
     315endif
     316
     317!==========================================================================
     318! --> 1.2.5 + NEW AER?
     319
     320
     321! Check if there is still at least one aerosol to compute
     322IF (.NOT.ANY(aerok)) THEN ! + NEW AER?
     323  write(*,*) "No aerosol among [dust/water ice/stormdust/topdust] was found in the file. Better stop now..."
     324  stop
     325ENDIF
     326
     327!==========================================================================
     328! 1.3 GCM ATMOSPHERIC DENSITY
     329!==========================================================================
    339330
    340331! Check that the GCM file contains that variable
     
    345336! Length allocation for each dimension of the 4D variable
    346337allocate(rho(lonlen,latlen,altlen,timelen))
    347 ! Load datasets
     338! Load dataset
    348339ierr=nf90_get_var(gcmfid,tmpvarid,rho)
    349340error_text="Failed to load atmospheric density"
    350341call status_check(ierr,error_text)
    351 write(*,*) "Loaded atmospheric density rho from "//trim(gcmfile)
    352 
    353 !==========================================================================
    354 ! 1.3 Some output variable's initializations
     342write(*,*) "Atmospheric density rho loaded from "//trim(gcmfile)
     343
     344
     345!==========================================================================
     346! 1.4 Output variable's initializations and datasets loading
    355347!==========================================================================
    356348! Define the ID shape of the output variables
     
    365357rho_aer(2)=920.  ! water ice
    366358rho_aer(3)=2500. ! stormdust
     359rho_aer(4)=2500. ! topdust
    367360! + NEW AER?
    368361
    369 allocate(opa_aer(naerkind,lonlen,latlen,altlen,timelen))
    370 
    371 
     362DO iaer = 1, naerkind ! Loop on aerosol kind
     363  if (aerok(iaer)) then ! check if this aerosol can be computed
     364    write(*,*)""
     365    SELECT CASE(iaer)
     366    CASE(1) ! DUST
     367      write(*,*)"Computing dust opacity..."
     368    CASE(2) ! WATER ICE
     369      write(*,*)"Computing water ice opacity..."
     370    CASE(3) ! STORMDUST
     371      write(*,*)"Computing stormdust opacity..."
     372    CASE(4) ! TOPDUST
     373      write(*,*)"Computing topdust opacity..."
     374! + NEW AER?
     375    END SELECT ! iaer
     376   
     377    ! Length allocation of the input variables
     378    ALLOCATE(mmr(lonlen,latlen,altlen,timelen))
     379    ALLOCATE(reff(lonlen,latlen,altlen,timelen))
     380   
     381    ! Datasets loading
     382     ! MMR
     383    ierr=NF90_GET_VAR(gcmfid,mmrvarid(iaer),mmr(:,:,:,:))
     384    error_text="Failed to load mass mixing ratio"
     385    call status_check(ierr,error_text)
     386    write(*,*) "Mass mixing ratio loaded from "//trim(gcmfile)
     387    ! Get missing value
     388    ierr=nf90_get_att(gcmfid,mmrvarid(1),"missing_value",missval(1))
     389    if (ierr.ne.nf90_noerr) then
     390      missval(1) = 1.e+20
     391    endif
     392   
     393     ! REFF
     394    if (iaer.ne.2) then
     395      ! Load dataset
     396      ierr=NF90_GET_VAR(gcmfid,reffvarid(iaer),reff(:,:,:,:))
     397      error_text="Failed to load effective radius"
     398      call status_check(ierr,error_text)
     399      write(*,*) "Effective radius loaded from "//trim(gcmfile)
     400   
     401    else ! water ice special case
     402      IF (reffwice_val.eq.0) THEN
     403        ! Load dataset
     404        ierr=NF90_GET_VAR(gcmfid,reffvarid(iaer),reff(:,:,1,:)) ! reffice is actually a GCM
     405                                                              ! surface (column-averaged) variable
     406        error_text="Failed to load effective radius"
     407        call status_check(ierr,error_text)
     408        do ialt=2,altlen
     409          reff(:,:,ialt,:) = reff(:,:,1,:) ! build up along altitude axis
     410        enddo
     411        write(*,*) "Effective radius loaded from "//trim(gcmfile)
     412      ELSE ! if reffwice_val/=0
     413        reff(:,:,:,:) = reffwice_val
     414        write(*,*) "Effective radius loaded from the user input"
     415      ENDIF
     416     
     417    endif ! iaer.ne.2
     418   
     419 
     420    ! Length allocation of the output variable
     421    ALLOCATE(opa_aer(lonlen,latlen,altlen,timelen))
     422   
     423 
    372424!===============================================================================
    373425! 2. OPTICAL PROPERTIES
    374426!===============================================================================
    375 
    376 DO iaer = 1, naerkind ! Loop on aerosol kind
    377   if (aerok(iaer)) then ! check if this aerosol can be computed
    378 
    379427!==========================================================================
    380428! 2.1 Open the ASCII file
     
    391439        optpropfile = "optprop_icevis_n30.dat"
    392440      CASE(3) ! STORMDUST
     441        ! Dust file
     442        optpropfile = "optprop_dustvis_TM_n50.dat"
     443      CASE(4) ! TOPDUST
    393444        ! Dust file
    394445        optpropfile = "optprop_dustvis_TM_n50.dat"
     
    407458        optpropfile = "optprop_iceir_n30.dat"
    408459      CASE(3) ! STORMDUST
     460        ! Dust file
     461        optpropfile = "optprop_dustir_n50.dat"
     462      CASE(4) ! TOPDUST
    409463        ! Dust file
    410464        optpropfile = "optprop_dustir_n50.dat"
     
    468522    ALLOCATE(radiusdyn(nsize))      ! Aerosol radius axis
    469523    ALLOCATE(Qext(nwvl,nsize))      ! Extinction efficiency coeff
     524    ALLOCATE(omeg(nwvl,nsize))      ! Single scattering albedo
    470525
    471526!==========================================================================
     
    516571              ENDIF
    517572            ENDDO
     573            jfile = jfile+1
     574        CASE(4) reading2_seq ! omeg ----------------------------
     575            isize = 1
     576            DO WHILE (isize .le. nsize)
     577              READ(file_unit,*,iostat=read_ok) scanline
     578              if (read_ok.ne.0) then
     579                write(*,*)'reading2_seq: Error while reading line: ',&
     580                          trim(scanline)
     581                write(*,*)'   of file ',&
     582                          trim(datadir)//'/'//trim(optpropfile)
     583                stop
     584              endif
     585              IF ((scanline(1:1).ne.'#').and.(scanline(1:1).ne.' ')) THEN
     586                BACKSPACE(file_unit)
     587                read(file_unit,*) omeg(:,isize)
     588                isize = isize + 1
     589              ENDIF
     590            ENDDO
    518591            endwhile = .true.
    519592        CASE DEFAULT reading2_seq ! default --------------------
     
    569642    ! Switch to netcdf define mode
    570643    ierr=nf90_redef(outfid)
     644    error_text="ERROR: Couldn't start netcdf define mode"
     645    call status_check(ierr,error_text)
    571646    write(*,*)""
    572647    SELECT CASE (iaer)
     
    580655     
    581656      ! Write the attributes
    582       ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Dust extinction opacity at reference wavelength")
     657      if (opatype.eq."ext") then
     658        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Dust extinction opacity at reference wavelength")
     659      else ! opatype.eq."abs"
     660        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Dust absorption opacity at reference wavelength")
     661      endif
    583662     
    584663    CASE(2) ! WATER ICE
     
    591670     
    592671      ! Write the attributes
    593       ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Water ice extinction opacity at reference wavelength")
     672      if (opatype.eq."ext") then
     673        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Water ice extinction opacity at reference wavelength")
     674      else ! opatype.eq."abs"
     675        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Water ice absorption opacity at reference wavelength")
     676      endif
    594677     
    595678    CASE(3) ! STORMDUST
     
    602685     
    603686      ! Write the attributes
    604       ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Stormdust extinction opacity at reference wavelength")
     687      if (opatype.eq."ext") then
     688        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Stormdust extinction opacity at reference wavelength")
     689      else ! opatype.eq."abs"
     690        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Stormdust absorption opacity at reference wavelength")
     691      endif
     692
     693    CASE(4) ! TOPDUST
     694      ! Insert the definition of the variable
     695      tmpvarname="opatopdust"
     696      ierr=NF90_DEF_VAR(outfid,trim(tmpvarname),nf90_float,varshape,tmpvaridout)
     697      error_text="ERROR: Couldn't create "//trim(tmpvarname)//" in the outfile"
     698      call status_check(ierr,error_text)
     699      write(*,*) trim(tmpvarname)//" has been created in the outfile"
     700     
     701      ! Write the attributes
     702      if (opatype.eq."ext") then
     703        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Topdust extinction opacity at reference wavelength")
     704      else ! opatype.eq."abs"
     705        ierr=nf90_put_att(outfid,tmpvaridout,"long_name","Topdust absorption opacity at reference wavelength")
     706      endif
    605707
    606708! + NEW AER?   
    607709    END SELECT ! iaer
    608 
     710   
    609711    ierr=nf90_put_att(outfid,tmpvaridout,"units","opacity/km")
    610712    ierr=nf90_put_att(outfid,tmpvaridout,"refwavelength",wvl_val)
     
    614716    ! End netcdf define mode
    615717    ierr=nf90_enddef(outfid)
    616 
     718    error_text="ERROR: Couldn't end netcdf define mode"
     719    call status_check(ierr,error_text)
     720     
    617721!==========================================================================
    618722! 3.2 Computation of the opacities
     
    624728         ! Get the optpropfile reff values encompassing the GCM reff
    625729         isize=1
    626          do while((isize.le.nsize).and.(radiusdyn(isize).lt.reff(iaer,ilon,ilat,ialt,it)))
     730         do while((isize.le.nsize).and.(radiusdyn(isize).lt.reff(ilon,ilat,ialt,it)))
    627731           isize=isize+1
    628732         enddo
    629          if ((isize.gt.nsize).or.(radiusdyn(1).gt.reff(iaer,ilon,ilat,ialt,it))) then
    630 !           write(*,*) "WARNING: the GCM reff (",reff(iaer,ilon,ilat,ialt,it),"m) is out of the bounds"
     733         if ((isize.gt.nsize).or.(radiusdyn(1).gt.reff(ilon,ilat,ialt,it))) then
     734!           write(*,*) "WARNING: the GCM reff (",reff(ilon,ilat,ialt,it),"m) is out of the bounds"
    631735!           write(*,*) "of the file ",trim(datadir)//'/'//trim(optpropfile)
    632736!           write(*,*) "(reff_inf=",radiusdyn(1),"m ; reff_sup=",radiusdyn(nsize),"m)"
     
    634738
    635739           ! NB: this should especially handle cases when reff=0
    636            opa_aer(iaer,ilon,ilat,ialt,it)=missval(iaer)
     740           opa_aer(ilon,ilat,ialt,it)=missval(iaer)
    637741           
    638          else if (mmr(iaer,ilon,ilat,ialt,it).eq.missval(iaer)) then
     742         else if (mmr(ilon,ilat,ialt,it).eq.missval(iaer)) then
    639743           ! if there is a missing value in input file
    640            opa_aer(iaer,ilon,ilat,ialt,it)=missval(iaer)
     744           opa_aer(ilon,ilat,ialt,it)=missval(iaer)
    641745           
    642746         else
    643            if (radiusdyn(isize).eq.reff(iaer,ilon,ilat,ialt,it)) then
    644              ! if the GCM reff is in the optpropfile
     747           if (radiusdyn(isize).eq.reff(ilon,ilat,ialt,it)) then
     748             ! if the GCM reff is exactly in the optpropfile
    645749             isize1 = isize
    646750             isize2 = isize
     
    650754           endif
    651755         
     756           ! Qext COMPUTATION
    652757           ! Linear interpolation in effective radius
    653758           if (isize2.ne.isize1) then
    654              coeff = (reff(iaer,ilon,ilat,ialt,it)-radiusdyn(isize1))/(radiusdyn(isize2)-radiusdyn(isize1))
     759             coeff = (reff(ilon,ilat,ialt,it)-radiusdyn(isize1))/(radiusdyn(isize2)-radiusdyn(isize1))
    655760           else
    656761             coeff = 0.
     
    658763           reffQext(1) = Qext(iwvl1,isize1)+coeff*(Qext(iwvl1,isize2)-Qext(iwvl1,isize1))
    659764           reffQext(2) = Qext(iwvl2,isize1)+coeff*(Qext(iwvl2,isize2)-Qext(iwvl2,isize1))
    660            
    661765           ! Linear interpolation in wavelength
    662766           if (iwvl2.ne.iwvl1) then
     
    667771           Qext_val = reffQext(1)+coeff*(reffQext(2)-reffQext(1))
    668772           
    669            ! Computation of the opacity [1/km]
    670            opa_aer(iaer,ilon,ilat,ialt,it)= 750.*Qext_val*mmr(iaer,ilon,ilat,ialt,it)*rho(ilon,ilat,ialt,it)&
    671                                                / ( rho_aer(iaer) * reff(iaer,ilon,ilat,ialt,it) )
    672                    
     773           ! COMPUTATION OF THE EXTINCTION OPACITY [1/km]
     774           opa_aer(ilon,ilat,ialt,it)= 750.*Qext_val*mmr(ilon,ilat,ialt,it)*rho(ilon,ilat,ialt,it)&
     775                                               / ( rho_aer(iaer) * reff(ilon,ilat,ialt,it) )
     776             
     777             
     778           if (opatype.eq."abs") then
     779             ! omeg COMPUTATION
     780             ! Linear interpolation in effective radius
     781             if (isize2.ne.isize1) then
     782               coeff = (reff(ilon,ilat,ialt,it)-radiusdyn(isize1))/(radiusdyn(isize2)-radiusdyn(isize1))
     783             else
     784               coeff = 0.
     785             endif
     786             reffomeg(1) = omeg(iwvl1,isize1)+coeff*(omeg(iwvl1,isize2)-omeg(iwvl1,isize1))
     787             reffomeg(2) = omeg(iwvl2,isize1)+coeff*(omeg(iwvl2,isize2)-omeg(iwvl2,isize1))
     788             ! Linear interpolation in wavelength
     789             if (iwvl2.ne.iwvl1) then
     790               coeff = (wvl_val-wvl(iwvl1))/(wvl(iwvl2)-wvl(iwvl1))
     791             else
     792               coeff = 0.
     793             endif
     794             omeg_val = reffomeg(1)+coeff*(reffomeg(2)-reffomeg(1))
     795
     796             ! COMPUTATION OF THE ABSORPTION OPACITY [1/km]
     797             opa_aer(ilon,ilat,ialt,it)= (1 - omeg_val) * opa_aer(ilon,ilat,ialt,it)
     798           endif ! opatype.eq."abs"
     799                 
    673800         endif
    674801       enddo ! it
     
    680807! 3.3 Writing in the output file
    681808!==========================================================================
    682     ierr = NF90_PUT_VAR(outfid, tmpvaridout, opa_aer(iaer,:,:,:,:))
     809    ierr = NF90_PUT_VAR(outfid, tmpvaridout, opa_aer(:,:,:,:))
    683810    error_text="Error: could not write "//trim(tmpvarname)//" data in the outfile"
    684811    call status_check(ierr,error_text)
     
    687814! 3.4 Prepare next loop
    688815!==========================================================================
     816    DEALLOCATE(mmr)
     817    DEALLOCATE(reff)
     818    DEALLOCATE(opa_aer)
    689819    DEALLOCATE(wvl)
    690820    DEALLOCATE(radiusdyn)
    691821    DEALLOCATE(Qext)
     822    DEALLOCATE(omeg)
    692823   
    693824  endif ! if aerok(iaer)
  • trunk/LMDZ.MARS/util/aeroptical.def

    r2317 r2443  
    335.e-7
    44~/datadir
    5 
     5ext
    66
    77
     
    14143) The wavelength at which the output opacities are calibrated (in meters)
    15154) Directory where the optical properties files are
     165) Opacity type : extinction (ext) or absorption (abs)
    1617
  • trunk/LMDZ.MARS/util/simu_MCS.F90

    r2404 r2443  
    12061206!===============================================================================
    12071207    ! Observer variables to extract :
    1208     IF ((trim(GCMvarname).eq."dsodust").or.(trim(GCMvarname).eq."dso") &
    1209       .or.(trim(GCMvarname).eq."dustq").or.(trim(GCMvarname).eq."dust") &
    1210       .or.(trim(GCMvarname).eq."reffdust")) THEN
     1208    IF ((index(GCMvarname,"dust").ne.0).or.(index(GCMvarname,"dso").ne.0)) THEN
     1209      ! if the variable name contains "dust" or "dso". Especially for the targeted variables :
     1210      ! dustq,dustN,dsodust,reffdust,opadust, and their equivalents for stormdust & topdust
    12111211      OBSvarname  = "dust"
    12121212      numbin_name = "numbindust"
    12131213    ELSE IF ((trim(GCMvarname).eq."h2o_ice").or.(trim(GCMvarname).eq."wice") &
    1214            .or.(trim(GCMvarname).eq."reffice")) THEN
     1214           .or.(trim(GCMvarname).eq."reffice").or.(trim(GCMvarname).eq."opawice")) THEN
    12151215      OBSvarname  = "wice"
    12161216      numbin_name = "numbinwice"
Note: See TracChangeset for help on using the changeset viewer.