Ignore:
Timestamp:
Oct 19, 2023, 4:02:57 PM (9 months ago)
Author:
idelkadi
Message:

Merged trunk changes -r4488:4726 LMDZ_ECRad branch

Location:
LMDZ6/branches/LMDZ_ECRad
Files:
34 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/LMDZ_ECRad

  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/advn.F

    r2603 r4727  
    146146      IMPLICIT NONE
    147147c
    148 #include "dimensions.h"
    149 #include "paramet.h"
    150 #include "iniprint.h"
     148      INCLUDE "dimensions.h"
     149      INCLUDE "paramet.h"
     150      INCLUDE "iniprint.h"
    151151c
    152152c
     
    263263      IMPLICIT NONE
    264264c
    265 #include "dimensions.h"
    266 #include "paramet.h"
    267 #include "iniprint.h"
     265      INCLUDE "dimensions.h"
     266      INCLUDE "paramet.h"
     267      INCLUDE "iniprint.h"
    268268c
    269269c
     
    359359      IMPLICIT NONE
    360360c
    361 #include "dimensions.h"
    362 #include "paramet.h"
    363 #include "iniprint.h"
     361      INCLUDE "dimensions.h"
     362      INCLUDE "paramet.h"
     363      INCLUDE "iniprint.h"
    364364c
    365365c
     
    746746      IMPLICIT NONE
    747747c
    748 #include "dimensions.h"
    749 #include "paramet.h"
    750 #include "comgeom.h"
    751 #include "iniprint.h"
     748      INCLUDE "dimensions.h"
     749      INCLUDE "paramet.h"
     750      INCLUDE "comgeom.h"
     751      INCLUDE "iniprint.h"
    752752c
    753753c
     
    877877      IMPLICIT NONE
    878878c
    879 #include "dimensions.h"
    880 #include "paramet.h"
    881 #include "comgeom.h"
    882 #include "iniprint.h"
     879      INCLUDE "dimensions.h"
     880      INCLUDE "paramet.h"
     881      INCLUDE "comgeom.h"
     882      INCLUDE "iniprint.h"
    883883c
    884884c
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/advz.F

    r2600 r4727  
    2424      include "paramet.h"
    2525
    26 C    #include "traceur.h"
     26C     INCLUDE "traceur.h"
    2727
    2828C  Arguments :
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/comconst_mod.F90

    r2597 r4727  
    2626      INTEGER iflag_top_bound ! sponge type
    2727      INTEGER ngroup ! parameter to group points (along longitude) near poles
     28      REAL maxlatfilter ! maximum latitude (in degrees) above which filter is active
    2829      INTEGER mode_top_bound  ! sponge mode
    2930      REAL tau_top_bound ! inverse of sponge characteristic time scale (Hz)
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/convflu.F

    r1945 r4727  
    2020      IMPLICIT NONE
    2121c
    22 #include "dimensions.h"
    23 #include "paramet.h"
     22      INCLUDE "dimensions.h"
     23      INCLUDE "paramet.h"
    2424      REAL       xflu,yflu,convfl,convpn,convps
    2525      INTEGER    l,ij,nbniv
     
    3030c
    3131c
    32 #include "comgeom.h"
     32      INCLUDE "comgeom.h"
    3333c
    3434      DO 5 l = 1,nbniv
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/diagedyn.F

    r2239 r4727  
    5757      IMPLICIT NONE
    5858C
    59 #include "dimensions.h"
    60 #include "paramet.h"
    61 #include "comgeom.h"
    62 #include "iniprint.h"
     59      INCLUDE "dimensions.h"
     60      INCLUDE "paramet.h"
     61      INCLUDE "comgeom.h"
     62      INCLUDE "iniprint.h"
    6363
    6464!#ifdef CPP_EARTH
    65 !#include "../phylmd/YOMCST.h"
    66 !#include "../phylmd/YOETHF.h"
     65!      INCLUDE "../phylmd/YOMCST.h"
     66!      INCLUDE "../phylmd/YOETHF.h"
    6767!#endif
    6868! Ehouarn: for now set these parameters to what is in Earth physics...
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/diverg.F

    r1945 r4727  
    2222c
    2323c   ---------------------------------------------------------------------
    24 #include "dimensions.h"
    25 #include "paramet.h"
    26 #include "comgeom.h"
     24      INCLUDE "dimensions.h"
     25      INCLUDE "paramet.h"
     26      INCLUDE "comgeom.h"
    2727c
    2828c    ..........          variables en arguments    ...................
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/diverg_gam.F

    r1945 r4727  
    2323c
    2424c   ---------------------------------------------------------------------
    25 #include "dimensions.h"
    26 #include "paramet.h"
    27 #include "comgeom.h"
     25      INCLUDE "dimensions.h"
     26      INCLUDE "paramet.h"
     27      INCLUDE "comgeom.h"
    2828c
    2929c    ..........          variables en arguments    ...................
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/divergf.F

    r1945 r4727  
    2222c
    2323c   ---------------------------------------------------------------------
    24 #include "dimensions.h"
    25 #include "paramet.h"
    26 #include "comgeom.h"
     24      INCLUDE "dimensions.h"
     25      INCLUDE "paramet.h"
     26      INCLUDE "comgeom.h"
    2727c
    2828c    ..........          variables en arguments    ...................
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/divergst.F

    r1945 r4727  
    1717c   -------------------------------------------------------------------
    1818c
    19 #include "dimensions.h"
    20 #include "paramet.h"
    21 #include "comgeom.h"
     19      INCLUDE "dimensions.h"
     20      INCLUDE "paramet.h"
     21      INCLUDE "comgeom.h"
    2222
    2323      INTEGER klevel
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/divgrad2.F

    r1945 r4727  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "comgeom2.h"
    20 #include "comdissipn.h"
     17      INCLUDE "dimensions.h"
     18      INCLUDE "paramet.h"
     19      INCLUDE "comgeom2.h"
     20      INCLUDE "comdissipn.h"
    2121
    2222c    .......    variables en arguments   .......
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/fxy.F

    r2598 r4727  
    2727     , rlonm025(iip1),xprimm025(iip1), rlonp025(iip1),xprimp025(iip1)
    2828
    29 #include "fxy_new.h"
     29      INCLUDE "fxy_new.h"
    3030
    3131
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/fxysinus.F

    r2597 r4727  
    1616c
    1717c
    18 #include "dimensions.h"
    19 #include "paramet.h"
     18      INCLUDE "dimensions.h"
     19      INCLUDE "paramet.h"
    2020
    2121       INTEGER i,j
     
    2626     , rlonm025(iip1),xprimm025(iip1), rlonp025(iip1),xprimp025(iip1)
    2727
    28 #include "fxy_sin.h"
     28      INCLUDE "fxy_sin.h"
    2929
    3030
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/gr_u_scal.F

    r1945 r4727  
    3030c   ---------------
    3131
    32 #include "dimensions.h"
    33 #include "paramet.h"
    34 #include "comgeom.h"
     32      INCLUDE "dimensions.h"
     33      INCLUDE "paramet.h"
     34      INCLUDE "comgeom.h"
    3535
    3636c   Arguments:
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/gr_v_scal.F

    r1945 r4727  
    3030c   ---------------
    3131
    32 #include "dimensions.h"
    33 #include "paramet.h"
    34 #include "comgeom.h"
     32      INCLUDE "dimensions.h"
     33      INCLUDE "paramet.h"
     34      INCLUDE "comgeom.h"
    3535
    3636c   Arguments:
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/grad.F

    r1945 r4727  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
     17      INCLUDE "dimensions.h"
     18      INCLUDE "paramet.h"
    1919      INTEGER klevel
    2020      REAL  pg( ip1jmp1,klevel )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/gradiv2.F

    r1945 r4727  
    1818      IMPLICIT NONE
    1919c
    20 #include "dimensions.h"
    21 #include "paramet.h"
    22 #include "comgeom.h"
    23 #include "comdissipn.h"
     20      INCLUDE "dimensions.h"
     21      INCLUDE "paramet.h"
     22      INCLUDE "comgeom.h"
     23      INCLUDE "comdissipn.h"
    2424c
    2525c     ........    variables en arguments      ........
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/infotrac.F90

    r4488 r4727  
    3636!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    3737!  | water in different |    water tagging      |  water isotopes | other tracers | additional tracers moments |
    38 !  | phases: H2O_[gls] |      isotopes         |                 |               |  for higher order schemes  |
     38!  | phases: H2O_[glsb] |      isotopes         |                 |               |  for higher order schemes  |
    3939!  |--------------------+-----------------------+-----------------+---------------+----------------------------|
    4040!  |                    |                       |                 |               |                            |
     
    6565!  | longName    | Long name (with adv. scheme suffix) for outputs      | ttext       |                        |
    6666!  | type        | Type (so far: tracer or tag)                         | /           | tracer,tag             |
    67 !  | phase       | Phases list ("g"as / "l"iquid / "s"olid)             | /           | [g][l][s]              |
     67!  | phase       | Phases list ("g"as / "l"iquid / "s"olid / "b"lowing) | /           | [g][l][s][b]           |
    6868!  | component   | Name(s) of the merged/cumulated section(s)           | /           | coma-separated names   |
    6969!  | iGeneration | Generation (>=1)                                     | /           |                        |
     
    9191!  | trac   | ntiso  | Isotopes + tagging tracers list + number         | / | ntraciso       |                 |
    9292!  | zone   | nzone  | Geographic tagging zones   list + number         | / | ntraceurs_zone |                 |
    93 !  | phase  | nphas  | Phases                     list + number         |                    | [g][l][s], 1:3 |
     93!  | phase  | nphas  | Phases                     list + number         |                    |[g][l][s][b],1:4 |
    9494!  | iqIsoPha        | Index in "qx"           = f(name(1:ntiso)),phas) | iqiso              | 1:nqtot         |
    9595!  | itZonIso        | Index in "trac(1:ntiso)"= f(zone, name(1:niso))  | index_trac         | 1:ntiso         |
     
    162162   TYPE(trac_type), POINTER             :: t1, t(:)
    163163   INTEGER :: ierr
     164   CHARACTER(LEN=maxlen),   ALLOCATABLE :: types_trac(:)  !--- Keyword for tracers type(s), parsed version
    164165
    165166   CHARACTER(LEN=*), PARAMETER :: modname="init_infotrac"
     
    175176   CALL msg('type_trac = "'//TRIM(type_trac)//'"', modname)
    176177
     178   lerr=strParse(type_trac, '|', types_trac, n=nt)
     179   IF (nt .GT. 1) THEN
     180      IF (nt .GT. 2) CALL abort_gcm(modname, 'you need to modify type_trac, this version is not supported by lmdz', 1)
     181      if (nt .EQ. 2) type_trac=types_trac(2)
     182   ENDIF
     183
     184
     185   
    177186   !--- MESSAGE ABOUT THE CHOSEN CONFIGURATION
    178187   msg1 = 'For type_trac = "'//TRIM(type_trac)//'":'
     
    227236      nbtr = nqINCA + nqCO2                                          !--- Number of tracers passed to phytrac
    228237      nqtrue = nbtr + nqo                                            !--- Total number of "true" tracers
    229       IF(ALL([2,3] /= nqo)) CALL abort_gcm(modname, 'Only 2 or 3 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
     238      IF(ALL([2,3,4,5] /= nqo)) CALL abort_gcm(modname, 'Only 2, 3, 4 , 5 water phases allowed ; found nqo='//TRIM(int2str(nqo)), 1)
    230239      ALLOCATE(hadv(nqtrue), hadv_inca(nqINCA), conv_flg_inca(nqINCA), solsym_inca(nqINCA))
    231240      ALLOCATE(vadv(nqtrue), vadv_inca(nqINCA),  pbl_flg_inca(nqINCA))
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/inigrads.F

    r1945 r4727  
    1616      character(len=*),intent(in) :: titlel
    1717
    18 #include "gradsdef.h"
     18      INCLUDE "gradsdef.h"
    1919
    2020c     data unit/66,32,34,36,38,40,42,44,46,48/
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/laplacien.F

    r1945 r4727  
    1414      IMPLICIT NONE
    1515c
    16 #include "dimensions.h"
    17 #include "paramet.h"
    18 #include "comgeom.h"
     16      INCLUDE "dimensions.h"
     17      INCLUDE "paramet.h"
     18      INCLUDE "comgeom.h"
    1919
    2020c
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/laplacien_gam.F

    r1945 r4727  
    1616      IMPLICIT NONE
    1717c
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comgeom.h"
     18      INCLUDE "dimensions.h"
     19      INCLUDE "paramet.h"
     20      INCLUDE "comgeom.h"
    2121
    2222c
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/laplacien_rot.F

    r1945 r4727  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "comgeom.h"
     17      INCLUDE "dimensions.h"
     18      INCLUDE "paramet.h"
     19      INCLUDE "comgeom.h"
    2020
    2121c
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/laplacien_rotgam.F

    r1945 r4727  
    1414      IMPLICIT NONE
    1515c
    16 #include "dimensions.h"
    17 #include "paramet.h"
    18 #include "comgeom.h"
     16      INCLUDE "dimensions.h"
     17      INCLUDE "paramet.h"
     18      INCLUDE "comgeom.h"
    1919
    2020c
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/nxgrad.F

    r1945 r4727  
    1414      IMPLICIT NONE
    1515c
    16 #include "dimensions.h"
    17 #include "paramet.h"
    18 #include "comgeom.h"
     16      INCLUDE "dimensions.h"
     17      INCLUDE "paramet.h"
     18      INCLUDE "comgeom.h"
    1919      INTEGER klevel
    2020      REAL rot( ip1jm,klevel ),x( ip1jmp1,klevel ),y(ip1jm,klevel )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/nxgrad_gam.F

    r1945 r4727  
    1414      IMPLICIT NONE
    1515c
    16 #include "dimensions.h"
    17 #include "paramet.h"
    18 #include "comgeom.h"
     16      INCLUDE "dimensions.h"
     17      INCLUDE "paramet.h"
     18      INCLUDE "comgeom.h"
    1919      INTEGER klevel
    2020      REAL rot( ip1jm,klevel ),x( ip1jmp1,klevel ),y(ip1jm,klevel )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/nxgradst.F

    r1945 r4727  
    1313c       x  et y    sont des arguments de sortie pour le s-prog
    1414c
    15 #include "dimensions.h"
    16 #include "paramet.h"
    17 #include "comgeom.h"
     15      INCLUDE "dimensions.h"
     16      INCLUDE "paramet.h"
     17      INCLUDE "comgeom.h"
    1818
    1919      INTEGER klevel
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/nxgraro2.F

    r1945 r4727  
    1717      IMPLICIT NONE
    1818c
    19 #include "dimensions.h"
    20 #include "paramet.h"
    21 #include "comdissipn.h"
     19      INCLUDE "dimensions.h"
     20      INCLUDE "paramet.h"
     21      INCLUDE "comdissipn.h"
    2222c
    2323c    ......  variables en arguments  .......
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/pbar.F

    r1945 r4727  
    7575
    7676
    77 #include "dimensions.h"
    78 #include "paramet.h"
     77      INCLUDE "dimensions.h"
     78      INCLUDE "paramet.h"
    7979
    80 #include "comgeom.h"
     80      INCLUDE "comgeom.h"
    8181
    8282      REAL pext( ip1jmp1 ),  pbarx ( ip1jmp1 )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/psextbar.F

    r1945 r4727  
    7575
    7676
    77 #include "dimensions.h"
    78 #include "paramet.h"
    79 #include "comgeom.h"
     77      INCLUDE "dimensions.h"
     78      INCLUDE "paramet.h"
     79      INCLUDE "comgeom.h"
    8080
    8181      REAL ps( ip1jmp1 ), psexbarxy ( ip1jm ), pext( ip1jmp1 )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/rotat.F

    r1945 r4727  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "comgeom.h"
     17      INCLUDE "dimensions.h"
     18      INCLUDE "paramet.h"
     19      INCLUDE "comgeom.h"
    2020c
    2121c   .....  variables en arguments  ......
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/rotat_nfil.F

    r1945 r4727  
    1515      IMPLICIT NONE
    1616c
    17 #include "dimensions.h"
    18 #include "paramet.h"
    19 #include "comgeom.h"
     17      INCLUDE "dimensions.h"
     18      INCLUDE "paramet.h"
     19      INCLUDE "comgeom.h"
    2020c
    2121c   .....  variables en arguments  ......
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/rotatf.F

    r1954 r4727  
    1616      IMPLICIT NONE
    1717c
    18 #include "dimensions.h"
    19 #include "paramet.h"
    20 #include "comgeom.h"
     18      INCLUDE "dimensions.h"
     19      INCLUDE "paramet.h"
     20      INCLUDE "comgeom.h"
    2121c
    2222c   .....  variables en arguments  ......
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/rotatst.F

    r1945 r4727  
    1616c
    1717      INTEGER klevel
    18 #include "dimensions.h"
    19 #include "paramet.h"
     18      INCLUDE "dimensions.h"
     19      INCLUDE "paramet.h"
    2020
    2121      REAL rot( ip1jm,klevel )
  • LMDZ6/branches/LMDZ_ECRad/libf/dyn3d_common/test_period.F

    r1952 r4727  
    1313c     IMPLICIT NONE
    1414c
    15 #include "dimensions.h"
    16 #include "paramet.h"
     15      INCLUDE "dimensions.h"
     16      INCLUDE "paramet.h"
    1717c
    1818c    ......  Arguments   ......
Note: See TracChangeset for help on using the changeset viewer.