Ignore:
Timestamp:
Aug 2, 2024, 9:58:25 PM (3 months ago)
Author:
abarral
Message:

Put dimensions.h and paramet.h into modules

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/dyn3d_common/initfluxsto.f90

    r5158 r5159  
    1313  USE lmdz_comgeom
    1414
     15  USE lmdz_dimensions, ONLY: iim, jjm, llm, ndm
     16  USE lmdz_paramet
    1517  IMPLICIT NONE
    1618
    17   !
     19
    1820  !   Routine d'initialisation des ecritures des fichiers histoires LMDZ
    1921  !   au format IOIPSL
    20   !
     22
    2123  !   Appels succesifs des routines: histbeg
    2224  !                              histhori
     
    2426  !                              histdef
    2527  !                              histend
    26   !
     28
    2729  !   Entree:
    28   !
     30
    2931  !  infile: nom du fichier histoire a creer
    3032  !  day0,anne0: date de reference
     
    3234  !  t_ops: frequence de l'operation pour IOIPSL
    3335  !  t_wrt: frequence d'ecriture sur le fichier
    34   !
     36
    3537  !   Sortie:
    3638  !  fileid: ID du fichier netcdf cree
    3739  !  filevid:ID du fichier netcdf pour la grille v
    38   !
     40
    3941  !   L. Fairhead, LMD, 03/99
    40   !
     42
    4143  ! =====================================================================
    42   !
     44
    4345  !   Declarations
    44   INCLUDE "dimensions.h"
    45   INCLUDE "paramet.h"
     46
     47
    4648
    4749  !   Arguments
    48   !
     50
    4951  CHARACTER(LEN = *) :: infile
    5052  REAL :: tstep, t_ops, t_wrt
     
    5355  ! This routine needs IOIPSL to work
    5456  !   Variables locales
    55   !
     57
    5658  REAL :: nivd(1)
    5759  INTEGER :: tau0
     
    6567  INTEGER :: zan, idayref
    6668  LOGICAL :: ok_sync
    67   !
     69
    6870  !  Initialisations
    69   !
     71
    7072  pi = 4. * atan (1.)
    7173  str = 'q  '
    7274  ctrac = 'traceur   '
    7375  ok_sync = .TRUE.
    74   !
     76
    7577  !  Appel a histbeg: creation du fichier netcdf et initialisations diverses
    7678  !
     
    9193          1, iip1, 1, jjp1, &
    9294          tau0, zjulian, tstep, uhoriid, fileid)
    93   !
     95
    9496  !  Creation du fichier histoire pour la grille en V (oblige pour l'instant,
    9597  !  IOIPSL ne permet pas de grilles avec des nombres de point differents dans
     
    112114          tau0, zjulian, tstep, dhoriid, filedid)
    113115
    114   !
     116
    115117  !  Appel a histhori pour rajouter les autres grilles horizontales
    116   !
     118
    117119  DO jj = 1, jjp1
    118120    DO ii = 1, iip1
     
    125127          'Grille points scalaires', thoriid)
    126128
    127   !
     129
    128130  !  Appel a histvert pour la grille verticale
    129   !
     131
    130132  CALL histvert(fileid, 'sig_s', 'Niveaux sigma', &
    131133          'sigma_level', &
     
    141143          1, nivd, dvertiid)
    142144
    143   !
     145
    144146  !  Appels a histdef pour la definition des variables a sauvegarder
    145147
     
    165167
    166168
    167   !
     169
    168170  ! Masse
    169   !
     171
    170172  CALL histdef(fileid, 'masse', 'Masse', 'kg', &
    171173          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
    172174          32, 'inst(X)', t_ops, t_wrt)
    173   !
     175
    174176  !  Pbaru
    175   !
     177
    176178  CALL histdef(fileid, 'pbaru', 'flx de masse zonal', 'kg m/s', &
    177179          iip1, jjp1, uhoriid, llm, 1, llm, zvertiid, &
    178180          32, 'inst(X)', t_ops, t_wrt)
    179181
    180   !
     182
    181183  !  Pbarv
    182   !
     184
    183185  CALL histdef(filevid, 'pbarv', 'flx de masse mer', 'kg m/s', &
    184186          iip1, jjm, vhoriid, llm, 1, llm, zvertiid, &
    185187          32, 'inst(X)', t_ops, t_wrt)
     188
     189  !  w
     190
     191  CALL histdef(fileid, 'w', 'flx de masse vert', 'kg m/s', &
     192          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
     193          32, 'inst(X)', t_ops, t_wrt)
     194
     195
     196  !  Temperature potentielle
     197
     198  CALL histdef(fileid, 'teta', 'temperature potentielle', '-', &
     199          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
     200          32, 'inst(X)', t_ops, t_wrt)
    186201  !
    187   !  w
    188   !
    189   CALL histdef(fileid, 'w', 'flx de masse vert', 'kg m/s', &
    190           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
    191           32, 'inst(X)', t_ops, t_wrt)
    192 
    193   !
    194   !  Temperature potentielle
    195   !
    196   CALL histdef(fileid, 'teta', 'temperature potentielle', '-', &
    197           iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
    198           32, 'inst(X)', t_ops, t_wrt)
    199   !
    200 
    201   !
     202
     203
    202204  ! Geopotentiel
    203   !
     205
    204206  CALL histdef(fileid, 'phi', 'geopotentiel instantane', '-', &
    205207          iip1, jjp1, thoriid, llm, 1, llm, zvertiid, &
    206208          32, 'inst(X)', t_ops, t_wrt)
    207   !
     209
    208210  !  Fin
    209   !
     211
    210212  CALL histend(fileid)
    211213  CALL histend(filevid)
Note: See TracChangeset for help on using the changeset viewer.