Changeset 3508


Ignore:
Timestamp:
Nov 8, 2024, 10:57:36 AM (13 days ago)
Author:
afalco
Message:

Pluto: physiq_mod to call write_output, which writes both via XIOS and diagfi routines.
Included xml example files for XIOS.
AF

Location:
trunk/LMDZ.PLUTO
Files:
5 added
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3506 r3508  
    100100      use wxios, only: wxios_context_init, xios_context_finalize
    101101#endif
     102      use write_output_mod, only: write_output
    102103
    103104      implicit none
     
    10381039            inertia_min=minval(inertiedat(ig,:))
    10391040            inertia_max=maxval(inertiedat(ig,:))
    1040             print*, "inertia min max" , inertia_min, inertia_max
    10411041            ! diurnal and annual skin depth
    10421042            diurnal_skin=(inertia_min/volcapa)*sqrt(daysec/pi)
     
    23342334            call wstats(ngrid,trim(noms(iq))//'_col',trim(noms(iq))//'_col',  &
    23352335                        'kg m^-2',2,qcol(1,iq) )
    2336             call wstats(ngrid,trim(noms(iq))//'_reff',trim(noms(iq))//'_reff',&
    2337                         'm',3,reffrad(1,1,iq))
     2336            ! call wstats(ngrid,trim(noms(iq))//'_reff',trim(noms(iq))//'_reff',&
     2337            !             'm',3,reffrad(1,1,iq)) ! bug (2): Subscript #3 of the array REFFRAD has value 2 which is greater than the upper bound of 1
    23382338         end do
    23392339
     
    23572357!------------------------------------------------------------------------------
    23582358
    2359       call writediagfi(ngrid,"Ls","solar longitude","deg",0,zls*180./pi)
    2360       call writediagfi(ngrid,"Lss","sub solar longitude","deg",0,zlss*180./pi)
    2361       call writediagfi(ngrid,"RA","right ascension","deg",0,right_ascen*180./pi)
    2362       call writediagfi(ngrid,"Declin","solar declination","deg",0,declin*180./pi)
    2363       call writediagfi(ngrid,"tsurf","Surface temperature","K",2,tsurf)
    2364       call writediagfi(ngrid,"ps","Surface pressure","Pa",2,ps)
    2365       call writediagfi(ngrid,"emis","Emissivity","",2,emis)
    2366 
    2367       !! Pluto outputs
    2368       call writediagfi(ngrid,"dist_star","dist_star","AU",0,dist_star)
     2359      call write_output("Ls","solar longitude","deg",zls*180./pi)
     2360      ! call write_output("Lss","sub solar longitude","deg",zlss*180./pi)
     2361      call write_output("RA","right ascension","deg",right_ascen*180./pi)
     2362      call write_output("Declin","solar declination","deg",declin*180./pi)
     2363      call write_output("dist_star","dist_star","AU",dist_star)
     2364
     2365      call write_output("tsurf","Surface temperature","K",tsurf)
     2366      call write_output("ps","Surface pressure","Pa",ps)
     2367      call write_output("emis","Emissivity","",emis)
    23692368
    23702369      if (fast) then
    2371          call writediagfi(ngrid,"globave","surf press","Pa",0,globave)
    2372          call writediagfi(ngrid,"fluxrad","fluxrad","W m-2",2,fluxrad)
    2373          call writediagfi(ngrid,"fluxgrd","fluxgrd","W m-2",2,fluxgrd)
    2374          call writediagfi(ngrid,"capcal","capcal","W.s m-2 K-1",2,capcal)
    2375          ! call writediagfi(ngrid,"dplanck","dplanck","W.s m-2 K-1",2,dplanck)
    2376          call writediagfi(ngrid,"tsoil","tsoil","K",3,tsoil)
     2370         call write_output("globave","surf press","Pa",globave)
     2371         call write_output("fluxrad","fluxrad","W m-2",fluxrad)
     2372         call write_output("fluxgrd","fluxgrd","W m-2",fluxgrd)
     2373         call write_output("capcal","capcal","W.s m-2 K-1",capcal)
     2374         ! call write_output("dplanck","dplanck","W.s m-2 K-1",dplanck)
     2375         call write_output("tsoil","tsoil","K",tsoil)
    23772376      else
    23782377         if (check_physics_outputs) then
    23792378            ! Check the validity of updated fields at the end of the physics step
    2380             call check_physics_fields("HERE physiq:", zt, zu, zv, pplev, zq)
    2381          endif
    2382 
    2383          call writediagfi(ngrid,"temp","temperature","K",3,zt)
    2384          call writediagfi(ngrid,"teta","potential temperature","K",3,zh)
    2385          call writediagfi(ngrid,"u","Zonal wind","m.s-1",3,zu)
    2386          call writediagfi(ngrid,"v","Meridional wind","m.s-1",3,zv)
    2387          call writediagfi(ngrid,"w","Vertical wind","m.s-1",3,pw)
    2388          call writediagfi(ngrid,"p","Pressure","Pa",3,pplay)
     2379            call check_physics_fields("physiq:", zt, zu, zv, pplev, zq)
     2380         endif
     2381
     2382         call write_output("zzlay","Midlayer altitude", "m",zzlay(:,:))
     2383         call write_output("zzlev","Interlayer altitude", "m",zzlev(:,1:nlayer))
     2384         !call write_output('pphi','Geopotential',' ',pphi)
     2385
     2386         call write_output("temperature","temperature","K",zt)
     2387         call write_output("teta","potential temperature","K",zh)
     2388         call write_output("u","Zonal wind","m.s-1",zu)
     2389         call write_output("v","Meridional wind","m.s-1",zv)
     2390         call write_output("w","Vertical wind","m.s-1",pw)
     2391         call write_output("p","Pressure","Pa",pplay)
    23892392      endif
    2390 
    2391 !     Subsurface temperatures
    2392 !        call writediagsoil(ngrid,"tsurf","Surface temperature","K",2,tsurf)
    2393 !        call writediagsoil(ngrid,"temp","temperature","K",3,tsoil)
    23942393
    23952394      ! Total energy balance diagnostics
    23962395      if(callrad)then
    2397 
    2398          call writediagfi(ngrid,"ALB","Surface albedo"," ",2,albedo_equivalent)
    2399          call writediagfi(ngrid,"ALB_1st","First Band Surface albedo"," ",2,albedo(:,1))
    2400          call writediagfi(ngrid,"ISR","incoming stellar rad.","W m-2",2,fluxtop_dn)
    2401          call writediagfi(ngrid,"ASR","absorbed stellar rad.","W m-2",2,fluxabs_sw)
    2402          call writediagfi(ngrid,"OLR","outgoing longwave rad.","W m-2",2,fluxtop_lw)
    2403          call writediagfi(ngrid,"shad","rings"," ", 2, fract)
    2404 
    2405 !           call writediagfi(ngrid,"fluxsurfsw","sw surface flux.","W m-2",2,fluxsurf_sw)
    2406 !           call writediagfi(ngrid,"fluxsurflw","lw back radiation.","W m-2",2,fluxsurf_lw)
    2407 
    2408          call writediagfi(ngrid,"GND","heat flux from ground","W m-2",2,fluxgrd)
    2409          ! endif
    2410 
    2411          call writediagfi(ngrid,"DYN","dynamical heat input","W m-2",2,fluxdyn)
    2412 
     2396         call write_output("ALB","Surface albedo"," ",albedo_equivalent)
     2397         call write_output("ASR","absorbed stellar rad.","W m-2",fluxabs_sw)
     2398         call write_output("ISR","incoming stellar rad.","W m-2",fluxtop_dn)
     2399         call write_output("OLR","outgoing longwave rad.","W m-2",fluxtop_lw)
     2400         call write_output("GND","heat flux from ground","W m-2",fluxgrd)
     2401         call write_output("DYN","dynamical heat input","W m-2",fluxdyn)
    24132402      endif ! end of 'callrad'
    24142403
    24152404      if(enertest) then
    24162405         if (calldifv) then
    2417 
    2418             call writediagfi(ngrid,"q2","turbulent kinetic energy","J.kg^-1",3,q2)
    2419             call writediagfi(ngrid,"sensibFlux","sensible heat flux","w.m^-2",2,sensibFlux)
    2420 
    2421 !             call writediagfi(ngrid,"dEzdiff","turbulent diffusion heating (-sensible flux)","w.m^-2",3,dEzdiff)
    2422 !             call writediagfi(ngrid,"dEdiff","integrated turbulent diffusion heating (-sensible flux)","w.m^-2",2,dEdiff)
    2423 !             call writediagfi(ngrid,"dEdiffs","In TurbDiff (correc rad+latent heat) surf nrj change","w.m^-2",2,dEdiffs)
    2424 
     2406            call write_output("q2","turbulent kinetic energy","J.kg^-1",q2)
     2407            call write_output("sensibFlux","sensible heat flux","w.m^-2",sensibFlux)
    24252408         endif
    24262409
    24272410         if (corrk) then
    2428             call writediagfi(ngrid,"dEzradsw","radiative heating","w.m^-2",3,dEzradsw)
    2429             call writediagfi(ngrid,"dEzradlw","radiative heating","w.m^-2",3,dEzradlw)
     2411            call write_output("dEzradsw","radiative heating","w.m^-2",dEzradsw)
     2412            call write_output("dEzradlw","radiative heating","w.m^-2",dEzradlw)
    24302413         endif
    24312414
    24322415         if (generic_condensation) then
    2433             call writediagfi(ngrid,"genericconddE","heat from generic condensation","W m-2",2,genericconddE)
    2434             call writediagfi(ngrid,"dt_generic_condensation","heating from generic condensation","K s-1",3,dt_generic_condensation)
     2416            call write_output("genericconddE","heat from generic condensation","W m-2",genericconddE)
     2417            call write_output("dt_generic_condensation","heating from generic condensation","K s-1",dt_generic_condensation)
    24352418         endif
    24362419
     
    24422425            do nw=1,L_NSPECTV
    24432426               write(str2,'(i2.2)') nw
    2444                call writediagfi(ngrid,'dtauv'//str2,'Layer optical thickness attenuation in VI band '//str2,'',1,int_dtauv(:,nlayer:1:-1,nw))
     2427               call write_output('dtauv'//str2,'Layer optical thickness attenuation in VI band '//str2,'',int_dtauv(:,nlayer:1:-1,nw))
    24452428            enddo
    24462429            do nw=1,L_NSPECTI
    24472430               write(str2,'(i2.2)') nw
    2448                call writediagfi(ngrid,'dtaui'//str2,'Layer optical thickness attenuation in IR band '//str2,'',1,int_dtaui(:,nlayer:1:-1,nw))
     2431               call write_output('dtaui'//str2,'Layer optical thickness attenuation in IR band '//str2,'',int_dtaui(:,nlayer:1:-1,nw))
    24492432            enddo
    24502433         endif
    24512434
    24522435         ! Temporary inclusions for heating diagnostics.
    2453          call writediagfi(ngrid,"zdtsw","SW heating","T s-1",3,zdtsw)
    2454          call writediagfi(ngrid,"zdtlw","LW heating","T s-1",3,zdtlw)
    2455          call writediagfi(ngrid,"dtrad","radiative heating","K s-1",3,dtrad)
    2456          call writediagfi(ngrid,"zdtdyn","Dyn. heating","T s-1",3,zdtdyn)
     2436         call write_output("zdtsw","SW heating","T s-1",zdtsw)
     2437         call write_output("zdtlw","LW heating","T s-1",zdtlw)
     2438         call write_output("dtrad","radiative heating","K s-1",dtrad)
     2439         call write_output("zdtdyn","Dyn. heating","T s-1",zdtdyn)
    24572440
    24582441         ! For Debugging.
    2459          !call writediagfi(ngrid,'rnat','Terrain type',' ',2,real(rnat))
    2460          !call writediagfi(ngrid,'pphi','Geopotential',' ',3,pphi)
     2442         !call write_output('rnat','Terrain type',' ',real(rnat))
    24612443
    24622444      ! Output tracers.
    24632445      if (tracer) then
    2464          ! call writediagfi(ngrid,"zdtc","tendancy T cond N2","K",3,zdtc)
     2446         ! call write_output("zdtc","tendancy T cond N2","K",zdtc)
    24652447
    24662448         do iq=1,nq
    2467             call writediagfi(ngrid,noms(iq),noms(iq),'kg/kg',3,zq(1,1,iq))
    2468             ! call writediagfi(ngrid,trim(noms(iq))//'_surf',trim(noms(iq))//'_surf',  &
    2469          !                    'kg m^-2',2,qsurf_hist(1,iq) )
    2470            call writediagfi(ngrid,trim(noms(iq))//'_col',trim(noms(iq))//'_col',    &
    2471                            'kg m^-2',2,qcol(1,iq) )
    2472             call writediagfi(ngrid,trim(noms(iq))//'_surf',trim(noms(iq))//'_surf',  &
    2473                          'kg m^-2',2,qsurf(1,iq) )
    2474 
    2475             if(generic_condensation)then
    2476                call writediagfi(ngrid,"rneb_generic","GCS cloud fraction (generic condensation)"," ",3,rneb_generic)
    2477                call writediagfi(ngrid,"CLF","GCS cloud fraction"," ",3,cloudfrac)
    2478                call writediagfi(ngrid,"RH_generic","GCS relative humidity"," ",3,RH_generic)
    2479             endif
    2480            ! call writediagfi(ngrid,"tau_col","Total aerosol optical depth","[]",2,tau_col)
     2449            call write_output(noms(iq),noms(iq),'kg/kg',zq(:,:,iq))
     2450            ! call write_output(trim(noms(iq))//'_surf',trim(noms(iq))//'_surf',  &
     2451         !                    'kg m^-2',qsurf_hist(1,iq) )
     2452           call write_output(trim(noms(iq))//'_col',trim(noms(iq))//'_col',    &
     2453                           'kg m^-2',qcol(:,iq) )
     2454            call write_output(trim(noms(iq))//'_surf',trim(noms(iq))//'_surf',  &
     2455                         'kg m^-2',qsurf(:,iq) )
    24812456         enddo ! end of 'nq' loop
    24822457
    24832458         !Pluto specific
    2484          call writediagfi(ngrid,'n2_iceflux','n2_iceflux',"kg m^-2 s^-1",2,flusurf(1,igcm_n2) )
     2459         call write_output('n2_iceflux','n2_iceflux',"kg m^-2 s^-1",flusurf(1,igcm_n2) )
    24852460         if (haze_radproffix)then
    2486             call writediagfi(ngrid,'haze_reff','haze_reff','m',3,reffrad(1,1,1))
     2461            call write_output('haze_reff','haze_reff','m',reffrad(1,1,1))
    24872462         end if
    24882463         if (methane) then
    2489             ! call writediagfi(ngrid,"rice_ch4","ch4 ice mass mean radius","m",3,rice_ch4)
    2490             ! call writediagfi(ngrid,"zq1temp_ch4"," "," ",2,zq1temp_ch4)
    2491             ! call writediagfi(ngrid,"qsat_ch4"," "," ",2,qsat_ch4)
    2492             ! call writediagfi(ngrid,"qsat_ch4_l1"," "," ",2,qsat_ch4_l1)
    2493 
    2494             call writediagfi(ngrid,'ch4_iceflux','ch4_iceflux',&
    2495                               "kg m^-2 s^-1",2,flusurf(1,igcm_ch4_ice) )
    2496             call writediagfi(ngrid,"vmr_ch4","vmr_ch4","%",2,vmr_ch4)
     2464            ! call write_output("rice_ch4","ch4 ice mass mean radius","m",rice_ch4)
     2465            ! call write_output("zq1temp_ch4"," "," ",zq1temp_ch4)
     2466            ! call write_output("qsat_ch4"," "," ",qsat_ch4)
     2467            ! call write_output("qsat_ch4_l1"," "," ",qsat_ch4_l1)
     2468
     2469            call write_output('ch4_iceflux','ch4_iceflux',&
     2470                              "kg m^-2 s^-1",flusurf(1,igcm_ch4_ice) )
     2471            call write_output("vmr_ch4","vmr_ch4","%",vmr_ch4)
    24972472            if (.not.fast) then
    2498                call writediagfi(ngrid,"zrho_ch4","zrho_ch4","kg.m-3",3,zrho_ch4(:,:))
     2473               call write_output("zrho_ch4","zrho_ch4","kg.m-3",zrho_ch4(:,:))
    24992474            endif
    25002475
    25012476            ! Tendancies
    2502             call writediagfi(ngrid,"zdqcn2_ch4","zdq condn2 ch4","",&
    2503                            3,zdqc(:,:,igcm_ch4_gas))
    2504             call writediagfi(ngrid,"zdqdif_ch4","zdqdif ch4","",&
    2505                            3,zdqdif(:,:,igcm_ch4_gas))
    2506             call writediagfi(ngrid,"zdqsdif_ch4_ice","zdqsdif ch4","",&
    2507                            2,zdqsdif(:,igcm_ch4_ice))
    2508             call writediagfi(ngrid,"zdqadj_ch4","zdqadj ch4","",&
    2509                            3,zdqadj(:,:,igcm_ch4_gas))
     2477            call write_output("zdqcn2_ch4","zdq condn2 ch4","",&
     2478                           zdqc(:,:,igcm_ch4_gas))
     2479            call write_output("zdqdif_ch4","zdqdif ch4","",&
     2480                           zdqdif(:,:,igcm_ch4_gas))
     2481            call write_output("zdqsdif_ch4_ice","zdqsdif ch4","",&
     2482                           zdqsdif(:,igcm_ch4_ice))
     2483            call write_output("zdqadj_ch4","zdqadj ch4","",&
     2484                           zdqadj(:,:,igcm_ch4_gas))
    25102485            if (sedimentation) then
    2511                call writediagfi(ngrid,"zdqsed_ch4","zdqsed ch4","",&
    2512                               3,zdqsed(:,:,igcm_ch4_gas))
    2513                call writediagfi(ngrid,"zdqssed_ch4","zdqssed ch4","",&
    2514                               2,zdqssed(:,igcm_ch4_gas))
     2486               call write_output("zdqsed_ch4","zdqsed ch4","",&
     2487                              zdqsed(:,:,igcm_ch4_gas))
     2488               call write_output("zdqssed_ch4","zdqssed ch4","",&
     2489                              zdqssed(:,igcm_ch4_gas))
    25152490            endif
    25162491            if (metcloud.and.(.not.fast)) then
    2517                call writediagfi(ngrid,"zdtch4cloud","ch4 cloud","T s-1",&
    2518                            3,zdtch4cloud)
    2519                call writediagfi(ngrid,"zdqch4cloud","ch4 cloud","T s-1",&
    2520                            3,zdqch4cloud(1,1,igcm_ch4_gas))
     2492               call write_output("zdtch4cloud","ch4 cloud","T s-1",&
     2493                           zdtch4cloud)
     2494               call write_output("zdqch4cloud","ch4 cloud","T s-1",&
     2495                           zdqch4cloud(1,1,igcm_ch4_gas))
    25212496            endif
    25222497
     
    25242499
    25252500         if (carbox) then
    2526             ! call writediagfi(ngrid,"zdtcocloud","tendancy T cocloud","K",3,zdtcocloud)
    2527             call writediagfi(ngrid,'co_iceflux','co_iceflux',&
    2528                                "kg m^-2 s^-1",2,flusurf(1,igcm_co_ice) )
    2529             call writediagfi(ngrid,"vmr_co","vmr_co","%",2,vmr_co)
     2501            ! call write_output("zdtcocloud","tendancy T cocloud","K",zdtcocloud)
     2502            call write_output('co_iceflux','co_iceflux',&
     2503                               "kg m^-2 s^-1",flusurf(1,igcm_co_ice) )
     2504            call write_output("vmr_co","vmr_co","%",vmr_co)
    25302505            if (.not.fast) THEN
    2531                call writediagfi(ngrid,"zrho_co","zrho_co","kg.m-3",3,zrho_co(:,:))
     2506               call write_output("zrho_co","zrho_co","kg.m-3",zrho_co(:,:))
    25322507            endif
    25332508         endif
    25342509
    25352510         if (haze) then
    2536    !         call writediagfi(ngrid,"zrho_haze","zrho_haze","kg.m-3",3,zrho_haze(:,:))
    2537             call writediagfi(ngrid,"zdqrho_photprec","zdqrho_photprec",&
    2538                         "kg.m-3.s-1",3,zdqrho_photprec(:,:))
    2539             call writediagfi(ngrid,"zdqphot_prec","zdqphot_prec","",&
    2540                                                 3,zdqphot_prec(:,:))
    2541             call writediagfi(ngrid,"zdqhaze_ch4","zdqhaze_ch4","",&
    2542                      3,zdqhaze(:,:,igcm_ch4_gas))
    2543             call writediagfi(ngrid,"zdqhaze_prec","zdqhaze_prec","",&
    2544                      3,zdqhaze(:,:,igcm_prec_haze))
     2511   !         call write_output("zrho_haze","zrho_haze","kg.m-3",zrho_haze(:,:))
     2512            call write_output("zdqrho_photprec","zdqrho_photprec",&
     2513                        "kg.m-3.s-1",zdqrho_photprec(:,:))
     2514            call write_output("zdqphot_prec","zdqphot_prec","",&
     2515                                                zdqphot_prec(:,:))
     2516            call write_output("zdqhaze_ch4","zdqhaze_ch4","",&
     2517                     zdqhaze(:,:,igcm_ch4_gas))
     2518            call write_output("zdqhaze_prec","zdqhaze_prec","",&
     2519                     zdqhaze(:,:,igcm_prec_haze))
    25452520            if (igcm_haze.ne.0) then
    2546                call writediagfi(ngrid,"zdqhaze_haze","zdqhaze_haze","",&
    2547                         3,zdqhaze(:,:,igcm_haze))
     2521               call write_output("zdqhaze_haze","zdqhaze_haze","",&
     2522                        zdqhaze(:,:,igcm_haze))
    25482523               if (sedimentation) then
    2549                   call writediagfi(ngrid,"zdqssed_haze","zdqssed haze",&
    2550                      "kg/m2/s",2,zdqssed(:,igcm_haze))
     2524                  call write_output("zdqssed_haze","zdqssed haze",&
     2525                     "kg/m2/s",zdqssed(:,igcm_haze))
    25512526               endif
    25522527            endif
    2553             call writediagfi(ngrid,"zdqphot_ch4","zdqphot_ch4","",&
    2554                                                 3,zdqphot_ch4(:,:))
    2555             call writediagfi(ngrid,"zdqconv_prec","zdqconv_prec","",&
    2556                                                 3,zdqconv_prec(:,:))
    2557    !         call writediagfi(ngrid,"zdqhaze_col","zdqhaze col","kg/m2/s",
    2558    !     &                   2,zdqhaze_col(:))
     2528            call write_output("zdqphot_ch4","zdqphot_ch4","",&
     2529                                                zdqphot_ch4(:,:))
     2530            call write_output("zdqconv_prec","zdqconv_prec","",&
     2531                                                zdqconv_prec(:,:))
     2532   !         call write_output("zdqhaze_col","zdqhaze col","kg/m2/s",
     2533   !     &                   zdqhaze_col(:))
    25592534         endif
    25602535
    25612536         if (aerohaze) then
    2562             call writediagfi(ngrid,"tau_col",&
    2563                "Total aerosol optical depth","opacity",2,tau_col)
     2537            call write_output("tau_col",&
     2538               "Total aerosol optical depth","opacity",tau_col)
    25642539         endif
    25652540
Note: See TracChangeset for help on using the changeset viewer.