Changeset 2545 for trunk/LMDZ.MARS/libf/phymars
- Timestamp:
- Jul 8, 2021, 4:00:21 PM (3 years ago)
- Location:
- trunk/LMDZ.MARS/libf/phymars
- Files:
-
- 4 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/libf/phymars/iniwrite.F
r1621 r2545 10 10 USE regular_lonlat_mod, ONLY: lon_reg, lat_reg 11 11 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev 12 use phyetat0_mod, only: tab_cntrl_mod 12 13 IMPLICIT NONE 13 14 … … 41 42 c Local: 42 43 c ------ 43 INTEGER length,l44 parameter (length = 100)45 REAL tab_cntrl(length) ! run parameters are stored in this array44 ! INTEGER length,l 45 ! parameter (length = 100) 46 ! REAL tab_cntrl(length) ! run parameters are stored in this array 46 47 INTEGER ierr 47 48 REAl,ALLOCATABLE :: lon_reg_ext(:) ! extended longitudes … … 61 62 ENDIF 62 63 63 DO l=1,length64 tab_cntrl(l)=0.65 ENDDO66 tab_cntrl(1) = real(nbp_lon)67 tab_cntrl(2) = real(nbp_lat-1)68 tab_cntrl(3) = real(nbp_lev)69 tab_cntrl(4) = real(idayref)70 tab_cntrl(5) = rad71 tab_cntrl(6) = omeg72 tab_cntrl(7) = g73 tab_cntrl(8) = mugaz74 tab_cntrl(9) = rcp75 tab_cntrl(10) = daysec76 tab_cntrl(11) = dtphys64 ! DO l=1,length 65 ! tab_cntrl(l)=0. 66 ! ENDDO 67 ! tab_cntrl(1) = real(nbp_lon) 68 ! tab_cntrl(2) = real(nbp_lat-1) 69 ! tab_cntrl(3) = real(nbp_lev) 70 ! tab_cntrl(4) = real(idayref) 71 ! tab_cntrl(5) = rad 72 ! tab_cntrl(6) = omeg 73 ! tab_cntrl(7) = g 74 ! tab_cntrl(8) = mugaz 75 ! tab_cntrl(9) = rcp 76 ! tab_cntrl(10) = daysec 77 ! tab_cntrl(11) = dtphys 77 78 ! tab_cntrl(12) = etot0 78 79 ! tab_cntrl(13) = ptot0 … … 81 82 ! tab_cntrl(16) = ang0 82 83 83 tab_cntrl(27) = hour_ini84 ! tab_cntrl(27) = hour_ini 84 85 c 85 86 c .......... P.Le Van ( ajout le 8/04/96 ) ......... … … 110 111 ierr = NF_REDEF (nid) 111 112 112 ierr = NF_DEF_DIM (nid, "index", length, idim_index)113 ierr = NF_DEF_DIM (nid, "index", SIZE(tab_cntrl_mod), idim_index) 113 114 ! ierr = NF_DEF_DIM (nid, "rlonu", iip1, idim_rlonu) 114 115 ierr = NF_DEF_DIM (nid, "latitude", nbp_lat, idim_rlatu) … … 138 139 ierr = NF_ENDDEF(nid) 139 140 #ifdef NC_DOUBLE 140 ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,tab_cntrl )141 #else 142 ierr = NF_PUT_VAR_REAL (nid,nvarid,tab_cntrl )141 ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,tab_cntrl_mod) 142 #else 143 ierr = NF_PUT_VAR_REAL (nid,nvarid,tab_cntrl_mod) 143 144 #endif 144 145 -
trunk/LMDZ.MARS/libf/phymars/phyetat0_mod.F90
r2417 r2545 2 2 3 3 implicit none 4 real,save :: tab_cntrl_mod(100) 4 5 5 6 contains … … 342 343 DEALLOCATE(time) 343 344 endif ! of if Time not found in file 345 346 call ini_tab_controle_dyn_xios(day_ini) 347 344 348 else 345 349 indextime = 1 … … 664 668 end subroutine phyetat0 665 669 670 671 subroutine ini_tab_controle_dyn_xios(idayref) 672 673 USE comcstfi_h, only: g, mugaz, omeg, rad, rcp 674 USE time_phylmdz_mod, ONLY: hour_ini, daysec, dtphys 675 USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev 676 IMPLICIT NONE 677 678 679 INTEGER*4,intent(in) :: idayref ! date (initial date for this run) 680 681 682 INTEGER length,l 683 parameter (length = 100) 684 REAL tab_cntrl(length) ! run parameters are stored in this array 685 686 DO l=1,length 687 tab_cntrl(l)=0. 688 ENDDO 689 tab_cntrl(1) = real(nbp_lon) 690 tab_cntrl(2) = real(nbp_lat-1) 691 tab_cntrl(3) = real(nbp_lev) 692 tab_cntrl(4) = real(idayref) 693 tab_cntrl(5) = rad 694 tab_cntrl(6) = omeg 695 tab_cntrl(7) = g 696 tab_cntrl(8) = mugaz 697 tab_cntrl(9) = rcp 698 tab_cntrl(10) = daysec 699 tab_cntrl(11) = dtphys 700 701 tab_cntrl(27) = hour_ini 702 703 tab_cntrl_mod = tab_cntrl 704 705 end subroutine ini_tab_controle_dyn_xios 706 666 707 end module phyetat0_mod -
trunk/LMDZ.MARS/libf/phymars/physiq_mod.F
r2544 r2545 74 74 use compute_dtau_mod, only: compute_dtau 75 75 use nonoro_gwd_ran_mod, only: nonoro_gwd_ran 76 use check_fields_mod, only: check_physics_fields77 76 #ifdef MESOSCALE 78 77 use comsoil_h, only: mlayer,layer … … 83 82 & planetwide_sumval 84 83 use phyredem, only: physdem0, physdem1 85 use phyetat0_mod, only: phyetat0 84 use phyetat0_mod, only: phyetat0, tab_cntrl_mod 86 85 use eofdump_mod, only: eofdump 87 86 USE vertical_layers_mod, ONLY: ap,bp,aps,bps,presnivs,pseudoalt … … 97 96 #endif 98 97 USE mod_grid_phy_lmdz, ONLY: grid_type, unstructured 99 use ioipsl_getin_p_mod, only: getin_p100 98 101 99 IMPLICIT NONE … … 398 396 REAL mdusttot(ngrid) ! Total mass of dust tracer (kg/m2) 399 397 REAL icetot(ngrid) ! Total mass of water ice (kg/m2) 400 REAL mtotco2 (ngrid)! Total mass of co2, including ice at the surface (kg/m2)401 REAL vaptotco2 (ngrid)! Total mass of co2 vapor (kg/m2)402 REAL icetotco2 (ngrid)! Total mass of co2 ice (kg/m2)398 REAL mtotco2 ! Total mass of co2, including ice at the surface (kg/m2) 399 REAL vaptotco2 ! Total mass of co2 vapor (kg/m2) 400 REAL icetotco2 ! Total mass of co2 ice (kg/m2) 403 401 REAL Nccntot(ngrid) ! Total number of ccn (nbr/m2) 404 402 REAL NccnCO2tot(ngrid) ! Total number of ccnCO2 (nbr/m2) … … 436 434 REAL dsotop(ngrid,nlayer) ! density scaled opacity for topdust 437 435 436 REAL nccnco2(ngrid,nlayer) ! true n ccnco2 (kg/kg) 437 REAL qccnco2(ngrid,nlayer) ! true q ccnco2 (kg/kg) 438 438 439 439 c Test 1d/3d scavenging … … 509 509 integer iloop 510 510 511 ! flags to trigger extra sanity checks 512 logical,save :: check_physics_inputs=.false. 513 logical,save :: check_physics_outputs=.false. 511 ! LOGICAL startphy_file 514 512 515 513 c======================================================================= … … 522 520 523 521 IF (firstcall) THEN 524 525 call getin_p("check_physics_inputs",check_physics_inputs)526 call getin_p("check_physics_outputs",check_physics_outputs)527 522 528 523 c variables set to 0 … … 741 736 ENDIF ! (end of "if firstcall") 742 737 743 if (check_physics_inputs) then744 ! Check the validity of input fields coming from the dynamics745 call check_physics_fields("begin physiq:",pt,pu,pv,pplev)746 endif747 748 738 c --------------------------------------------------- 749 739 c 1.2 Initializations done at every physical timestep: … … 1665 1655 pdt(1:ngrid,1:nlayer) = 1666 1656 & pdt(1:ngrid,1:nlayer) + 1667 & zdtcloudco2(1:ngrid,1:nlayer) 1657 & zdtcloudco2(1:ngrid,1:nlayer)! --> in co2condens 1668 1658 1669 1659 … … 1960 1950 $ zdtc,zdtsurfc,pdpsrf,zduc,zdvc,zdqc, 1961 1951 $ fluxsurf_sw,zls, 1962 $ zdqssed_co2,zcondicea_co2microp) 1952 $ zdqssed_co2,zcondicea_co2microp, 1953 & zdtcloudco2) 1963 1954 ! no scavenging yet 1964 1955 zdqsc(:,:) = 0. … … 1971 1962 $ fluxsurf_sw,zls, 1972 1963 $ zdqssed_co2,zcondicea_co2microp, 1973 & zd qsc)1964 & zdtcloudco2,zdqsc) 1974 1965 DO iq=1, nq 1975 1966 DO ig=1,ngrid … … 1977 1968 ENDDO ! (ig) 1978 1969 ENDDO ! (iq) 1979 end if ! co2clouds1970 end if 1980 1971 DO l=1,nlayer 1981 1972 DO ig=1,ngrid … … 2422 2413 endif !(rdstorm) 2423 2414 2415 if (co2clouds) then 2416 do ig=1,ngrid 2417 nccnco2(ig,:) = 2418 & zq(ig,:,igcm_ccnco2_number)*tauscaling(ig) 2419 qccnco2(ig,:) = 2420 & zq(ig,:,igcm_ccnco2_mass)*tauscaling(ig) 2421 enddo 2422 endif ! of if (co2clouds) 2424 2423 2425 2424 if (water) then … … 2518 2517 2519 2518 endif ! of if (water) 2520 2521 2522 if (co2clouds) then2523 mtotco2(1:ngrid) = 0.2524 icetotco2(1:ngrid) = 0.2525 vaptotco2(1:ngrid) = 0.2526 do ig=1,ngrid2527 do l=1,nlayer2528 vaptotco2(ig) = vaptotco2(ig) +2529 & zq(ig,l,igcm_co2) *2530 & (zplev(ig,l) - zplev(ig,l+1)) / g2531 icetotco2(ig) = icetot(ig) +2532 & zq(ig,l,igcm_co2_ice) *2533 & (zplev(ig,l) - zplev(ig,l+1)) / g2534 end do2535 mtotco2(ig) = icetotco2(ig) + vaptotco2(ig)2536 end do2537 end if2538 2519 endif ! of if (tracer) 2539 2520 #ifndef MESOSCALE … … 2660 2641 2661 2642 endif ! of if (water) 2662 2663 if (co2clouds) then 2664 call wstats(ngrid,"mtotco2", 2665 & "total mass atm of co2","kg/m2", 2666 & 2,mtotco2) 2667 call wstats(ngrid,"icetotco2", 2668 & "total mass atm of co2 ice","kg/m2", 2669 & 2,icetotco2) 2670 call wstats(ngrid,"vaptotco2", 2671 & "total mass atm of co2 vapor","kg/m2", 2672 & 2,icetotco2) 2673 end if 2643 2674 2644 2675 2645 if (dustbin.ne.0) then … … 2954 2924 2955 2925 if (tracer.and.(igcm_co2.ne.0)) then 2926 ! call WRITEDIAGFI(ngrid,"co2_l1","co2 mix. ratio in 1st layer", 2927 ! & "kg/kg",2,zq(1,1,igcm_co2)) 2956 2928 call WRITEDIAGFI(ngrid,"co2","co2 mass mixing ratio", 2957 & "kg .kg-1",3,zq(:,:,igcm_co2))2929 & "kg/kg",3,zq(:,:,igcm_co2)) 2958 2930 2959 2931 if (co2clouds) then 2960 call WRITEDIAGFI(ngrid,'ccnqco2','CCNco2 mmr', 2961 & 'kg.kg-1',3,zq(:,:,igcm_ccnco2_mass)) 2932 call WRITEDIAGFI(ngrid,'zdtcloudco2', 2933 & 'temperature variation of CO2 latent heat', 2934 & 'K/s',3,zdtcloudco2) 2935 2936 call WRITEDIAGFI(ngrid,'ccnqco2','CCNco2 mass mr', 2937 & 'kg/kg',3,qccnco2) 2962 2938 2963 2939 call WRITEDIAGFI(ngrid,'ccnNco2','CCNco2 number', 2964 & 'part.kg-1',3,zq(:,:,igcm_ccnco2_number)) 2965 2966 call WRITEDIAGFI(ngrid,'co2_ice','co2_ice mmr in atm', 2967 & 'kg.kg-1', 3, zq(:,:,igcm_co2_ice)) 2968 2969 call WRITEDIAGFI(ngrid,"mtotco2","total mass atm of co2", 2970 & "kg.m-2",2, mtotco2) 2971 call WRITEDIAGFI(ngrid,"icetotco2","total mass atm of co2 ice", 2972 & "kg.m-2", 2, icetotco2) 2973 call WRITEDIAGFI(ngrid,"vaptotco2","total mass atm of co2 2974 & vapor","kg.m-2", 2, vaptotco2) 2975 call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2, 2976 & emis) 2940 & 'part/kg',3,nccnco2) 2941 2942 call WRITEDIAGFI(ngrid,'co2_ice','co2_ice','kg/kg', 2943 & 3,zq(:,:,igcm_co2_ice)) 2944 2945 call WRITEDIAGFI(ngrid,'precip_co2_ice', 2946 & 'surface deposition of co2 ice', 2947 & 'kg.m-2.s-1',2, 2948 & zdqssed(1:ngrid,igcm_co2_ice)) 2977 2949 end if ! of if (co2clouds) 2978 2950 end if ! of if (tracer.and.(igcm_co2.ne.0)) … … 3794 3766 rave2=max(rave2/max(totrave2,1.e-30),1.e-30) 3795 3767 CALL WRITEDIAGFI(ngrid,'rmoym', 3796 & 'reffice',3768 & 'reffice', 3797 3769 & 'm',0,rave2) 3798 3770 … … 3829 3801 3830 3802 ENDIF ! of IF (water) 3831 3803 3804 3805 ! co2clouds 3806 if (co2clouds) then 3807 call WRITEDIAGFI(ngrid,'zdtcloudco2', 3808 & 'temperature variation of CO2 latent heat', 3809 & 'K/s',3,zdtcloudco2) 3810 call WRITEDIAGFI(ngrid,"emis","Surface emissivity","w.m-1",2, 3811 & emis) 3812 3813 end if 3814 3832 3815 ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc 3833 3816 ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc … … 3864 3847 & '%',0,(co2totA-co2totB)/co2totA) 3865 3848 endif ! of if (igcm_co2_ice.ne.0) 3866 3867 3849 ! XIOS outputs 3868 3850 #ifdef CPP_XIOS … … 3870 3852 ! <field id="..." /> in context_lmdz_physics.xml to be correctly used) 3871 3853 CALL send_xios_field("ls",zls*180./pi) 3854 3855 CALL send_xios_field("controle",tab_cntrl_mod,1) 3856 3857 CALL send_xios_field("ap",ap,1) 3858 CALL send_xios_field("bp",bp,1) 3859 CALL send_xios_field("aps",aps,1) 3860 CALL send_xios_field("bps",bps,1) 3861 3862 CALL send_xios_field("phisinit",phisfi) 3863 3864 ! ap,bp (interlayer),aps,bps (altitude) 3872 3865 3873 3866 CALL send_xios_field("ps",ps) … … 3882 3875 CALL send_xios_field("co2ice",co2ice) 3883 3876 3884 CALL send_xios_field("temp erature",zt)3877 CALL send_xios_field("temp",zt) 3885 3878 CALL send_xios_field("u",zu) 3886 3879 CALL send_xios_field("v",zv) 3887 3880 3881 CALL send_xios_field("rho",rho) 3882 ! Orographic Gravity waves tendencies 3883 if (calllott) then 3884 CALL send_xios_field("dugw",zdugw/ptimestep) 3885 CALL send_xios_field("dvgw",zdvgw/ptimestep) 3886 CALL send_xios_field("dtgw",zdtgw/ptimestep) 3887 endif 3888 3888 !CREATE IF CO2CYCLE 3889 3889 if (tracer.and.(igcm_co2.ne.0)) then 3890 3890 CALL send_xios_field("co2",zq(:,:,igcm_co2)) 3891 3891 endif 3892 ! Water cycle 3893 if (water) then 3894 CALL send_xios_field("watercap",watercap) 3895 !CALL send_xios_field("watercaptag",watercaptag) 3896 CALL send_xios_field("mtot",mtot) 3897 CALL send_xios_field("icetot",icetot) 3898 if (igcm_h2o_vap.ne.0 .and. igcm_h2o_ice.ne.0) then 3899 CALL send_xios_field("h2o_vap",zq(:,:,igcm_h2o_vap)) 3900 CALL send_xios_field("h2o_ice",zq(:,:,igcm_h2o_ice)) 3901 endif 3902 endif 3903 if (.not.activice) then 3904 ! CALL send_xios_field("tauTESap",tauTES) 3905 else 3906 CALL send_xios_field("tauTES",taucloudtes) 3907 endif 3908 3909 CALL send_xios_field("h2o_ice_s",qsurf(:,igcm_h2o_ice)) 3910 3892 3911 3893 3912 if (lastcall.and.is_omp_master) then … … 3897 3916 #endif 3898 3917 3899 if (check_physics_outputs) then3900 ! Check the validity of updated fields at the end of the physics step3901 call check_physics_fields("end of physiq:",zt,zu,zv,zplev)3902 endif3903 3918 3904 3919 icount=icount+1 -
trunk/LMDZ.MARS/libf/phymars/xios_output_mod.F90
r2514 r2545 11 11 12 12 INTERFACE send_xios_field 13 MODULE PROCEDURE histwrite0d_xios,histwrite 2d_xios,histwrite3d_xios13 MODULE PROCEDURE histwrite0d_xios,histwrite1d_xios,histwrite2d_xios,histwrite3d_xios 14 14 END INTERFACE 15 15 … … 57 57 CALL xios_set_axis_attr("altitude", n_glo=size(pseudoalt), value=pseudoalt,& 58 58 unit="km",positive="up") 59 CALL xios_set_axis_attr("interlayer", n_glo=size(pseudoalt)+1,& 60 unit="km",positive="up") 59 61 IF (prt_level>=10) WRITE(lunout,*) "initialize_xios_output: call xios_set_axis_attr for soil" 60 62 CALL xios_set_axis_attr("soil_layers", n_glo=size(mlayer), value=mlayer,& … … 194 196 195 197 IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite0d_xios ',trim(field_name) 196 197 198 !$OMP MASTER 198 199 CALL xios_send_field(field_name,field) … … 202 203 203 204 END SUBROUTINE histwrite0d_xios 205 206 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 207 208 SUBROUTINE histwrite1d_xios(field_name,field,dimens) 209 USE xios, ONLY: xios_send_field 210 USE print_control_mod, ONLY: prt_level, lunout 211 IMPLICIT NONE 212 213 CHARACTER(LEN=*), INTENT(IN) :: field_name 214 REAL, DIMENSION(:), INTENT(IN) :: field 215 INTEGER, INTENT(IN) :: dimens 216 IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite1d_xios ',trim(field_name) 217 !$OMP MASTER 218 CALL xios_send_field(field_name,field) 219 !$OMP END MASTER 220 221 IF (prt_level >= 10) WRITE(lunout,*)'End histrwrite1d_xios ',trim(field_name) 222 223 END SUBROUTINE histwrite1d_xios 204 224 205 225 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 221 241 222 242 IF (prt_level >= 10) WRITE(lunout,*)'Begin histrwrite2d_xios ',trim(field_name) 223 224 243 IF (SIZE(field)/=klon) CALL abort_physic('iophy::histwrite2d_xios','Field first DIMENSION not equal to klon',1) 225 244
Note: See TracChangeset
for help on using the changeset viewer.