Changeset 1943 for trunk/LMDZ.TITAN/libf
- Timestamp:
- Jun 4, 2018, 11:59:42 AM (7 years ago)
- Location:
- trunk/LMDZ.TITAN/libf/phytitan
- Files:
-
- 5 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.TITAN/libf/phytitan/chem_settings.F90
r1903 r1943 1 SUBROUTINE chem_settings(nid,ngrid, indextime)1 SUBROUTINE chem_settings(nid,ngrid,nlayer,indextime) 2 2 3 3 ! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 18 18 19 19 USE comchem_h 20 21 20 USE iostart, only: get_field, get_var, inquire_dimension_length 22 21 USE callkeys_mod, only : callchim 22 23 USE vertical_layers_mod, only: presnivs, pseudoalt 23 24 24 25 IMPLICIT NONE … … 29 30 INTEGER,INTENT(IN) :: nid ! Input Netcdf file ID 30 31 INTEGER,INTENT(IN) :: ngrid ! # of horizontal grid points 32 INTEGER,INTENT(IN) :: nlayer ! # of vertical layers 31 33 INTEGER,INTENT(IN) :: indextime ! position on time axis 32 34 !====================================================================== 33 35 ! local variables: 36 REAL :: phi0, phi 37 34 38 INTEGER :: ierr ! status (returned by NetCDF functions) 35 39 INTEGER :: nvarid ! ID of NetCDF variable 36 40 INTEGER :: dimid ! ID of NetCDF dimension 37 41 38 INTEGER :: i q42 INTEGER :: ilay, iq 39 43 40 44 LOGICAL :: found … … 59 63 WRITE(*,*) "chem_settings: Upper chemistry pressure grid <preskim> range:", & 60 64 maxval(preskim), minval(preskim) 65 66 ! 3. Compute others chemistry grid 67 68 ! a. Total pressure grid (0->1300km) 69 DO ilay=1,nlayer ! GCM levels 70 preskim_tot(ilay) = presnivs(ilay) 71 ENDDO 72 DO ilay=1,nlaykim_up ! Upper chemistry 73 preskim_tot(ilay+nlayer) = preskim(ilay) 74 ENDDO 75 76 ! b. Pseudo-altitudes ( TBD - hydrostatic equilibrium or read somewhere ?) 61 77 62 ! 3. Inquire ( and load ) upper chemistry composition fields78 ! 4. Inquire ( and load ) upper chemistry composition fields 63 79 64 80 CALL get_field("H_up",ykim_up(1,:,:),found,indextime) … … 73 89 74 90 DEALLOCATE(ykim_up) ! it will be useless 91 DEALLOCATE(ykim_tot) ! it will be useless 75 92 76 93 ELSE -
trunk/LMDZ.TITAN/libf/phytitan/comchem_h.F90
r1908 r1943 78 78 79 79 REAL,SAVE,ALLOCATABLE,DIMENSION(:) :: preskim ! Pressure (Pa) of upper chemistry (mid)-layers 80 REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: zlay _kim ! Altitude (km) of allchemistry (mid)-layers80 REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: zlaykim ! Pseudo-altitude (km) of upper chemistry (mid)-layers 81 81 REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_up ! Upper chemistry fields (mol/mol) 82 !$OMP_THREADPRIVATE(preskim,zlay_kim,ykim_up) 83 84 82 83 ! These "_tot" fields are for output only 84 REAL,SAVE,ALLOCATABLE,DIMENSION(:) :: preskim_tot ! Pressure (Pa) of total chemistry (mid)-layers 85 REAL,SAVE,ALLOCATABLE,DIMENSION(:,:) :: zlaykim_tot ! Pseudo-altitude (km) of total chemistry (mid)-layers 86 REAL,SAVE,ALLOCATABLE,DIMENSION(:,:,:) :: ykim_tot ! Total chemistry fields (mol/mol) 87 88 !$OMP_THREADPRIVATE(preskim,zlaykim,ykim_up) 89 !$OMP_THREADPRIVATE(preskim_tot,zlaykim_tot,ykim_tot) 85 90 86 91 ! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ … … 116 121 117 122 IF (.NOT.allocated(preskim)) ALLOCATE(preskim(nlaykim_up)) 118 IF (.NOT.allocated(zlay _kim)) ALLOCATE(zlay_kim(ngrid,nlaykim_tot))123 IF (.NOT.allocated(zlaykim)) ALLOCATE(zlaykim(ngrid,nlaykim_up)) 119 124 IF (.NOT.allocated(ykim_up)) ALLOCATE(ykim_up(nkim,ngrid,nlaykim_up)) 125 126 IF (.NOT.allocated(preskim_tot)) ALLOCATE(preskim_tot(nlaykim_tot)) 127 IF (.NOT.allocated(zlaykim_tot)) ALLOCATE(zlaykim_tot(ngrid,nlaykim_tot)) 128 IF (.NOT.allocated(ykim_tot)) ALLOCATE(ykim_tot(nkim,ngrid,nlaykim_tot)) 120 129 121 130 END SUBROUTINE ini_comchem_h -
trunk/LMDZ.TITAN/libf/phytitan/phyetat0_mod.F90
r1894 r1943 274 274 ! Call to soil_settings, in order to read upper chemistry 275 275 ! pressure grid as well as composition fields 276 call chem_settings(nid_start,ngrid, indextime)276 call chem_settings(nid_start,ngrid,nlayer,indextime) 277 277 endif ! of if (startphy_file) 278 278 -
trunk/LMDZ.TITAN/libf/phytitan/physiq_mod.F90
r1927 r1943 17 17 use radcommon_h, only: sigma, glat, grav, BWNV 18 18 use surfdat_h, only: phisfi, zmea, zstd, zsig, zgam, zthe 19 use comchem_h, only: nkim, cnames 19 use comchem_h, only: nkim, cnames, nlaykim_up, ykim_up, ykim_tot 20 20 use comdiurn_h, only: coslat, sinlat, coslon, sinlon 21 21 use comsaison_h, only: mu0, fract, dist_star, declin, right_ascen … … 1593 1593 ! Chemical tracers 1594 1594 if (callchim) then 1595 1596 ! Advected fields 1595 1597 do iq=1,nkim 1596 CALL send_xios_field( cnames(iq),zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) !mol/mol1598 CALL send_xios_field(trim(cnames(iq)),zq(:,:,iq+nmicro)/rat_mmol(iq+nmicro)) ! kg/kg -> mol/mol 1597 1599 enddo 1598 endif 1600 1601 ! Upper chemistry fields 1602 do iq=1,nkim 1603 CALL send_xios_field(trim(cnames(iq))//"_up",ykim_up(iq,:,:)) ! mol/mol 1604 enddo 1605 1606 ! Append fields in ykim_tot for output on the total vertical grid (0->1300km) 1607 do iq=1,nkim 1608 1609 ! GCM levels 1610 do l=1,nlayer 1611 ykim_tot(iq,:,l) = zq(:,l,iq+nmicro)/rat_mmol(iq+nmicro) 1612 enddo 1613 ! Upper levels 1614 do l=1,nlaykim_up 1615 ykim_tot(iq,:,nlayer+l) = ykim_up(iq,:,l) 1616 enddo 1617 1618 CALL send_xios_field(trim(cnames(iq))//"_tot",ykim_tot(iq,:,:)) ! mol/mol 1619 1620 enddo 1621 1622 endif ! of 'if callchim' 1599 1623 1600 1624 ! Microphysical tracers -
trunk/LMDZ.TITAN/libf/phytitan/xios_output_mod.F90
r1896 r1943 35 35 #endif 36 36 USE wxios, ONLY: wxios_domain_param, wxios_domain_param_unstructured, wxios_closedef 37 38 USE comchem_h, ONLY: preskim, preskim_tot, zlaykim, zlaykim_tot 39 37 40 IMPLICIT NONE 38 41 … … 45 48 46 49 50 INTEGER :: i 47 51 INTEGER :: data_ibegin, data_iend 48 52 TYPE(xios_duration) :: timestep … … 60 64 CALL xios_set_axis_attr("altitude", n_glo=size(pseudoalt), value=pseudoalt,& 61 65 unit="km",positive="up") 66 67 IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim" 68 CALL xios_set_axis_attr("preskim", n_glo=size(preskim), value=preskim,& 69 unit="Pa",positive="down") 70 71 IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for preskim_tot" 72 CALL xios_set_axis_attr("preskim_tot", n_glo=size(preskim_tot), value=preskim_tot,& 73 unit="Pa",positive="down") 74 75 ! Calculation of pseudo-altitudes is still to be done 76 !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim" 77 !CALL xios_set_axis_attr("zlaykim", n_glo=size(preskim), value=preskim,& 78 ! unit="km",positive="up") 79 ! 80 !IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for zlaykim_tot" 81 !CALL xios_set_axis_attr("zlaykim_tot", n_glo=size(zlaykim_tot), value=zlaykim_tot,& 82 ! unit="km",positive="up") 83 62 84 63 85 ! 2. Declare horizontal domain
Note: See TracChangeset
for help on using the changeset viewer.