Changeset 3092


Ignore:
Timestamp:
Oct 18, 2023, 3:35:24 PM (12 months ago)
Author:
jbclement
Message:

Marc PCM:

  • Correction of a bug in "writediagfi.F": the case of using the 1D model with parallelization was not anticipated so that the "diagfi.nc" file was filled with NaNf?;
  • Addition of the file "start1D.txt" as an example in the directory deftank/;
  • Some "cosmetic" modifications in "improvedclouds_mod.F", "write_output_mod.F90" and "testphys1d.F90".

JBC

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

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.MARS/changelog.txt

    r3078 r3092  
    42574257is correctly handled (i.e. on lon-lat grid outputs polar mesh area must
    42584258be adjusted to account for the replicated polar meshes).
    4259  
     4259
     4260== 10/10/2023 == EM+JBC
     4261Follow-up of r3078 which broke the 1D model.
     4262Also added initialisation of non-oro GW tendencies stored in startfi.nc when in 1D.
     4263
     4264== 18/10/2023 == JBC
     4265    - Correction of a bug in "writediagfi.F": the case of using the 1D model with parallelization was not anticipated so that the "diagfi.nc" file was filled with NaNf;
     4266    - Addition of the file "start1D.txt" as an example in the directory deftank/;
     4267    - Some "cosmetic" modifications in "improvedclouds_mod.F", "write_output_mod.F90" and "testphys1d.F90".
  • trunk/LMDZ.MARS/libf/phymars/dyn1d/testphys1d.F90

    r3074 r3092  
    3434!   and a file describing the sigma layers (e.g. "z2sig.def")
    3535!
    36 !   author: Frederic Hourdin, R.Fournier,F.Forget
     36!   author: Frederic Hourdin, R. Fournier, F. Forget
    3737!   -------
    3838!
     
    9090real, dimension(1)      :: latitude, longitude, cell_area
    9191logical                 :: there
    92 character(len = 2)      :: str2
    93 character(len = 7)      :: str7
    94 character(len = 44)     :: txt
     92character(2)            :: str2
     93character(7)            :: str7
     94character(44)           :: txt
    9595
    9696! RV & JBC: Use of starting files for 1D
  • trunk/LMDZ.MARS/libf/phymars/improvedclouds_mod.F

    r3075 r3092  
    613613      print*, 'count is ',countcells, ' i.e. ',
    614614     &     countcells*100/(nlay*ngrid), '% for microphys computation'
    615 
    616 #ifndef MESOSCALE
    617 !      IF (ngrid.ne.1) THEN ! 3D
    618 !         call WRITEDIAGFI(ngrid,"satu","ratio saturation","",3,
    619 !     &                    satu_out)
    620 !         call WRITEDIAGFI(ngrid,"dM","ccn variation","kg/kg",3,
    621 !     &                    dM_out)
    622 !         call WRITEDIAGFI(ngrid,"dN","ccn variation","#",3,
    623 !     &                    dN_out)
    624 !         call WRITEDIAGFI(ngrid,"error","dichotomy max error","%",2,
    625 !     &                    error2d)
    626 !         call WRITEDIAGFI(ngrid,"zqsat","zqsat","kg",3,
    627 !     &                    zqsat)
    628 !      ENDIF
    629 
    630 !      IF (ngrid.eq.1) THEN ! 1D
    631 !         call WRITEDIAGFI(ngrid,"error","incertitude sur glace","%",1,
    632 !     &                    error_out)
    633          call WRITEdiagfi(ngrid,"resist","resistance","s/m2",1,
    634      &                    res_out)
    635          call WRITEdiagfi(ngrid,"satu_bf","satu before","kg/kg",1,
    636      &                    satubf)
    637          call WRITEdiagfi(ngrid,"satu_af","satu after","kg/kg",1,
    638      &                    satuaf)
    639          call WRITEdiagfi(ngrid,"vapbf","h2ovap before","kg/kg",1,
    640      &                    zq0(1,1,igcm_h2o_vap))
    641          call WRITEdiagfi(ngrid,"vapaf","h2ovap after","kg/kg",1,
    642      &                    zq(1,1,igcm_h2o_vap))
    643          call WRITEdiagfi(ngrid,"icebf","h2oice before","kg/kg",1,
    644      &                    zq0(1,1,igcm_h2o_ice))
    645          call WRITEdiagfi(ngrid,"iceaf","h2oice after","kg/kg",1,
    646      &                    zq(1,1,igcm_h2o_ice))
    647          call WRITEdiagfi(ngrid,"ccnbf","ccn before","/kg",1,
    648      &                    zq0(1,1,igcm_ccn_number))
    649          call WRITEdiagfi(ngrid,"ccnaf","ccn after","/kg",1,
    650      &                    zq(1,1,igcm_ccn_number))
    651 c         call WRITEDIAGFI(ngrid,"growthrate","growth rate","m^2/s",1,
    652 c     &                    gr_out)
    653 c         call WRITEDIAGFI(ngrid,"nuclearate","nucleation rate","",1,
    654 c     &                    rate_out)
    655 c         call WRITEDIAGFI(ngrid,"dM","ccn variation","kg",1,
    656 c     &                    dM_out)
    657 c         call WRITEDIAGFI(ngrid,"dN","ccn variation","#",1,
    658 c     &                    dN_out)
    659          call WRITEdiagfi(ngrid,"zqsat","p vap sat","kg/kg",1,
    660      &                    zqsat)
    661 !         call WRITEDIAGFI(ngrid,"satu","ratio saturation","",1,
    662 !     &                    satu_out)
    663          call WRITEdiagfi(ngrid,"rice","ice radius","m",1,
    664      &                    rice)
    665 !         call WRITEDIAGFI(ngrid,"rdust_sca","rdust","m",1,
    666 !     &                    rdust)
    667 !         call WRITEDIAGFI(ngrid,"rsedcloud","rsedcloud","m",1,
    668 !     &                    rsedcloud)
    669 !         call WRITEDIAGFI(ngrid,"rhocloud","rhocloud","kg.m-3",1,
    670 !     &                    rhocloud)
    671 !      ENDIF
    672 #endif
    673615     
    674616      ENDIF ! endif test_flag
  • trunk/LMDZ.MARS/libf/phymars/write_output_mod.F90

    r3055 r3092  
    11MODULE write_output_mod
    2     IMPLICIT NONE
     2
     3IMPLICIT NONE
     4
    35PRIVATE
    4    
    5     INTERFACE write_output
    6       MODULE PROCEDURE write_output_d0,write_output_d1,write_output_d2, &
    7                        write_output_i0,write_output_i1,write_output_i2, &
    8                        write_output_l0,write_output_l1,write_output_l2
    9 
    10     END INTERFACE write_output
    11 
    12     PUBLIC write_output
    13    
     6
     7INTERFACE write_output
     8    MODULE PROCEDURE write_output_d0, write_output_d1, write_output_d2, &
     9                     write_output_i0, write_output_i1, write_output_i2, &
     10                     write_output_l0, write_output_l1, write_output_l2
     11END INTERFACE write_output
     12
     13PUBLIC write_output
     14
     15!----------------------------------------------------------------------
    1416CONTAINS
     17!----------------------------------------------------------------------
    1518
    1619  SUBROUTINE write_output_d0(field_name,title,units,field)
     
    2831  CHARACTER(LEN=*),INTENT(IN)    :: units
    2932  REAL,INTENT(IN)                :: field
    30  
     33
    3134  call writediagfi(ngrid,field_name,title,units,0,field)
    32 #ifdef CPP_XIOS 
     35#ifdef CPP_XIOS
    3336  if (xios_is_active_field(field_name)) then
    3437    ! only send the field to xios if the user asked for it
     
    3639  endif
    3740#endif
    38  
     41
    3942  END SUBROUTINE write_output_d0
    4043
     44!----------------------------------------------------------------------
     45
    4146  SUBROUTINE write_output_d1(field_name,title,units,field)
    4247  ! For a surface field
     
    5358  CHARACTER(LEN=*),INTENT(IN)    :: units
    5459  REAL,INTENT(IN)                :: field(:)
    55  
     60
    5661  call writediagfi(ngrid,field_name,title,units,2,field)
    57 #ifdef CPP_XIOS 
     62#ifdef CPP_XIOS
    5863  if (xios_is_active_field(field_name)) then
    5964    ! only send the field to xios if the user asked for it
     
    6166  endif
    6267#endif
    63  
     68
    6469  END SUBROUTINE write_output_d1
     70
     71!----------------------------------------------------------------------
    6572
    6673  SUBROUTINE write_output_d2(field_name,title,units,field)
     
    8390  if(size(field(:,:),2).eq.nsoilmx) then
    8491    call writediagsoil(ngrid,field_name,title,units,3,field)
    85   else 
     92  else
    8693    call writediagfi(ngrid,field_name,title,units,3,field(:,:))
    8794  endif
    88 #ifdef CPP_XIOS 
     95#ifdef CPP_XIOS
    8996  if (xios_is_active_field(field_name)) then
    9097    ! only send the field to xios if the user asked for it
     
    9299  endif
    93100#endif
    94  
     101
    95102  END SUBROUTINE write_output_d2
    96103
     104!----------------------------------------------------------------------
     105
    97106  SUBROUTINE write_output_i0(field_name,title,units,field)
    98107  ! For a surface field
     
    109118  CHARACTER(LEN=*),INTENT(IN)    :: units
    110119  INTEGER,INTENT(IN)             :: field
    111  
     120
    112121  call writediagfi(ngrid,field_name,title,units,0,real(field))
    113 #ifdef CPP_XIOS 
     122#ifdef CPP_XIOS
    114123  if (xios_is_active_field(field_name)) then
    115124    ! only send the field to xios if the user asked for it
     
    117126  endif
    118127#endif
    119  
     128
    120129  END SUBROUTINE write_output_i0
    121130
     131!----------------------------------------------------------------------
     132
    122133  SUBROUTINE write_output_i1(field_name,title,units,field)
    123134  ! For a surface field
     
    134145  CHARACTER(LEN=*),INTENT(IN)    :: units
    135146  INTEGER,INTENT(IN)             :: field(:)
    136  
     147
    137148  call writediagfi(ngrid,field_name,title,units,2,real(field))
    138 #ifdef CPP_XIOS 
     149#ifdef CPP_XIOS
    139150  if (xios_is_active_field(field_name)) then
    140151    ! only send the field to xios if the user asked for it
     
    142153  endif
    143154#endif
    144  
     155
    145156  END SUBROUTINE write_output_i1
     157
     158!----------------------------------------------------------------------
    146159
    147160  SUBROUTINE write_output_i2(field_name,title,units,field)
     
    164177  if(size(field(:,:),2).eq.nsoilmx) then
    165178    call writediagsoil(ngrid,field_name,title,units,3,real(field))
    166   else 
     179  else
    167180    call writediagfi(ngrid,field_name,title,units,3,real(field(:,:)))
    168181  endif
    169 #ifdef CPP_XIOS 
     182#ifdef CPP_XIOS
    170183  if (xios_is_active_field(field_name)) then
    171184    ! only send the field to xios if the user asked for it
     
    173186  endif
    174187#endif
    175  
     188
    176189  END SUBROUTINE write_output_i2
     190
     191!----------------------------------------------------------------------
    177192
    178193  SUBROUTINE write_output_l0(field_name,title,units,field)
     
    195210  field_real=0
    196211  if(field) field_real=1
    197  
     212
    198213  call writediagfi(ngrid,field_name,title,units,0,field_real)
    199 #ifdef CPP_XIOS 
     214#ifdef CPP_XIOS
    200215  if (xios_is_active_field(field_name)) then
    201216    ! only send the field to xios if the user asked for it
     
    203218  endif
    204219#endif
    205  
     220
    206221  END SUBROUTINE write_output_l0
     222
     223!----------------------------------------------------------------------
    207224
    208225  SUBROUTINE write_output_l1(field_name,title,units,field)
     
    228245    if(field(i)) field_real(i)=1.
    229246  ENDDO
    230  
     247
    231248  call writediagfi(ngrid,field_name,title,units,2,field_real(:))
    232 #ifdef CPP_XIOS 
     249#ifdef CPP_XIOS
    233250  if (xios_is_active_field(field_name)) then
    234251    ! only send the field to xios if the user asked for it
     
    236253  endif
    237254#endif
    238  
     255
    239256  END SUBROUTINE write_output_l1
     257
     258!----------------------------------------------------------------------
    240259
    241260  SUBROUTINE write_output_l2(field_name,title,units,field)
     
    270289  if(size(field(:,:),2).eq.nsoilmx) then
    271290    call writediagsoil(ngrid,field_name,title,units,3,field_real)
    272   else 
     291  else
    273292    call writediagfi(ngrid,field_name,title,units,3,field_real(:,:))
    274293  endif
    275294
    276 #ifdef CPP_XIOS 
     295#ifdef CPP_XIOS
    277296  if (xios_is_active_field(field_name)) then
    278297    ! only send the field to xios if the user asked for it
     
    280299  endif
    281300#endif
    282  
     301
    283302  deallocate(field_real)
    284303
  • trunk/LMDZ.MARS/libf/phymars/writediagfi.F

    r2900 r3092  
    312312        if (dim.eq.3) then
    313313
     314          IF (klon_glo>1) THEN ! General case
    314315#ifdef CPP_PARA
    315316          ! Gather field on a "global" (without redundant longitude) array
     
    327328!         Passage variable physique -->  variable dynamique
    328329!         recast (copy) variable from physics grid to dynamics grid
    329           IF (klon_glo>1) THEN ! General case
    330330           DO l=1,nbp_lev
    331331             DO i=1,nbp_lon+1
     
    341341             ENDDO
    342342           ENDDO
     343#endif
    343344          ELSE ! 1D model case
    344345           dx3_1d(1,1:nbp_lev)=px(1,1:nbp_lev)
    345346          ENDIF
    346 #endif
    347347!         Ecriture du champs
    348348
     
    416416        else if (dim.eq.2) then
    417417
     418          IF (klon_glo>1) THEN ! General case
    418419#ifdef CPP_PARA
    419420          ! Gather field on a "global" (without redundant longitude) array
     
    433434!         Passage variable physique -->  physique dynamique
    434435!         recast (copy) variable from physics grid to dynamics grid
    435           IF (klon_glo>1) THEN ! General case
    436436             DO i=1,nbp_lon+1
    437437                dx2(i,1)=px(1,1)
     
    445445                dx2(nbp_lon+1,j)=dx2(1,j)
    446446             ENDDO
     447#endif
    447448          ELSE ! 1D model case
    448449            dx2_1d=px(1,1)
    449450          ENDIF
    450 #endif
    451451
    452452          if (is_master) then
Note: See TracChangeset for help on using the changeset viewer.