Changeset 3122


Ignore:
Timestamp:
Nov 10, 2023, 4:48:52 PM (13 months ago)
Author:
jbclement
Message:

PEM:
Correction of the reading of the PCM data (it did not work if no slope was used) + some minor related cleanings.
JBC

Location:
trunk
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/evolution/changelog.txt

    r3114 r3122  
    130130== 03/11/2023 == JBC
    131131Following r3113, addition of 'nqsoil' and 'qsoil' in the arguments of the subroutines 'phyetat0' and 'physdem1' to be able to compile.
     132
     133== 10/11/2023 == JBC
     134Correction of the reading of the PCM data (it did not work if no slope was used) + some minor related cleanings.
  • trunk/LMDZ.COMMON/libf/evolution/pem.F90

    r3114 r3122  
    604604!------------------------
    605605call pemetat0("startpem.nc",ngrid,nsoilmx,nsoilmx_PEM,nslope,timelen,timestep,TI_PEM,tsoil_PEM,porefillingice_depth, &
    606               porefillingice_thickness,tsurf_ave_yr1, tsurf_ave, q_co2_PEM_phys, q_h2o_PEM_phys,ps_timeseries,          &
    607               tsoil_phys_PEM_timeseries,tendencies_h2o_ice,tendencies_co2_ice,qsurf(:,igcm_co2,:),                      &
    608               qsurf(:,igcm_h2o_ice,:),global_ave_press_GCM,watersurf_density_ave,watersoil_density_PEM_ave,             &
     606              porefillingice_thickness,tsurf_ave_yr1, tsurf_ave, q_co2_PEM_phys, q_h2o_PEM_phys,ps_timeseries,       &
     607              tsoil_phys_PEM_timeseries,tendencies_h2o_ice,tendencies_co2_ice,qsurf(:,igcm_co2,:),                   &
     608              qsurf(:,igcm_h2o_ice,:),global_ave_press_GCM,watersurf_density_ave,watersoil_density_PEM_ave,          &
    609609              co2_adsorbded_phys,delta_co2_adsorbded,h2o_adsorbded_phys,delta_h2o_adsorbded,water_reservoir)
    610610
     
    717717        do t = 1,timelen
    718718            q_co2_PEM_phys(ig,t) = q_co2_PEM_phys(ig,t)*(zplev_old_timeseries(ig,l,t) - zplev_old_timeseries(ig,l + 1,t))/ &
    719                                    (zplev_new_timeseries(ig,l,t) - zplev_new_timeseries(ig,l + 1,t))   &
    720                                 + ((zplev_new_timeseries(ig,l,t) - zplev_new_timeseries(ig,l + 1,t))   &
    721                                 -  (zplev_old_timeseries(ig,l,t) - zplev_old_timeseries(ig,l + 1,t)))/ &
     719                                   (zplev_new_timeseries(ig,l,t) - zplev_new_timeseries(ig,l + 1,t))                       &
     720                                + ((zplev_new_timeseries(ig,l,t) - zplev_new_timeseries(ig,l + 1,t))                       &
     721                                -  (zplev_old_timeseries(ig,l,t) - zplev_old_timeseries(ig,l + 1,t)))/                     &
    722722                                   (zplev_new_timeseries(ig,l,t) - zplev_new_timeseries(ig,l + 1,t))
    723723            if (q_co2_PEM_phys(ig,t) < 0) then
     
    861861
    862862        deallocate(TI_locslope,Tsoil_locslope,Tsurf_locslope)
     863
     864! II_d.3 Update the ice table
    863865        write(*,*) "Compute ice table"
    864 
    865 ! II_d.3 Update the ice table
    866866        porefillingice_thickness_prev_iter(:,:) = porefillingice_thickness(:,:)
    867867        call computeice_table_equilibrium(ngrid,nslope,nsoilmx_PEM,watercaptag,watersurf_density_ave,watersoil_density_PEM_ave,TI_PEM(:,1,:),porefillingice_depth,porefillingice_thickness)
    868 
    869868        call compute_massh2o_exchange_ssi(ngrid,nslope,nsoilmx_PEM,porefillingice_thickness_prev_iter,porefillingice_thickness,porefillingice_depth,tsoil_PEM,delta_h2o_icetablesublim) ! Mass of H2O exchange between the ssi and the atmosphere
    870869
     870! II_d.4 Update the soil thermal properties
    871871        write(*,*) "Update soil propreties"
    872 
    873 ! II_d.4 Update the soil thermal properties
    874872        call update_soil_thermalproperties(ngrid,nslope,nsoilmx_PEM,tendencies_h2o_ice,qsurf(:,igcm_h2o_ice,:),global_ave_press_new,porefillingice_depth,porefillingice_thickness,TI_PEM)
    875873
     
    932930    i_myear = i_myear + dt_pem
    933931
    934     write(*,*) "Checking all the stopping criterion."
     932    write(*,*) "Checking all the stopping criteria..."
    935933    if (STOPPING_water) then
    936934        write(*,*) "STOPPING because surface of water ice sublimating is too low, see message above", STOPPING_water
     
    11361134             float(day_ini),0.,nslope,def_slope,subslope_dist)
    11371135call pemdem1("restartpem.nc",i_myear,nsoilmx_PEM,ngrid,nslope,tsoil_PEM, &
    1138              TI_PEM, porefillingice_depth,porefillingice_thickness,         &
     1136             TI_PEM, porefillingice_depth,porefillingice_thickness,      &
    11391137             co2_adsorbded_phys,h2o_adsorbded_phys,water_reservoir)
    11401138write(*,*) "restartpem.nc has been written"
  • trunk/LMDZ.COMMON/libf/evolution/read_data_PCM_mod.F90

    r3096 r3122  
    77implicit none
    88
    9 character(256) :: msg, var, modname ! for reading
    10 integer        :: fID, vID          ! for reading
     9character(13), parameter :: modname = 'read_data_PCM'
     10character(256)           :: msg      ! for reading
     11integer                  :: fID, vID ! for reading
    1112
    1213!=======================================================================
     
    1415!=======================================================================
    1516
    16 SUBROUTINE read_data_PCM(fichnom,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries,           &
     17SUBROUTINE read_data_PCM(filename,timelen,iim_input,jjm_input,ngrid,nslope,vmr_co2_gcm_phys,ps_timeseries,          &
    1718                         min_co2_ice,min_h2o_ice,tsurf_ave,tsoil_ave,tsurf_gcm,tsoil_gcm,q_co2,q_h2o,co2_ice_slope, &
    1819                         watersurf_density_ave,watersoil_density)
     
    3536! Arguments:
    3637
    37 character(len = *), intent(in) :: fichnom                             !--- FILE NAME
     38character(len = *), intent(in) :: filename                            ! File name
    3839integer,            intent(in) :: timelen                             ! number of times stored in the file
    3940integer                        :: iim_input, jjm_input, ngrid, nslope ! number of points in the lat x lon dynamical grid, number of subgrid slopes
     
    5354real, dimension(ngrid,nslope),                 intent(out) :: watersurf_density_ave ! Water density at the surface [kg/m^3]
    5455real, dimension(ngrid,nsoilmx,nslope,timelen), intent(out) :: watersoil_density     ! Water density in the soil layer, time series [kg/m^3]
    55 !===============================================================================
    56 !   Local Variables
     56!=======================================================================
     57! Local Variables
    5758character(12)                   :: start_file_type = "earth" ! default start file type
    5859real, dimension(:), allocatable :: time      ! times stored in start
     
    6061integer                         :: edges(4), corner(4)
    6162integer                         :: i, j, l, t          ! loop variables
    62 real                            ::  A , B, mmean       ! Molar Mass of co2 and no co2, A;B intermediate variables to compute the mean molar mass of the layer
     63real                            :: A, B, mmean         ! Molar Mass of co2 and no co2, A;B intermediate variables to compute the mean molar mass of the layer
    6364integer                         :: islope              ! loop for variables
    6465character(2)                    :: num                 ! for reading sloped variables
    6566real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: h2o_ice_s_dyn         ! h2o ice per slope of the concatenated file [kg/m^2]
    66 real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: watercap_slope
    67 real, dimension(iim_input + 1,jjm_input + 1,timelen)                :: vmr_co2_gcm           ! CO2 volume mixing ratio in the first layer  [mol/m^3]
     67real, dimension(iim_input + 1,jjm_input + 1,nslope,timelen)         :: watercap
     68real, dimension(iim_input + 1,jjm_input + 1,timelen)                :: vmr_co2_gcm           ! CO2 volume mixing ratio in the first layer [mol/m^3]
    6869real, dimension(iim_input + 1,jjm_input + 1,timelen)                :: ps_GCM                ! Surface Pressure [Pa]
    6970real, dimension(iim_input + 1,jjm_input + 1,nslope)                 :: min_co2_ice_dyn
     
    7980real, dimension(iim_input + 1,jjm_input + 1,nsoilmx,nslope,timelen) :: watersoil_density_dyn ! Water density in the soil layer, time series [kg/m^3]
    8081real, dimension(ngrid,nslope,timelen)                               :: watersurf_density     ! Water density at the surface, time series [kg/m^3]
    81 
    8282!-----------------------------------------------------------------------
    83 modname="read_data_PCM"
    84 
    85 A = (1/m_co2 - 1/m_noco2)
    86 B = 1/m_noco2
    87 
    88 write(*,*) "Opening ", fichnom, "..."
    89 
    90 !  Open initial state NetCDF file
    91 var = fichnom
    92 call error_msg(NF90_OPEN(var,NF90_NOWRITE,fID),"open",var)
    93 
    94 write(*,*) "Downloading data for vmr co2..."
    95 
    96 call get_var3("co2_layer1"   ,q_co2_dyn)
    97 
    98 write(*,*) "Downloading data for vmr co2 done"
    99 write(*,*) "Downloading data for vmr h20..."
    100 
    101 call get_var3("h2o_layer1"   ,q_h2o_dyn)
    102 
    103 write(*,*) "Downloading data for vmr h2o done"
    104 write(*,*) "Downloading data for surface pressure ..."
    105 
    106 call get_var3("ps"   ,ps_GCM)
    107 
    108 write(*,*) "Downloading data for surface pressure done"
    109 write(*,*) "nslope=", nslope
    110 
    111 if (nslope > 1) then
    112     write(*,*) "Downloading data for co2ice_slope ..."
    113 
     83! Open the NetCDF file
     84write(*,*) "Opening "//filename//"..."
     85call error_msg(NF90_OPEN(filename,NF90_NOWRITE,fID),"open",filename)
     86
     87! Dowload the data from the file
     88call get_var3("ps",ps_GCM)
     89write(*,*) "Data for surface pressure downloaded!"
     90
     91call get_var3("co2_layer1",q_co2_dyn)
     92write(*,*) "Data for vmr co2 downloaded!"
     93
     94call get_var3("h2o_layer1",q_h2o_dyn)
     95write(*,*) "Data for vmr h2o downloaded!"
     96
     97if (nslope == 1) then ! There is no slope
     98    call get_var3("co2ice",co2_ice_slope_dyn(:,:,1,:))
     99    write(*,*) "Data for co2_ice downloaded!"
     100
     101    call get_var3("h2o_ice_s",h2o_ice_s_dyn(:,:,1,:))
     102    write(*,*) "Data for h2o_ice_s downloaded!"
     103
     104#ifndef CPP_STD
     105    call get_var3("watercap",watercap(:,:,1,:))
     106    write(*,*) "Data for watercap downloaded!"
     107#endif
     108
     109    call get_var3("tsurf",tsurf_gcm_dyn(:,:,1,:))
     110    write(*,*) "Data for tsurf downloaded!"
     111
     112#ifndef CPP_STD
     113    if (soil_pem) then
     114        call get_var4("soiltemp",tsoil_gcm_dyn(:,:,:,1,:))
     115        write(*,*) "Data for soiltemp downloaded!"
     116
     117        call get_var4("waterdensity_soil",watersoil_density_dyn(:,:,:,1,:))
     118        write(*,*) "Data for waterdensity_soil downloaded!"
     119
     120        call get_var3("waterdensity_surface",watersurf_density_dyn(:,:,islope,:))
     121        write(*,*) "Data for waterdensity_surface downloaded!"
     122    endif !soil_pem
     123#endif
     124else ! We use slopes
    114125    do islope = 1,nslope
    115126        write(num,'(i2.2)') islope
    116127        call get_var3("co2ice_slope"//num,co2_ice_slope_dyn(:,:,islope,:))
    117128    enddo
    118    
    119     write(*,*) "Downloading data for co2ice_slope done"
    120     write(*,*) "Downloading data for h2o_ice_s_slope ..."
    121    
     129    write(*,*) "Data for co2_ice downloaded!"
     130
    122131    do islope = 1,nslope
    123132        write(num,'(i2.2)') islope
    124133        call get_var3("h2o_ice_s_slope"//num,h2o_ice_s_dyn(:,:,islope,:))
    125134    enddo
    126 
    127     write(*,*) "Downloading data for h2o_ice_s_slope done"
     135    write(*,*) "Data for h2o_ice_s downloaded!"
    128136
    129137#ifndef CPP_STD
    130     write(*,*) "Downloading data for watercap_slope ..."
    131138    do islope = 1,nslope
    132139        write(num,'(i2.2)') islope
    133         call get_var3("watercap_slope"//num,watercap_slope(:,:,islope,:))
    134 !        watercap_slope(:,:,:,:) = 0.
    135     enddo
    136     write(*,*) "Downloading data for watercap_slope done"
    137 #endif
    138 
    139     write(*,*) "Downloading data for tsurf_slope ..."
    140 
    141     do islope=1,nslope
     140        call get_var3("watercap_slope"//num,watercap(:,:,islope,:))
     141    enddo
     142    write(*,*) "Data for watercap downloaded!"
     143#endif
     144
     145    do islope = 1,nslope
    142146        write(num,'(i2.2)') islope
    143147        call get_var3("tsurf_slope"//num,tsurf_gcm_dyn(:,:,islope,:))
    144148    enddo
    145 
    146     write(*,*) "Downloading data for tsurf_slope done"
     149    write(*,*) "Data for tsurf downloaded!"
    147150
    148151#ifndef CPP_STD
    149152    if (soil_pem) then
    150         write(*,*) "Downloading data for soiltemp_slope ..."
    151 
    152153        do islope = 1,nslope
    153154            write(num,'(i2.2)') islope
    154155            call get_var4("soiltemp_slope"//num,tsoil_gcm_dyn(:,:,:,islope,:))
    155156        enddo
    156 
    157         write(*,*) "Downloading data for soiltemp_slope done"
    158         write(*,*) "Downloading data for watersoil_density ..."
     157        write(*,*) "Data for soiltemp downloaded!"
    159158
    160159        do islope = 1,nslope
    161160            write(num,'(i2.2)') islope
    162             call get_var4("Waterdensity_soil_slope"//num,watersoil_density_dyn(:,:,:,islope,:))
    163         enddo
    164 
    165         write(*,*) "Downloading data for  watersoil_density  done"
    166         write(*,*) "Downloading data for  watersurf_density  ..."
     161            call get_var4("waterdensity_soil_slope"//num,watersoil_density_dyn(:,:,:,islope,:))
     162        enddo
     163        write(*,*) "Data for waterdensity_soil downloaded!"
    167164
    168165        do islope = 1,nslope
    169166            write(num,'(i2.2)') islope
    170             call get_var3("Waterdensity_surface"//num,watersurf_density_dyn(:,:,islope,:))
    171         enddo
    172 
    173         write(*,*) "Downloading data for  watersurf_density  done"
    174 
     167            call get_var3("waterdensity_surface"//num,watersurf_density_dyn(:,:,islope,:))
     168        enddo
     169        write(*,*) "Data for waterdensity_surface downloaded!"
    175170    endif !soil_pem
    176171#endif
    177 else !nslope = 1 no slope, we copy all the values
    178     call get_var3("h2o_ice_s", h2o_ice_s_dyn(:,:,1,:))
    179     call get_var3("co2ice", co2_ice_slope_dyn(:,:,1,:))
    180     call get_var3("tsurf", tsurf_gcm_dyn(:,:,1,:))
    181    
    182 #ifndef CPP_STD
    183 !    call get_var3("watercap", watercap_slope(:,:,1,:))
    184     watercap_slope(:,:,1,:) = 0.
    185     watersurf_density_dyn(:,:,:,:) = 0.
    186     watersoil_density_dyn(:,:,:,:,:) = 0.
    187 #endif
    188 
    189     if (soil_pem) call get_var4("soiltemp",tsoil_gcm_dyn(:,:,:,1,:))
    190 endif !nslope=1
     172endif
    191173
    192174! Compute the minimum over the year for each point
    193 write(*,*) "Computing the min of h2o_ice_slope"
    194 min_h2o_ice_dyn(:,:,:) = minval(h2o_ice_s_dyn + watercap_slope,4)
    195 write(*,*) "Computing the min of co2_ice_slope"
     175write(*,*) "Computing the min of h2o_ice..."
     176where (h2o_ice_s_dyn < 0.) h2o_ice_s_dyn = 0.
     177min_h2o_ice_dyn(:,:,:) = minval(h2o_ice_s_dyn + watercap,4)
     178write(*,*) "Computing the min of co2_ice..."
     179where (co2_ice_slope_dyn < 0.) co2_ice_slope_dyn = 0.
    196180min_co2_ice_dyn(:,:,:) = minval(co2_ice_slope_dyn,4)
    197181
    198 !Compute averages
    199 write(*,*) "Computing average of tsurf"
     182! Compute averages over the year for each point
     183write(*,*) "Computing the average of tsurf..."
    200184tsurf_ave_dyn(:,:,:) = sum(tsurf_gcm_dyn(:,:,:,:),4)/timelen
    201185
     
    203187    do islope = 1,nslope
    204188        do t = 1,timelen
    205             call gr_dyn_fi(1,iim_input+1,jjm_input+1,ngrid,watersurf_density_dyn(:,:,islope,t),watersurf_density(:,islope,t))
     189            call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,watersurf_density_dyn(:,:,islope,t),watersurf_density(:,islope,t))
    206190        enddo
    207191    enddo
     
    209193
    210194if (soil_pem) then
    211     write(*,*) "Computing average of tsoil"
     195    write(*,*) "Computing average of tsoil..."
    212196    tsoil_ave_dyn(:,:,:,:) = sum(tsoil_gcm_dyn(:,:,:,:,:),5)/timelen
    213     write(*,*) "Computing average of watersurf_density"
     197    write(*,*) "Computing average of waterdensity_surface..."
    214198    watersurf_density_ave(:,:) = sum(watersurf_density(:,:,:),3)/timelen
    215199endif
    216200
    217 ! By definition, a density is positive, we get rid of the negative values
    218 where (min_co2_ice_dyn < 0.) min_co2_ice_dyn = 0.
    219 where (min_h2o_ice_dyn < 0.) min_h2o_ice_dyn = 0.
    220 
     201! By definition, we get rid of the negative values
     202A = (1./m_co2 - 1./m_noco2)
     203B = 1./m_noco2
    221204do i = 1,iim + 1
    222205    do j = 1,jjm_input + 1
     
    250233            do l = 1,nsoilmx
    251234                call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_ave_dyn(:,:,l,islope),tsoil_ave(:,l,islope))
    252                 do t=1,timelen
     235                do t = 1,timelen
    253236                    call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsoil_gcm_dyn(:,:,l,islope,t),tsoil_gcm(:,l,islope,t))
    254237                    call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,watersoil_density_dyn(:,:,l,islope,t),watersoil_density(:,l,islope,t))
    255238                enddo
    256239            enddo
    257         endif !soil_pem
     240        endif ! soil_pem
    258241        do t = 1,timelen
    259242            call gr_dyn_fi(1,iim_input + 1,jjm_input + 1,ngrid,tsurf_GCM_dyn(:,:,islope,t),tsurf_GCM(:,islope,t))
     
    274257        tsoil_gcm(1,:,:,:) = tsoil_gcm_dyn(1,1,:,:,:)
    275258        watersoil_density(1,:,:,:) = watersoil_density_dyn(1,1,:,:,:)
    276     endif !soil_pem
     259    endif ! soil_pem
    277260    tsurf_GCM(1,:,:) = tsurf_GCM_dyn(1,1,:,:)
    278261    co2_ice_slope(1,:,:) = co2_ice_slope_dyn(1,1,:,:)
     
    281264
    282265END SUBROUTINE read_data_PCM
     266
     267!=======================================================================
    283268
    284269SUBROUTINE check_dim(n1,n2,str1,str2)
     
    302287!=======================================================================
    303288
    304 SUBROUTINE get_var1(var,v)
    305 
    306 implicit none
    307 
    308 character(len = *), intent(in)  :: var
     289SUBROUTINE get_var1(filename,v)
     290
     291implicit none
     292
     293character(len = *), intent(in)  :: filename
    309294real, dimension(:), intent(out) :: v
    310295
    311 call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
    312 call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
     296call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
     297call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
    313298
    314299END SUBROUTINE get_var1
     
    316301!=======================================================================
    317302
    318 SUBROUTINE get_var3(var,v) ! on U grid
    319 
    320 implicit none
    321 
    322 character(len = *),     intent(in)  :: var
     303SUBROUTINE get_var3(filename,v) ! on U grid
     304
     305implicit none
     306
     307character(len = *),     intent(in)  :: filename
    323308real, dimension(:,:,:), intent(out) :: v
    324309
    325 call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
    326 call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
     310call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
     311call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
    327312
    328313END SUBROUTINE get_var3
     
    330315!=======================================================================
    331316
    332 SUBROUTINE get_var4(var,v)
    333 
    334 implicit none
    335 
    336 character(len = *),       intent(in)  :: var
     317SUBROUTINE get_var4(filename,v)
     318
     319implicit none
     320
     321character(len = *),       intent(in)  :: filename
    337322real, dimension(:,:,:,:), intent(out) :: v
    338323
    339 call error_msg(NF90_INQ_VARID(fID,var,vID),"inq",var)
    340 call error_msg(NF90_GET_VAR(fID,vID,v),"get",var)
     324call error_msg(NF90_INQ_VARID(fID,filename,vID),"inq",filename)
     325call error_msg(NF90_GET_VAR(fID,vID,v),"get",filename)
    341326
    342327END SUBROUTINE get_var4
  • trunk/LMDZ.COMMON/libf/evolution/writediagpem.F90

    r3097 r3122  
    3232!         Oct 2011 Francois: enable having a 'diagpem.def' file to select
    3333!                            at runtime, which variables to put in file
    34 !         Oct 2023 JB: conversion into Fortran 90 with module for the PEM
     34!         Oct 2023 JBC: conversion into Fortran 90 with module for the PEM
    3535!
    3636!  parametres (input) :
  • trunk/LMDZ.MARS/deftank/field_def_physics_mars.xml

    r3115 r3122  
    44<!-- =========================================================================================================== -->
    55
    6     <field_definition prec="4" 
     6    <field_definition prec="4"
    77                      freq_op="1ts"
    88                      enabled=".TRUE.">
    9        
     9
    1010        <!-- 0D variables -->
    1111        <field_group id="fields_0D" grid_ref="scalarpoint">
     
    150150                   unit="g" />
    151151
    152         </field_group>   
     152        </field_group>
    153153
    154154        <field_group id="fields_controle" grid_ref="controle_grid">
     
    171171        </field_group>
    172172
    173        
     173
    174174        <!-- 2D variables -->
    175175        <field_group id="fields_2D" domain_ref="dom_glo">
     
    178178                   unit="m2" />
    179179            <field id="phisfi"
    180                    long_name="Surface geopotential" 
     180                   long_name="Surface geopotential"
    181181                   unit="m2.s-2" />
    182182            <field id="emis"
    183                    long_name="Surface emissivity" 
     183                   long_name="Surface emissivity"
    184184                   unit="" />
    185185            <field id="emis_slope01"
    186                    long_name="Surface emissivity of slope 01" 
     186                   long_name="Surface emissivity of slope 01"
    187187                   unit="" />
    188188            <field id="emis_slope02"
    189                    long_name="Surface emissivity of slope 02" 
     189                   long_name="Surface emissivity of slope 02"
    190190                   unit="" />
    191191            <field id="emis_slope03"
    192                    long_name="Surface emissivity of slope 03" 
     192                   long_name="Surface emissivity of slope 03"
    193193                   unit="" />
    194194            <field id="emis_slope04"
    195                    long_name="Surface emissivity of slope 04" 
     195                   long_name="Surface emissivity of slope 04"
    196196                   unit="" />
    197197            <field id="emis_slope05"
    198                    long_name="Surface emissivity of slope 05" 
     198                   long_name="Surface emissivity of slope 05"
    199199                   unit="" />
    200200            <field id="emis_slope06"
    201                    long_name="Surface emissivity of slope 06" 
     201                   long_name="Surface emissivity of slope 06"
    202202                   unit="" />
    203203            <field id="emis_slope07"
    204                    long_name="Surface emissivity of slope 07" 
     204                   long_name="Surface emissivity of slope 07"
    205205                   unit="" />
    206206            <field id="albedo"
    207                    long_name="Albedo of the surface" 
     207                   long_name="Albedo of the surface"
    208208                   unit="" />
    209209            <field id="albedo_slope01"
    210                    long_name="Albedo of the surface for slope 01" 
     210                   long_name="Albedo of the surface for slope 01"
    211211                   unit="" />
    212212            <field id="albedo_slope02"
    213                    long_name="Albedo of the surface for slope 02" 
     213                   long_name="Albedo of the surface for slope 02"
    214214                   unit="" />
    215215            <field id="albedo_slope03"
    216                    long_name="Albedo of the surface for slope 03" 
     216                   long_name="Albedo of the surface for slope 03"
    217217                   unit="" />
    218218            <field id="albedo_slope04"
    219                    long_name="Albedo of the surface for slope 04" 
     219                   long_name="Albedo of the surface for slope 04"
    220220                   unit="" />
    221221            <field id="albedo_slope05"
    222                    long_name="Albedo of the surface for slope 05" 
     222                   long_name="Albedo of the surface for slope 05"
    223223                   unit="" />
    224224            <field id="albedo_slope06"
    225                    long_name="Albedo of the surface for slope 06" 
     225                   long_name="Albedo of the surface for slope 06"
    226226                   unit="" />
    227227            <field id="albedo_slope07"
    228                    long_name="Albedo of the surface for slope 07" 
     228                   long_name="Albedo of the surface for slope 07"
    229229                   unit="" />
    230230            <field id="local_time"
    231                    long_name="Local time" 
     231                   long_name="Local time"
    232232                   unit="sol" />
    233233
    234234            <field id="ps"
    235                    long_name="Surface Pressure" 
     235                   long_name="Surface Pressure"
    236236                   unit="Pa" />
    237237            <field id="tsurf"
     
    268268            <!-- Radiation -->
    269269            <field id="fluxsurf_lw"
    270                    long_name="Longwave radiation at the surface" 
     270                   long_name="Longwave radiation at the surface"
    271271                   unit="W.m-2" />
    272272            <field id="fluxsurf_lw_slope01"
    273                    long_name="Longwave radiation at the surface on slope 01" 
     273                   long_name="Longwave radiation at the surface on slope 01"
    274274                   unit="W.m-2" />
    275275            <field id="fluxsurf_lw_slope02"
    276                    long_name="Longwave radiation at the surface on slope 02" 
     276                   long_name="Longwave radiation at the surface on slope 02"
    277277                   unit="W.m-2" />
    278278            <field id="fluxsurf_lw_slope03"
    279                    long_name="Longwave radiation at the surface on slope 03" 
     279                   long_name="Longwave radiation at the surface on slope 03"
    280280                   unit="W.m-2" />
    281281            <field id="fluxsurf_lw_slope04"
    282                    long_name="Longwave radiation at the surface on slope 04" 
     282                   long_name="Longwave radiation at the surface on slope 04"
    283283                   unit="W.m-2" />
    284284            <field id="fluxsurf_lw_slope05"
    285                    long_name="Longwave radiation at the surface on slope 05" 
     285                   long_name="Longwave radiation at the surface on slope 05"
    286286                   unit="W.m-2" />
    287287            <field id="fluxsurf_lw_slope06"
    288                    long_name="Longwave radiation at the surface on slope 06" 
     288                   long_name="Longwave radiation at the surface on slope 06"
    289289                   unit="W.m-2" />
    290290            <field id="fluxsurf_lw_slope07"
    291                    long_name="Longwave radiation at the surface on slope 07" 
     291                   long_name="Longwave radiation at the surface on slope 07"
    292292                   unit="W.m-2" />
    293293
    294294            <field id="fluxtop_lw"
    295                    long_name="Longwave radiation at the top of the atmosphere" 
     295                   long_name="Longwave radiation at the top of the atmosphere"
    296296                   unit="W.m-2" />
    297297            <field id="fluxtop_dn_sw"
    298                    long_name="Incoming shortwave radiation at the top of the atmosphere" 
     298                   long_name="Incoming shortwave radiation at the top of the atmosphere"
    299299                   unit="W.m-2" />
    300300            <field id="fluxtop_up_sw"
    301                    long_name="Upward shortwave radiation at the top of the atmosphere" 
     301                   long_name="Upward shortwave radiation at the top of the atmosphere"
    302302                   unit="W.m-2" />
    303303
    304304            <field id="fluxsurf_dn_sw"
    305                    long_name="Incoming shortwave radiation at the surface" 
     305                   long_name="Incoming shortwave radiation at the surface"
    306306                   unit="W.m-2" />
    307307            <field id="fluxsurf_dn_sw_slope01"
    308                    long_name="Incoming shortwave radiation at the surface on slope 01" 
     308                   long_name="Incoming shortwave radiation at the surface on slope 01"
    309309                   unit="W.m-2" />
    310310            <field id="fluxsurf_dn_sw_slope02"
    311                    long_name="Incoming shortwave radiation at the surface on slope 02" 
     311                   long_name="Incoming shortwave radiation at the surface on slope 02"
    312312                   unit="W.m-2" />
    313313            <field id="fluxsurf_dn_sw_slope03"
    314                    long_name="Incoming shortwave radiation at the surface on slope 03" 
     314                   long_name="Incoming shortwave radiation at the surface on slope 03"
    315315                   unit="W.m-2" />
    316316            <field id="fluxsurf_dn_sw_slope04"
    317                    long_name="Incoming shortwave radiation at the surface on slope 04" 
     317                   long_name="Incoming shortwave radiation at the surface on slope 04"
    318318                   unit="W.m-2" />
    319319            <field id="fluxsurf_dn_sw_slope05"
    320                    long_name="Incoming shortwave radiation at the surface on slope 05" 
     320                   long_name="Incoming shortwave radiation at the surface on slope 05"
    321321                   unit="W.m-2" />
    322322            <field id="fluxsurf_dn_sw_slope06"
    323                    long_name="Incoming shortwave radiation at the surface on slope 06" 
     323                   long_name="Incoming shortwave radiation at the surface on slope 06"
    324324                   unit="W.m-2" />
    325325            <field id="fluxsurf_dn_sw_slope07"
    326                    long_name="Incoming shortwave radiation at the surface on slope 07" 
    327                    unit="W.m-2" />
    328            
     326                   long_name="Incoming shortwave radiation at the surface on slope 07"
     327                   unit="W.m-2" />
     328
    329329            <!-- dust cycle -->
    330330            <field id="tau_pref_scenario"
     
    409409                   long_name="dust injection rate"
    410410                   unit="s-1" />
    411            
     411
    412412            <field id="stormfract"
    413413                   long_name="fraction of the mesh with stormdust"
     
    429429            <field id="watercap"
    430430                   long_name="Perennial water ice thickness"
    431                    unit="kg.m-2" />           
     431                   unit="kg.m-2" />
    432432            <field id="watercap_slope01"
    433433                   long_name="Perennial water ice thickness of slope 01"
    434                    unit="kg.m-2" /> 
     434                   unit="kg.m-2" />
    435435            <field id="watercap_slope02"
    436436                   long_name="Perennial water ice thickness of slope 02"
     
    451451                   long_name="Perennial water ice thickness of slope 07"
    452452                   unit="kg/m2" />
    453    
     453
    454454            <field id="surf_h2o_lh"
    455455                   long_name="Ground ice latent heat flux"
     
    503503                   long_name="Mass of water ice on the surface of slope 07"
    504504                   unit="kg/m2" />
    505             <field id="Waterdensity_surface"
    506                    long_name="Waterdensity_surface"
    507                    unit="kg.m-3" />
    508             <field id="Waterdensity_surface01"
    509                    long_name="Waterdensity_surface of slope 01"
    510                    unit="kg.m-3" />
    511             <field id="Waterdensity_surface02"
    512                    long_name="Waterdensity_surface of slope 02"
    513                    unit="kg.m-3" />
    514             <field id="Waterdensity_surface03"
    515                    long_name="Waterdensity_surface of slope 03"
    516                    unit="kg.m-3" />
    517             <field id="Waterdensity_surface04"
    518                    long_name="Waterdensity_surface of slope 04"
    519                    unit="kg.m-3" />
    520             <field id="Waterdensity_surface05"
    521                    long_name="Waterdensity_surface of slope 05"
    522                    unit="kg.m-3" />
    523             <field id="Waterdensity_surface06"
    524                    long_name="Waterdensity_surface of slope 06"
    525                    unit="kg.m-3" />
    526             <field id="Waterdensity_surface07"
    527                    long_name="Waterdensity_surface of slope 07"
     505            <field id="waterdensity_surface"
     506                   long_name="waterdensity_surface"
     507                   unit="kg.m-3" />
     508            <field id="waterdensity_surface01"
     509                   long_name="waterdensity_surface of slope 01"
     510                   unit="kg.m-3" />
     511            <field id="waterdensity_surface02"
     512                   long_name="waterdensity_surface of slope 02"
     513                   unit="kg.m-3" />
     514            <field id="waterdensity_surface03"
     515                   long_name="waterdensity_surface of slope 03"
     516                   unit="kg.m-3" />
     517            <field id="waterdensity_surface04"
     518                   long_name="waterdensity_surface of slope 04"
     519                   unit="kg.m-3" />
     520            <field id="waterdensity_surface05"
     521                   long_name="waterdensity_surface of slope 05"
     522                   unit="kg.m-3" />
     523            <field id="waterdensity_surface06"
     524                   long_name="waterdensity_surface of slope 06"
     525                   unit="kg.m-3" />
     526            <field id="waterdensity_surface07"
     527                   long_name="waterdensity_surface of slope 07"
    528528                   unit="kg.m-3" />
    529529            <field id="h2o_layer1"
    530                    long_name="h2o in the first layer" 
     530                   long_name="h2o in the first layer"
    531531                   unit="kg/kg" />
    532532            <field id="co2_layer1"
    533                    long_name="co2 in the first layer" 
    534                    unit="kg/kg" />
    535 
    536 
    537            
     533                   long_name="co2 in the first layer"
     534                   unit="kg/kg" />
     535
     536
     537
    538538            <!-- CO2 cycle -->
    539539            <field id="co2ice"
     
    567567
    568568            <!-- tracer columns (chemistry) -->
    569             <field id="c_co2" 
    570                    long_name="CO2 column" 
    571                    unit="mol.cm-2" />
    572             <field id="c_co" 
    573                    long_name="CO column" 
    574                    unit="mol.cm-2" />
    575             <field id="c_o" 
    576                    long_name="O column" 
    577                    unit="mol.cm-2" />
    578             <field id="c_o1d" 
    579                    long_name="O1d column" 
    580                    unit="mol.cm-2" />
    581             <field id="c_o2" 
    582                    long_name="O2 column" 
    583                    unit="mol.cm-2" />
    584             <field id="c_o3" 
    585                    long_name="O3 column" 
    586                    unit="mol.cm-2" />
    587             <field id="c_h" 
    588                    long_name="H column" 
    589                    unit="mol.cm-2" />
    590             <field id="c_h2" 
    591                    long_name="H2 column" 
    592                    unit="mol.cm-2" />
    593             <field id="c_oh" 
    594                    long_name="OH column" 
    595                    unit="mol.cm-2" />
    596             <field id="c_ho2" 
    597                    long_name="HO2 column" 
    598                    unit="mol.cm-2" />
    599             <field id="c_h2o2" 
    600                    long_name="H2 column" 
    601                    unit="mol.cm-2" />
    602             <field id="c_n2" 
    603                    long_name="N2 column" 
    604                    unit="mol.cm-2" />
    605             <field id="c_ar" 
    606                    long_name="Ar column" 
    607                    unit="mol.cm-2" />
    608             <field id="c_h2o_ice" 
    609                    long_name="H2O_ice column" 
    610                    unit="mol.cm-2" />
    611             <field id="c_h2o_vap" 
    612                    long_name="H2O_vap column" 
    613                    unit="mol.cm-2" />
    614             <field id="c_n" 
    615                    long_name="N column" 
    616                    unit="mol.cm-2" />
    617             <field id="c_no" 
    618                    long_name="NO column" 
    619                    unit="mol.cm-2" />
    620             <field id="c_no2" 
    621                    long_name="NO2 column" 
    622                    unit="mol.cm-2" />
    623             <field id="c_n2d" 
    624                    long_name="N2d column" 
    625                    unit="mol.cm-2" />
    626             <field id="c_ch4" 
    627                    long_name="CH4 column" 
    628                    unit="mol.cm-2" />
    629             <field id="c_he" 
    630                    long_name="He column" 
     569            <field id="c_co2"
     570                   long_name="CO2 column"
     571                   unit="mol.cm-2" />
     572            <field id="c_co"
     573                   long_name="CO column"
     574                   unit="mol.cm-2" />
     575            <field id="c_o"
     576                   long_name="O column"
     577                   unit="mol.cm-2" />
     578            <field id="c_o1d"
     579                   long_name="O1d column"
     580                   unit="mol.cm-2" />
     581            <field id="c_o2"
     582                   long_name="O2 column"
     583                   unit="mol.cm-2" />
     584            <field id="c_o3"
     585                   long_name="O3 column"
     586                   unit="mol.cm-2" />
     587            <field id="c_h"
     588                   long_name="H column"
     589                   unit="mol.cm-2" />
     590            <field id="c_h2"
     591                   long_name="H2 column"
     592                   unit="mol.cm-2" />
     593            <field id="c_oh"
     594                   long_name="OH column"
     595                   unit="mol.cm-2" />
     596            <field id="c_ho2"
     597                   long_name="HO2 column"
     598                   unit="mol.cm-2" />
     599            <field id="c_h2o2"
     600                   long_name="H2 column"
     601                   unit="mol.cm-2" />
     602            <field id="c_n2"
     603                   long_name="N2 column"
     604                   unit="mol.cm-2" />
     605            <field id="c_ar"
     606                   long_name="Ar column"
     607                   unit="mol.cm-2" />
     608            <field id="c_h2o_ice"
     609                   long_name="H2O_ice column"
     610                   unit="mol.cm-2" />
     611            <field id="c_h2o_vap"
     612                   long_name="H2O_vap column"
     613                   unit="mol.cm-2" />
     614            <field id="c_n"
     615                   long_name="N column"
     616                   unit="mol.cm-2" />
     617            <field id="c_no"
     618                   long_name="NO column"
     619                   unit="mol.cm-2" />
     620            <field id="c_no2"
     621                   long_name="NO2 column"
     622                   unit="mol.cm-2" />
     623            <field id="c_n2d"
     624                   long_name="N2d column"
     625                   unit="mol.cm-2" />
     626            <field id="c_ch4"
     627                   long_name="CH4 column"
     628                   unit="mol.cm-2" />
     629            <field id="c_he"
     630                   long_name="He column"
    631631                   unit="mol.cm-2" />
    632632
    633633            <!-- ions -->
    634             <field id="c_co2plus" 
    635                    long_name="CO2+ column" 
    636                    unit="mol.cm-2" />
    637             <field id="c_oplus" 
    638                    long_name="O+ column" 
    639                    unit="mol.cm-2" />
    640             <field id="c_o2plus" 
    641                    long_name="O2+ column" 
    642                    unit="mol.cm-2" />
    643             <field id="c_coplus" 
    644                    long_name="CO+ column" 
    645                    unit="mol.cm-2" />
    646             <field id="c_coplus" 
    647                    long_name="CO+ column" 
    648                    unit="mol.cm-2" />
    649             <field id="c_cplus" 
    650                    long_name="C+ column" 
    651                    unit="mol.cm-2" />
    652             <field id="c_nplus" 
    653                    long_name="N+ column" 
    654                    unit="mol.cm-2" />
    655             <field id="c_noplus" 
    656                    long_name="NO+ column" 
    657                    unit="mol.cm-2" />
    658             <field id="c_n2plus" 
    659                    long_name="N2+ column" 
    660                    unit="mol.cm-2" />
    661             <field id="c_hplus" 
    662                    long_name="H+ column" 
    663                    unit="mol.cm-2" />
    664             <field id="c_hco2plus" 
    665                    long_name="HCO2+ column" 
    666                    unit="mol.cm-2" />
    667             <field id="c_hcoplus" 
    668                    long_name="HCO+ column" 
    669                    unit="mol.cm-2" />
    670             <field id="c_h2oplus" 
    671                    long_name="H2O+ column" 
    672                    unit="mol.cm-2" />
    673             <field id="c_h3oplus" 
    674                    long_name="H3O+ column" 
    675                    unit="mol.cm-2" />
    676             <field id="c_ohplus" 
    677                    long_name="OH+ column" 
    678                    unit="mol.cm-2" />
    679             <field id="c_elec" 
    680                    long_name="electron column" 
     634            <field id="c_co2plus"
     635                   long_name="CO2+ column"
     636                   unit="mol.cm-2" />
     637            <field id="c_oplus"
     638                   long_name="O+ column"
     639                   unit="mol.cm-2" />
     640            <field id="c_o2plus"
     641                   long_name="O2+ column"
     642                   unit="mol.cm-2" />
     643            <field id="c_coplus"
     644                   long_name="CO+ column"
     645                   unit="mol.cm-2" />
     646            <field id="c_coplus"
     647                   long_name="CO+ column"
     648                   unit="mol.cm-2" />
     649            <field id="c_cplus"
     650                   long_name="C+ column"
     651                   unit="mol.cm-2" />
     652            <field id="c_nplus"
     653                   long_name="N+ column"
     654                   unit="mol.cm-2" />
     655            <field id="c_noplus"
     656                   long_name="NO+ column"
     657                   unit="mol.cm-2" />
     658            <field id="c_n2plus"
     659                   long_name="N2+ column"
     660                   unit="mol.cm-2" />
     661            <field id="c_hplus"
     662                   long_name="H+ column"
     663                   unit="mol.cm-2" />
     664            <field id="c_hco2plus"
     665                   long_name="HCO2+ column"
     666                   unit="mol.cm-2" />
     667            <field id="c_hcoplus"
     668                   long_name="HCO+ column"
     669                   unit="mol.cm-2" />
     670            <field id="c_h2oplus"
     671                   long_name="H2O+ column"
     672                   unit="mol.cm-2" />
     673            <field id="c_h3oplus"
     674                   long_name="H3O+ column"
     675                   unit="mol.cm-2" />
     676            <field id="c_ohplus"
     677                   long_name="OH+ column"
     678                   unit="mol.cm-2" />
     679            <field id="c_elec"
     680                   long_name="electron column"
    681681                   unit="mol.cm-2" />
    682682
     
    734734                   long_name="Eastward Zonal Wind"
    735735                   unit="m.s-1" />
    736             <field id="v" 
    737                    long_name="Northward Meridional Wind" 
     736            <field id="v"
     737                   long_name="Northward Meridional Wind"
    738738                   unit="m.s-1" />
    739             <field id="w" 
    740                    long_name="Vertical Wind (positive when downward)" 
     739            <field id="w"
     740                   long_name="Vertical Wind (positive when downward)"
    741741                   unit="m.s-1" />
    742             <field id="rho" 
    743                    long_name="Atmospheric density" 
    744                    unit="kg.m-3" />
    745             <field id="pressure" 
    746                    long_name="Atmospheric pressure" 
     742            <field id="rho"
     743                   long_name="Atmospheric density"
     744                   unit="kg.m-3" />
     745            <field id="pressure"
     746                   long_name="Atmospheric pressure"
    747747                   unit="Pa" />
    748             <field id="zplev" 
    749                    long_name="Interlayer pressure" 
     748            <field id="zplev"
     749                   long_name="Interlayer pressure"
    750750                   unit="Pa" />
    751751
    752752            <!-- heating rates -->
    753             <field id="dtrad" 
    754                    long_name="total radiative heating rate" 
     753            <field id="dtrad"
     754                   long_name="total radiative heating rate"
    755755                   unit="K.s-1" />
    756             <field id="sw_htrt" 
    757                    long_name="Shortwave heating rate" 
     756            <field id="sw_htrt"
     757                   long_name="Shortwave heating rate"
    758758                   unit="K.s-1" />
    759             <field id="lw_htrt" 
    760                    long_name="Longwave heating rate" 
     759            <field id="lw_htrt"
     760                   long_name="Longwave heating rate"
    761761                   unit="K.s-1" />
    762             <field id="q15um" 
    763                    long_name="15 um cooling" 
     762            <field id="q15um"
     763                   long_name="15 um cooling"
    764764                   unit="K.s-1" />
    765             <field id="qnir" 
    766                    long_name="NIR heating rate" 
     765            <field id="qnir"
     766                   long_name="NIR heating rate"
    767767                   unit="K.s-1" />
    768             <field id="quv" 
    769                    long_name="EUV heating rate" 
     768            <field id="quv"
     769                   long_name="EUV heating rate"
    770770                   unit="K.s-1" />
    771             <field id="cond" 
    772                    long_name="Thermal conduction heating rate" 
     771            <field id="cond"
     772                   long_name="Thermal conduction heating rate"
    773773                   unit="K.s-1" />
    774774
    775775            <!-- tracers (CO2 and water) -->
    776             <field id="co2" 
    777                    long_name="CO2 mass mixing ratio" 
    778                    unit="kg/kg" />
    779             <field id="vmr_co2" 
    780                    long_name="CO2 volume mixing ratio" 
    781                    unit="mol/mol" />
    782             <field id="num_co2" 
    783                    long_name="CO2 number density" 
    784                    unit="cm-3" />
    785             <field id="h2o_ice" 
    786                    long_name="water ice mass mixing ratio" 
    787                    unit="kg/kg" />
    788             <field id="vmr_h2oice" 
    789                    long_name="water ice volume mixing ratio" 
    790                    unit="mol/mol" />
    791             <field id="vmr_h2o_ice" 
    792                    long_name="water ice volume mixing ratio" 
    793                    unit="mol/mol" />
    794             <field id="num_h2o_ice" 
    795                    long_name="water ice number density" 
    796                    unit="cm-3" />
    797             <field id="h2o_vap" 
    798                    long_name="water vapor mass mixing ratio" 
    799                    unit="kg/kg" />
    800             <field id="vmr_h2ovap" 
    801                    long_name="water vapor volume mixing ratio" 
    802                    unit="mol/mol" />
    803             <field id="vmr_h2o_vap" 
    804                    long_name="water vapor volume mixing ratio" 
    805                    unit="mol/mol" />
    806             <field id="num_h2o_vap" 
    807                    long_name="water vapor number density" 
    808                    unit="cm-3" />
    809        
     776            <field id="co2"
     777                   long_name="CO2 mass mixing ratio"
     778                   unit="kg/kg" />
     779            <field id="vmr_co2"
     780                   long_name="CO2 volume mixing ratio"
     781                   unit="mol/mol" />
     782            <field id="num_co2"
     783                   long_name="CO2 number density"
     784                   unit="cm-3" />
     785            <field id="h2o_ice"
     786                   long_name="water ice mass mixing ratio"
     787                   unit="kg/kg" />
     788            <field id="vmr_h2oice"
     789                   long_name="water ice volume mixing ratio"
     790                   unit="mol/mol" />
     791            <field id="vmr_h2o_ice"
     792                   long_name="water ice volume mixing ratio"
     793                   unit="mol/mol" />
     794            <field id="num_h2o_ice"
     795                   long_name="water ice number density"
     796                   unit="cm-3" />
     797            <field id="h2o_vap"
     798                   long_name="water vapor mass mixing ratio"
     799                   unit="kg/kg" />
     800            <field id="vmr_h2ovap"
     801                   long_name="water vapor volume mixing ratio"
     802                   unit="mol/mol" />
     803            <field id="vmr_h2o_vap"
     804                   long_name="water vapor volume mixing ratio"
     805                   unit="mol/mol" />
     806            <field id="num_h2o_vap"
     807                   long_name="water vapor number density"
     808                   unit="cm-3" />
     809
    810810            <!-- tracers (chemistry) -->
    811             <field id="co" 
    812                    long_name="CO mass mixing ratio" 
    813                    unit="kg/kg" />
    814             <field id="vmr_co" 
    815                    long_name="CO volume mixing ratio" 
    816                    unit="mol/mol" />
    817             <field id="num_co" 
    818                    long_name="CO number density" 
    819                    unit="cm-3" />
    820             <field id="o" 
    821                    long_name="O mass mixing ratio" 
    822                    unit="kg/kg" />
    823             <field id="vmr_o" 
    824                    long_name="O volume mixing ratio" 
    825                    unit="mol/mol" />
    826             <field id="num_o" 
    827                    long_name="O number density" 
    828                    unit="cm-3" />
    829             <field id="o1d" 
    830                    long_name="O1d mass mixing ratio" 
    831                    unit="kg/kg" />
    832             <field id="vmr_o1d" 
    833                    long_name="O1d volume mixing ratio" 
    834                    unit="mol/mol" />
    835             <field id="num_o1d" 
    836                    long_name="O1d number density" 
    837                    unit="cm-3" />
    838             <field id="o2" 
    839                    long_name="O2 mass mixing ratio" 
    840                    unit="kg/kg" />
    841             <field id="vmr_o2" 
    842                    long_name="O2 volume mixing ratio" 
    843                    unit="mol/mol" />
    844             <field id="num_o2" 
    845                    long_name="O2 number density" 
    846                    unit="cm-3" />
    847             <field id="o3" 
    848                    long_name="O3 mass mixing ratio" 
    849                    unit="kg/kg" />
    850             <field id="vmr_o3" 
    851                    long_name="O3 volume mixing ratio" 
    852                    unit="mol/mol" />
    853             <field id="num_o3" 
    854                    long_name="O3 number density" 
    855                    unit="cm-3" />
    856             <field id="h" 
    857                    long_name="H mass mixing ratio" 
    858                    unit="kg/kg" />
    859             <field id="vmr_h" 
    860                    long_name="H volume mixing ratio" 
    861                    unit="mol/mol" />
    862             <field id="num_h" 
    863                    long_name="H number density" 
    864                    unit="cm-3" />
    865             <field id="h2" 
    866                    long_name="H2 mass mixing ratio" 
    867                    unit="kg/kg" />
    868             <field id="vmr_h2" 
    869                    long_name="H2 volume mixing ratio" 
    870                    unit="mol/mol" />
    871             <field id="num_h2" 
    872                    long_name="H2 number density" 
    873                    unit="cm-3" />
    874             <field id="oh" 
    875                    long_name="OH mass mixing ratio" 
    876                    unit="kg/kg" />
    877             <field id="vmr_oh" 
    878                    long_name="OH volume mixing ratio" 
    879                    unit="mol/mol" />
    880             <field id="num_oh" 
    881                    long_name="OH number density" 
    882                    unit="cm-3" />
    883             <field id="ho2" 
    884                    long_name="HO2 mass mixing ratio" 
    885                    unit="kg/kg" />
    886             <field id="vmr_ho2" 
    887                    long_name="HO2 volume mixing ratio" 
    888                    unit="mol/mol" />
    889             <field id="num_ho2" 
    890                    long_name="HO2 number density" 
    891                    unit="cm-3" />
    892             <field id="h2o2" 
    893                    long_name="H2O2 mass mixing ratio" 
    894                    unit="kg/kg" />
    895             <field id="vmr_h2o2" 
    896                    long_name="H2O2 volume mixing ratio" 
    897                    unit="mol/mol" />
    898             <field id="num_h2o2" 
    899                    long_name="H2O2 number density" 
    900                    unit="cm-3" />
    901             <field id="n2" 
    902                    long_name="N2 mass mixing ratio" 
    903                    unit="kg/kg" />
    904             <field id="vmr_n2" 
    905                    long_name="N2 volume mixing ratio" 
    906                    unit="mol/mol" />
    907             <field id="num_n2" 
    908                    long_name="N2 number density" 
    909                    unit="cm-3" />
    910             <field id="ar" 
    911                    long_name="Ar mass mixing ratio" 
    912                    unit="kg/kg" />
    913             <field id="vmr_ar" 
    914                    long_name="Ar volume mixing ratio" 
    915                    unit="mol/mol" />
    916             <field id="num_ar" 
    917                    long_name="Ar number density" 
    918                    unit="cm-3" />
    919             <field id="num_n" 
    920                    long_name="N number density" 
    921                    unit="cm-3" />
    922             <field id="num_no" 
    923                    long_name="NO number density" 
    924                    unit="cm-3" />
    925             <field id="num_no2" 
    926                    long_name="NO2 number density" 
    927                    unit="cm-3" />
    928             <field id="num_n2d" 
    929                    long_name="N2d number density" 
    930                    unit="cm-3" />
    931             <field id="ch4" 
    932                    long_name="CH4 mass mixing ratio" 
    933                    unit="kg/kg" />
    934             <field id="vmr_ch4" 
    935                    long_name="CH4 volume mixing ratio" 
    936                    unit="mol/mol" />
    937             <field id="num_ch4" 
    938                    long_name="CH4 number density" 
    939                    unit="cm-3" />
    940             <field id="he" 
    941                    long_name="He mass mixing ratio" 
    942                    unit="kg/kg" />
    943             <field id="vmr_he" 
    944                    long_name="He volume mixing ratio" 
    945                    unit="mol/mol" />
    946             <field id="num_he" 
    947                    long_name="He number density" 
     811            <field id="co"
     812                   long_name="CO mass mixing ratio"
     813                   unit="kg/kg" />
     814            <field id="vmr_co"
     815                   long_name="CO volume mixing ratio"
     816                   unit="mol/mol" />
     817            <field id="num_co"
     818                   long_name="CO number density"
     819                   unit="cm-3" />
     820            <field id="o"
     821                   long_name="O mass mixing ratio"
     822                   unit="kg/kg" />
     823            <field id="vmr_o"
     824                   long_name="O volume mixing ratio"
     825                   unit="mol/mol" />
     826            <field id="num_o"
     827                   long_name="O number density"
     828                   unit="cm-3" />
     829            <field id="o1d"
     830                   long_name="O1d mass mixing ratio"
     831                   unit="kg/kg" />
     832            <field id="vmr_o1d"
     833                   long_name="O1d volume mixing ratio"
     834                   unit="mol/mol" />
     835            <field id="num_o1d"
     836                   long_name="O1d number density"
     837                   unit="cm-3" />
     838            <field id="o2"
     839                   long_name="O2 mass mixing ratio"
     840                   unit="kg/kg" />
     841            <field id="vmr_o2"
     842                   long_name="O2 volume mixing ratio"
     843                   unit="mol/mol" />
     844            <field id="num_o2"
     845                   long_name="O2 number density"
     846                   unit="cm-3" />
     847            <field id="o3"
     848                   long_name="O3 mass mixing ratio"
     849                   unit="kg/kg" />
     850            <field id="vmr_o3"
     851                   long_name="O3 volume mixing ratio"
     852                   unit="mol/mol" />
     853            <field id="num_o3"
     854                   long_name="O3 number density"
     855                   unit="cm-3" />
     856            <field id="h"
     857                   long_name="H mass mixing ratio"
     858                   unit="kg/kg" />
     859            <field id="vmr_h"
     860                   long_name="H volume mixing ratio"
     861                   unit="mol/mol" />
     862            <field id="num_h"
     863                   long_name="H number density"
     864                   unit="cm-3" />
     865            <field id="h2"
     866                   long_name="H2 mass mixing ratio"
     867                   unit="kg/kg" />
     868            <field id="vmr_h2"
     869                   long_name="H2 volume mixing ratio"
     870                   unit="mol/mol" />
     871            <field id="num_h2"
     872                   long_name="H2 number density"
     873                   unit="cm-3" />
     874            <field id="oh"
     875                   long_name="OH mass mixing ratio"
     876                   unit="kg/kg" />
     877            <field id="vmr_oh"
     878                   long_name="OH volume mixing ratio"
     879                   unit="mol/mol" />
     880            <field id="num_oh"
     881                   long_name="OH number density"
     882                   unit="cm-3" />
     883            <field id="ho2"
     884                   long_name="HO2 mass mixing ratio"
     885                   unit="kg/kg" />
     886            <field id="vmr_ho2"
     887                   long_name="HO2 volume mixing ratio"
     888                   unit="mol/mol" />
     889            <field id="num_ho2"
     890                   long_name="HO2 number density"
     891                   unit="cm-3" />
     892            <field id="h2o2"
     893                   long_name="H2O2 mass mixing ratio"
     894                   unit="kg/kg" />
     895            <field id="vmr_h2o2"
     896                   long_name="H2O2 volume mixing ratio"
     897                   unit="mol/mol" />
     898            <field id="num_h2o2"
     899                   long_name="H2O2 number density"
     900                   unit="cm-3" />
     901            <field id="n2"
     902                   long_name="N2 mass mixing ratio"
     903                   unit="kg/kg" />
     904            <field id="vmr_n2"
     905                   long_name="N2 volume mixing ratio"
     906                   unit="mol/mol" />
     907            <field id="num_n2"
     908                   long_name="N2 number density"
     909                   unit="cm-3" />
     910            <field id="ar"
     911                   long_name="Ar mass mixing ratio"
     912                   unit="kg/kg" />
     913            <field id="vmr_ar"
     914                   long_name="Ar volume mixing ratio"
     915                   unit="mol/mol" />
     916            <field id="num_ar"
     917                   long_name="Ar number density"
     918                   unit="cm-3" />
     919            <field id="num_n"
     920                   long_name="N number density"
     921                   unit="cm-3" />
     922            <field id="num_no"
     923                   long_name="NO number density"
     924                   unit="cm-3" />
     925            <field id="num_no2"
     926                   long_name="NO2 number density"
     927                   unit="cm-3" />
     928            <field id="num_n2d"
     929                   long_name="N2d number density"
     930                   unit="cm-3" />
     931            <field id="ch4"
     932                   long_name="CH4 mass mixing ratio"
     933                   unit="kg/kg" />
     934            <field id="vmr_ch4"
     935                   long_name="CH4 volume mixing ratio"
     936                   unit="mol/mol" />
     937            <field id="num_ch4"
     938                   long_name="CH4 number density"
     939                   unit="cm-3" />
     940            <field id="he"
     941                   long_name="He mass mixing ratio"
     942                   unit="kg/kg" />
     943            <field id="vmr_he"
     944                   long_name="He volume mixing ratio"
     945                   unit="mol/mol" />
     946            <field id="num_he"
     947                   long_name="He number density"
    948948                   unit="cm-3" />
    949949
    950950            <!-- ions -->
    951             <field id="num_co2plus" 
    952                    long_name="CO2+ number density" 
    953                    unit="cm-3" />
    954             <field id="num_oplus" 
    955                    long_name="O+ number density" 
    956                    unit="cm-3" />
    957             <field id="num_o2plus" 
    958                    long_name="O2+ number density" 
    959                    unit="cm-3" />
    960             <field id="num_coplus" 
    961                    long_name="CO+ number density" 
    962                    unit="cm-3" />
    963             <field id="num_coplus" 
    964                    long_name="CO+ number density" 
    965                    unit="cm-3" />
    966             <field id="num_cplus" 
    967                    long_name="C+ number density" 
    968                    unit="cm-3" />
    969             <field id="num_nplus" 
    970                    long_name="N+ number density" 
    971                    unit="cm-3" />
    972             <field id="num_noplus" 
    973                    long_name="NO+ number density" 
    974                    unit="cm-3" />
    975             <field id="num_n2plus" 
    976                    long_name="N2+ number density" 
    977                    unit="cm-3" />
    978             <field id="num_hplus" 
    979                    long_name="H+ number density" 
    980                    unit="cm-3" />
    981             <field id="num_hco2plus" 
    982                    long_name="HCO2+ number density" 
    983                    unit="cm-3" />
    984             <field id="num_hcoplus" 
    985                    long_name="HCO+ number density" 
    986                    unit="cm-3" />
    987             <field id="num_h2oplus" 
    988                    long_name="H2O+ number density" 
    989                    unit="cm-3" />
    990             <field id="num_h3oplus" 
    991                    long_name="H3O+ number density" 
    992                    unit="cm-3" />
    993             <field id="num_ohplus" 
    994                    long_name="OH+ number density" 
    995                    unit="cm-3" />
    996             <field id="num_elec" 
    997                    long_name="electron number density" 
     951            <field id="num_co2plus"
     952                   long_name="CO2+ number density"
     953                   unit="cm-3" />
     954            <field id="num_oplus"
     955                   long_name="O+ number density"
     956                   unit="cm-3" />
     957            <field id="num_o2plus"
     958                   long_name="O2+ number density"
     959                   unit="cm-3" />
     960            <field id="num_coplus"
     961                   long_name="CO+ number density"
     962                   unit="cm-3" />
     963            <field id="num_coplus"
     964                   long_name="CO+ number density"
     965                   unit="cm-3" />
     966            <field id="num_cplus"
     967                   long_name="C+ number density"
     968                   unit="cm-3" />
     969            <field id="num_nplus"
     970                   long_name="N+ number density"
     971                   unit="cm-3" />
     972            <field id="num_noplus"
     973                   long_name="NO+ number density"
     974                   unit="cm-3" />
     975            <field id="num_n2plus"
     976                   long_name="N2+ number density"
     977                   unit="cm-3" />
     978            <field id="num_hplus"
     979                   long_name="H+ number density"
     980                   unit="cm-3" />
     981            <field id="num_hco2plus"
     982                   long_name="HCO2+ number density"
     983                   unit="cm-3" />
     984            <field id="num_hcoplus"
     985                   long_name="HCO+ number density"
     986                   unit="cm-3" />
     987            <field id="num_h2oplus"
     988                   long_name="H2O+ number density"
     989                   unit="cm-3" />
     990            <field id="num_h3oplus"
     991                   long_name="H3O+ number density"
     992                   unit="cm-3" />
     993            <field id="num_ohplus"
     994                   long_name="OH+ number density"
     995                   unit="cm-3" />
     996            <field id="num_elec"
     997                   long_name="electron number density"
    998998                   unit="cm-3" />
    999999
    10001000            <!-- Dust cycle parametrization -->
    1001             <field id="reffdust" 
    1002                    long_name="Dust effective radius" 
     1001            <field id="reffdust"
     1002                   long_name="Dust effective radius"
    10031003                   unit="m" />
    1004             <field id="rdust" 
    1005                    long_name="Dust radius" 
     1004            <field id="rdust"
     1005                   long_name="Dust radius"
    10061006                   unit="m" />
    1007             <field id="dustq" 
    1008                    long_name="Dust mass mixing ratio" 
    1009                    unit="kg/kg" />
    1010             <field id="dustN" 
    1011                    long_name="Dust number mixing ratio" 
     1007            <field id="dustq"
     1008                   long_name="Dust mass mixing ratio"
     1009                   unit="kg/kg" />
     1010            <field id="dustN"
     1011                   long_name="Dust number mixing ratio"
    10121012                   unit="part/kg" />
    1013             <field id="dsodust_TES" 
    1014                    long_name="Density scaled extinction opacity of std dust at 9.3um(TES)" 
     1013            <field id="dsodust_TES"
     1014                   long_name="Density scaled extinction opacity of std dust at 9.3um(TES)"
    10151015                   unit="m2.kg-1" />
    1016             <field id="dso_TES" 
    1017                    long_name="Density scaled extinction opacity of all dust at 9.3um(TES)" 
     1016            <field id="dso_TES"
     1017                   long_name="Density scaled extinction opacity of all dust at 9.3um(TES)"
    10181018                   unit="m2.kg-1" />
    1019             <field id="dsodust" 
    1020                    long_name="Density scaled extinction opacity of std dust at 21.6um(MCS)" 
     1019            <field id="dsodust"
     1020                   long_name="Density scaled extinction opacity of std dust at 21.6um(MCS)"
    10211021                   unit="m2.kg-1" />
    1022             <field id="dso" 
    1023                    long_name="Density scaled extinction opacity of all dust at 21.6um(MCS)" 
     1022            <field id="dso"
     1023                   long_name="Density scaled extinction opacity of all dust at 21.6um(MCS)"
    10241024                   unit="m2.kg-1" />
    1025             <field id="aerosol_dust" 
    1026                    long_name="Opacity of background dust" 
    1027                    unit="" />
    1028 
    1029             <field id="reffstormdust" 
    1030                    long_name="Stormdust dust effective radius" 
     1025            <field id="aerosol_dust"
     1026                   long_name="Opacity of background dust"
     1027                   unit="" />
     1028
     1029            <field id="reffstormdust"
     1030                   long_name="Stormdust dust effective radius"
    10311031                   unit="m" />
    1032             <field id="rstormdust" 
    1033                    long_name="Stormdust dust radius" 
     1032            <field id="rstormdust"
     1033                   long_name="Stormdust dust radius"
    10341034                   unit="m" />
    1035             <field id="dsords_TES" 
    1036                    long_name="Density scaled extinction opacity of stormdust at 9.3um(TES)" 
     1035            <field id="dsords_TES"
     1036                   long_name="Density scaled extinction opacity of stormdust at 9.3um(TES)"
    10371037                   unit="m2.kg-1" />
    1038             <field id="dsords" 
    1039                    long_name="Density scaled extinction opacity of stormdust at 21.6um(MCS)" 
     1038            <field id="dsords"
     1039                   long_name="Density scaled extinction opacity of stormdust at 21.6um(MCS)"
    10401040                   unit="m2.kg-1" />
    1041             <field id="rdsdustq" 
    1042                    long_name="Stormdust dust mass mixing ratio" 
    1043                    unit="kg/kg" />
    1044             <field id="rdsdustqmodel" 
    1045                    long_name="Stormdust dust mass mixing ratio" 
    1046                    unit="kg/kg" />
    1047             <field id="rdsdustN" 
    1048                    long_name="Stormdust dust number mixing ratio" 
     1041            <field id="rdsdustq"
     1042                   long_name="Stormdust dust mass mixing ratio"
     1043                   unit="kg/kg" />
     1044            <field id="rdsdustqmodel"
     1045                   long_name="Stormdust dust mass mixing ratio"
     1046                   unit="kg/kg" />
     1047            <field id="rdsdustN"
     1048                   long_name="Stormdust dust number mixing ratio"
    10491049                   unit="part/kg" />
    1050             <field id="rdsdustN" 
    1051                    long_name="Stormdust dust number mixing ratio" 
     1050            <field id="rdsdustN"
     1051                   long_name="Stormdust dust number mixing ratio"
    10521052                   unit="part/kg" />
    1053             <field id="wspeed_stormdust" 
    1054                    long_name="vertical velocity of stormdust" 
     1053            <field id="wspeed_stormdust"
     1054                   long_name="vertical velocity of stormdust"
    10551055                   unit="m/s" />
    1056             <field id="zdqsed_dust_mass" 
    1057                    long_name="sedimentation tendency of background dust mmr" 
     1056            <field id="zdqsed_dust_mass"
     1057                   long_name="sedimentation tendency of background dust mmr"
    10581058                   unit="kg/kg.s-1" />
    1059             <field id="zdqsed_dust_number" 
    1060                    long_name="sedimentation tendency of background dust number" 
     1059            <field id="zdqsed_dust_number"
     1060                   long_name="sedimentation tendency of background dust number"
    10611061                   unit="nbr/kg.s-1" />
    1062             <field id="zdqsed_stormdust_mass" 
    1063                    long_name="sedimentation tendency of stormdust dust mmr" 
     1062            <field id="zdqsed_stormdust_mass"
     1063                   long_name="sedimentation tendency of stormdust dust mmr"
    10641064                   unit="kg/kg.s-1" />
    1065             <field id="aerosol_stormdust" 
    1066                    long_name="Opacity of stormdust dust" 
    1067                    unit="" />
    1068             <field id="rds_lapserate" 
    1069                    long_name="lapse rate in the rocket dust storm" 
     1065            <field id="aerosol_stormdust"
     1066                   long_name="Opacity of stormdust dust"
     1067                   unit="" />
     1068            <field id="rds_lapserate"
     1069                   long_name="lapse rate in the rocket dust storm"
    10701070                   unit="K/m" />
    1071             <field id="rds_deltahr" 
    1072                    long_name="extra heating rate in the rocket dust storm" 
     1071            <field id="rds_deltahr"
     1072                   long_name="extra heating rate in the rocket dust storm"
    10731073                   unit="K/s" />
    10741074
    1075             <field id="topdustq" 
    1076                    long_name="Topdust dust mass mixing ratio" 
    1077                    unit="kg/kg" />
    1078             <field id="topdustN" 
    1079                    long_name="Topdust dust number mixing ratio" 
     1075            <field id="topdustq"
     1076                   long_name="Topdust dust mass mixing ratio"
     1077                   unit="kg/kg" />
     1078            <field id="topdustN"
     1079                   long_name="Topdust dust number mixing ratio"
    10801080                   unit="part/kg" />
    1081             <field id="refftopdust" 
    1082                    long_name="Topdust dust effective radius" 
     1081            <field id="refftopdust"
     1082                   long_name="Topdust dust effective radius"
    10831083                   unit="m" />
    1084             <field id="dsotop_TES" 
    1085                    long_name="Density scaled extinction opacity of topdust at 9.3um(TES)" 
     1084            <field id="dsotop_TES"
     1085                   long_name="Density scaled extinction opacity of topdust at 9.3um(TES)"
    10861086                   unit="m2.kg-1" />
    1087             <field id="dsotop" 
    1088                    long_name="Density scaled extinction opacity of topdust at 21.6um(MCS)" 
     1087            <field id="dsotop"
     1088                   long_name="Density scaled extinction opacity of topdust at 21.6um(MCS)"
    10891089                   unit="m2.kg-1" />
    10901090
    10911091
    10921092            <!-- Water cycle parametrization -->
    1093             <field id="rice" 
    1094                    long_name="Water ice particle size" 
     1093            <field id="rice"
     1094                   long_name="Water ice particle size"
    10951095                   unit="m" />
    1096             <field id="h2o_saturation" 
    1097                    long_name="h2o vapor saturation ratio" 
    1098                    unit="" />
    1099             <field id="watercloud_pdqh2oice" 
    1100                    long_name="pdqcloud_h2o_ice after microphysics" 
     1096            <field id="h2o_saturation"
     1097                   long_name="h2o vapor saturation ratio"
     1098                   unit="" />
     1099            <field id="watercloud_pdqh2oice"
     1100                   long_name="pdqcloud_h2o_ice after microphysics"
    11011101                   unit="kg/kg.s-1" />
    1102             <field id="watercloud_pdqh2ovap" 
    1103                    long_name="pdqcloud_h2o_vap after microphysics" 
     1102            <field id="watercloud_pdqh2ovap"
     1103                   long_name="pdqcloud_h2o_vap after microphysics"
    11041104                   unit="kg/kg.s-1" />
    1105             <field id="watercloud_pdqhdoice" 
    1106                    long_name="pdqcloud_hdo_ice after microphysics" 
     1105            <field id="watercloud_pdqhdoice"
     1106                   long_name="pdqcloud_hdo_ice after microphysics"
    11071107                   unit="kg/kg.s-1" />
    1108             <field id="watercloud_pdqhdovap" 
    1109                    long_name="pdqcloud_hdo_vap after microphysics" 
     1108            <field id="watercloud_pdqhdovap"
     1109                   long_name="pdqcloud_hdo_vap after microphysics"
    11101110                   unit="kg/kg.s-1" />
    1111            
    1112             <field id="zpotcond_inst" 
    1113                    long_name="zpotcond_inst microphysics" 
     1111
     1112            <field id="zpotcond_inst"
     1113                   long_name="zpotcond_inst microphysics"
    11141114                   unit="(kg/kg)" />
    1115             <field id="zpotcond_full" 
    1116                    long_name="zpotcond_full microphysics" 
     1115            <field id="zpotcond_full"
     1116                   long_name="zpotcond_full microphysics"
    11171117                   unit="(kg/kg)" />
    1118             <field id="zpotcond" 
    1119                    long_name="zpotcond microphysics" 
     1118            <field id="zpotcond"
     1119                   long_name="zpotcond microphysics"
    11201120                   unit="(kg/kg)" />
    1121             <field id="count_micro" 
    1122                    long_name="count_micro after microphysics" 
     1121            <field id="count_micro"
     1122                   long_name="count_micro after microphysics"
    11231123                   unit="integer" />
    11241124
    1125             <field id="zdqcloud_ice" 
    1126                    long_name="cloud ice" 
     1125            <field id="zdqcloud_ice"
     1126                   long_name="cloud ice"
    11271127                   unit="kg.m-2.s-1" />
    11281128            <field id="zdqcloud_vap"
     
    11341134
    11351135            <!-- CO2 condensation parametrization -->
    1136             <field id="co2condens_pdtc" 
    1137                    long_name="Temperature tendency due to CO2 condensation" 
     1136            <field id="co2condens_pdtc"
     1137                   long_name="Temperature tendency due to CO2 condensation"
    11381138                   unit="K.s-1" />
    1139            
     1139
    11401140            <!-- Non-orographic GW parametrization -->
    1141             <field id="nonoro_bv" 
    1142                    long_name="Brunt Vaisala frequency in nonoro" 
     1141            <field id="nonoro_bv"
     1142                   long_name="Brunt Vaisala frequency in nonoro"
    11431143                   unit="Hz" />
    1144             <field id="nonoro_u_epflux_tot" 
    1145                    long_name="Total EP Flux along U in nonoro" 
    1146                    unit="" />
    1147             <field id="nonoro_v_epflux_tot" 
    1148                    long_name="Total EP Flux along V in nonoro" 
    1149                    unit="" />
    1150             <field id="du_nonoro_gwd" 
    1151                    long_name="Tendency on U due to nonoro GW" 
     1144            <field id="nonoro_u_epflux_tot"
     1145                   long_name="Total EP Flux along U in nonoro"
     1146                   unit="" />
     1147            <field id="nonoro_v_epflux_tot"
     1148                   long_name="Total EP Flux along V in nonoro"
     1149                   unit="" />
     1150            <field id="du_nonoro_gwd"
     1151                   long_name="Tendency on U due to nonoro GW"
    11521152                   unit="m.s-2" />
    1153             <field id="dv_nonoro_gwd" 
    1154                    long_name="Tendency on V due to nonoro GW" 
    1155                    unit="m.s-2" />       
    1156        
     1153            <field id="dv_nonoro_gwd"
     1154                   long_name="Tendency on V due to nonoro GW"
     1155                   unit="m.s-2" />
     1156
    11571157        </field_group>
    11581158
     
    12071207                   long_name="Soil thermal inertia for slope 07"
    12081208                   unit="J/kg/K" />
    1209             <field id="Waterdensity_soil"
    1210                    long_name="Waterdensity_soil"
    1211                    unit="kg.m-3" />
    1212             <field id="Waterdensity_soil_slope01"
    1213                    long_name="Waterdensity_soil of slope 01"
    1214                    unit="kg.m-3" />
    1215             <field id="Waterdensity_soil_slope02"
    1216                    long_name="Waterdensity_soil of slope 02"
    1217                    unit="kg.m-3" />
    1218             <field id="Waterdensity_soil_slope03"
    1219                    long_name="Waterdensity_soil of slope 03"
    1220                    unit="kg.m-3" />
    1221             <field id="Waterdensity_soil_slope04"
    1222                    long_name="Waterdensity_soil of slope 04"
    1223                    unit="kg.m-3" />
    1224             <field id="Waterdensity_soil_slope05"
    1225                    long_name="Waterdensity_soil of slope 05"
    1226                    unit="kg.m-3" />
    1227             <field id="Waterdensity_soil_slope06"
    1228                    long_name="Waterdensity_soil of slope 06"
    1229                    unit="kg.m-3" />
    1230             <field id="Waterdensity_soil_slope07"
    1231                    long_name="Waterdensity_soil of slope 07"
     1209            <field id="waterdensity_soil"
     1210                   long_name="waterdensity_soil"
     1211                   unit="kg.m-3" />
     1212            <field id="waterdensity_soil_slope01"
     1213                   long_name="waterdensity_soil of slope 01"
     1214                   unit="kg.m-3" />
     1215            <field id="waterdensity_soil_slope02"
     1216                   long_name="waterdensity_soil of slope 02"
     1217                   unit="kg.m-3" />
     1218            <field id="waterdensity_soil_slope03"
     1219                   long_name="waterdensity_soil of slope 03"
     1220                   unit="kg.m-3" />
     1221            <field id="waterdensity_soil_slope04"
     1222                   long_name="waterdensity_soil of slope 04"
     1223                   unit="kg.m-3" />
     1224            <field id="waterdensity_soil_slope05"
     1225                   long_name="waterdensity_soil of slope 05"
     1226                   unit="kg.m-3" />
     1227            <field id="waterdensity_soil_slope06"
     1228                   long_name="waterdensity_soil of slope 06"
     1229                   unit="kg.m-3" />
     1230            <field id="waterdensity_soil_slope07"
     1231                   long_name="waterdensity_soil of slope 07"
    12321232                   unit="kg.m-3" />
    12331233            <field id="zdqsdif_ssi_frost"
  • trunk/LMDZ.MARS/deftank/file_def_physics_mars.xml

    r3106 r3122  
    99        <file id="histins"
    1010              name="Xhistins"
    11               output_freq="12ts" 
     11              output_freq="12ts"
    1212              time_units="days"
    1313              type="one_file"
    1414              enabled=".false.">
    15                    
     15
    1616            <!-- VARS 0D -->
    1717            <field_group operation="instant"
     
    5454        <file id="diurnalave_"
    5555              name="Xdiurnalave_"
    56               output_freq="1d" 
     56              output_freq="1d"
    5757              time_units="days"
    5858              type="one_file"
    5959              enabled=".false.">
    60                    
     60
    6161            <!-- VARS 0D -->
    6262            <field_group operation="average"
     
    8888              time_units="days"
    8989              enabled=".true.">
    90                    
     90
    9191            <!-- VARS 0D -->
    9292            <field_group operation="average"
     
    100100                <field field_ref="ps" />
    101101                <field field_ref="tsurf" />
    102                 <field field_ref="Waterdensity_surface" />
     102                <field field_ref="waterdensity_surface" />
    103103                <field field_ref="h2o_layer1" />
    104104                <field field_ref="co2_layer1" />
     
    118118                         freq_op="1ts">
    119119                <field field_ref="soiltemp" />
    120                 <field field_ref="Waterdensity_soil" />
     120                <field field_ref="waterdensity_soil" />
    121121            </field_group>
    122122        </file>
     
    129129              time_units="days"
    130130              enabled=".false.">
    131                    
    132             <!-- VARS 0D -->
    133             <field_group operation="average"
    134                          freq_op="1ts">
    135                 <field field_ref="Ls" />
    136             </field_group>
    137 
    138             <field_group operation="average"
    139                          freq_op="1ts">
    140                 <field field_ref="area" operation="once" />
    141                 <field field_ref="ps" />
    142                 <field field_ref="tsurf" />
     131
     132            <!-- VARS 0D -->
     133            <field_group operation="average"
     134                         freq_op="1ts">
     135                <field field_ref="Ls" />
     136            </field_group>
     137
     138            <field_group operation="average"
     139                         freq_op="1ts">
     140                <field field_ref="area" operation="once" />
     141                <field field_ref="ps" />
    143142                <field field_ref="tsurf_slope01" />
    144143                <field field_ref="tsurf_slope02" />
     
    148147                <field field_ref="tsurf_slope06" />
    149148                <field field_ref="tsurf_slope07" />
    150                 <field field_ref="Waterdensity_surface" />
    151                 <field field_ref="Waterdensity_surface01" />
    152                 <field field_ref="Waterdensity_surface02" />
    153                 <field field_ref="Waterdensity_surface03" />
    154                 <field field_ref="Waterdensity_surface04" />
    155                 <field field_ref="Waterdensity_surface05" />
    156                 <field field_ref="Waterdensity_surface06" />
    157                 <field field_ref="Waterdensity_surface07" />
     149                <field field_ref="waterdensity_surface01" />
     150                <field field_ref="waterdensity_surface02" />
     151                <field field_ref="waterdensity_surface03" />
     152                <field field_ref="waterdensity_surface04" />
     153                <field field_ref="waterdensity_surface05" />
     154                <field field_ref="waterdensity_surface06" />
     155                <field field_ref="waterdensity_surface07" />
    158156                <field field_ref="h2o_layer1" />
    159157                <field field_ref="co2_layer1" />
     
    172170                <field field_ref="co2ice_slope06" />
    173171                <field field_ref="co2ice_slope07" />
    174                 <field field_ref="h2o_ice_s" />
    175172                <field field_ref="h2o_ice_s_slope01" />
    176173                <field field_ref="h2o_ice_s_slope02" />
     
    180177                <field field_ref="h2o_ice_s_slope06" />
    181178                <field field_ref="h2o_ice_s_slope07" />
    182                 <field field_ref="watercap" />
    183179                <field field_ref="watercap_slope01" />
    184180                <field field_ref="watercap_slope02" />
     
    193189            <field_group operation="average"
    194190                         freq_op="1ts">
    195                 <field field_ref="soiltemp" />
    196191                <field field_ref="soiltemp_slope01" />
    197192                <field field_ref="soiltemp_slope02" />
     
    201196                <field field_ref="soiltemp_slope06" />
    202197                <field field_ref="soiltemp_slope07" />
    203                 <field field_ref="Waterdensity_soil" />
    204                 <field field_ref="Waterdensity_soil_slope01" />
    205                 <field field_ref="Waterdensity_soil_slope02" />
    206                 <field field_ref="Waterdensity_soil_slope03" />
    207                 <field field_ref="Waterdensity_soil_slope04" />
    208                 <field field_ref="Waterdensity_soil_slope05" />
    209                 <field field_ref="Waterdensity_soil_slope06" />
    210                 <field field_ref="Waterdensity_soil_slope07" />
     198                <field field_ref="waterdensity_soil_slope01" />
     199                <field field_ref="waterdensity_soil_slope02" />
     200                <field field_ref="waterdensity_soil_slope03" />
     201                <field field_ref="waterdensity_soil_slope04" />
     202                <field field_ref="waterdensity_soil_slope05" />
     203                <field field_ref="waterdensity_soil_slope06" />
     204                <field field_ref="waterdensity_soil_slope07" />
    211205            </field_group>
    212206        </file>
    213207
    214208    </file_definition>
    215 
  • trunk/LMDZ.MARS/libf/phymars/physiq_mod.F

    r3115 r3122  
    38903890        ENDDO
    38913891
    3892       CALL write_output("Waterdensity_soil",
     3892      CALL write_output("waterdensity_soil",
    38933893     &     "rhowater_soil",'kg.m-3',
    38943894     &     rhowater_soil(:,:,iflat))
    3895       CALL write_output("Waterdensity_surface",
     3895      CALL write_output("waterdensity_surface",
    38963896     &     "rhowater_surface",'kg.m-3',
    38973897     &     rhowater_surf(:,iflat))
    38983898      DO islope = 1,nslope
    38993899        write(str2(1:2),'(i2.2)') islope
    3900         CALL write_output("Waterdensity_soil_slope"//str2,
     3900        CALL write_output("waterdensity_soil_slope"//str2,
    39013901     &     "rhowater_soil_slope"//str2,'kg.m-3',
    39023902     &     rhowater_soil(:,:,islope))
    3903         CALL write_output("Waterdensity_surface"//str2,
     3903        CALL write_output("waterdensity_surface"//str2,
    39043904     &     "rhowater_surface"//str2,'kg.m-3',
    39053905     &     rhowater_surf(:,islope))
Note: See TracChangeset for help on using the changeset viewer.