Changeset 2601


Ignore:
Timestamp:
Jul 24, 2016, 11:51:55 AM (8 years ago)
Author:
Ehouarn Millour
Message:

Cleanup in the dynamics: turn temps.h into module temps_mod.F90
EM

Location:
LMDZ5/trunk/libf
Files:
1 added
1 deleted
60 edited
3 moved

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/advtrac.F90

    r2600 r2601  
    2020  include "comgeom2.h"
    2121  include "logic.h"
    22   include "temps.h"
    2322  include "ener.h"
    2423  include "description.h"
  • LMDZ5/trunk/libf/dyn3d/bilan_dyn.F

    r2600 r2601  
    1515      USE comconst_mod, ONLY: pi, cpp
    1616      USE comvert_mod, ONLY: presnivs
     17      USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    1718
    1819      IMPLICIT NONE
     
    2122      include "paramet.h"
    2223      include "comgeom2.h"
    23       include "temps.h"
    2424      include "iniprint.h"
    2525
  • LMDZ5/trunk/libf/dyn3d/conf_gcm.F90

    r2598 r2601  
    1818  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    1919                       alphax,alphay,taux,tauy
     20  USE temps_mod, ONLY: calend
    2021
    2122  IMPLICIT NONE
     
    3839  include "logic.h"
    3940  include "comdissnew.h"
    40   include "temps.h"
    4141  include "iniprint.h"
    4242
  • LMDZ5/trunk/libf/dyn3d/dynetat0.f90

    r2600 r2601  
    1414  USE comconst_mod, ONLY: cpp, daysec, dtvr, g, im, jm, kappa, lllm, omeg, rad
    1515  USE serre_mod, ONLY: clon, clat, grossismx, grossismy
     16  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn, start_time
    1617
    1718  IMPLICIT NONE
    1819  include "dimensions.h"
    1920  include "paramet.h"
    20   include "temps.h"
    2121  include "comgeom2.h"
    2222  include "ener.h"
  • LMDZ5/trunk/libf/dyn3d/dynredem.F90

    r2600 r2601  
    1616  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    1717                              taux,tauy
     18  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itaufin, start_time
     19 
    1820  IMPLICIT NONE
    1921  include "dimensions.h"
    2022  include "paramet.h"
    2123  include "comgeom2.h"
    22   include "temps.h"
    2324  include "ener.h"
    2425  include "logic.h"
     
    170171  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
    171172                          err, modname, fil, msg
     173  USE temps_mod, ONLY: itau_dyn, itaufin
     174 
    172175  IMPLICIT NONE
    173176  include "dimensions.h"
     
    175178  include "description.h"
    176179  include "comgeom.h"
    177   include "temps.h"
    178180  include "iniprint.h"
    179181!===============================================================================
  • LMDZ5/trunk/libf/dyn3d/fluxstokenc.F

    r2600 r2601  
    2020      include "comgeom.h"
    2121      include "tracstoke.h"
    22       include "temps.h"
    2322      include "iniprint.h"
    2423
  • LMDZ5/trunk/libf/dyn3d/gcm.F90

    r2600 r2601  
    2323  USE control_mod
    2424  USE mod_const_mpi, ONLY: COMM_LMDZ
     25  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
     26                     itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end
    2527  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
    2628
     
    7173  include "comgeom.h"
    7274  include "logic.h"
    73   include "temps.h"
    7475  include "ener.h"
    7576  include "description.h"
  • LMDZ5/trunk/libf/dyn3d/iniacademic.F90

    r2600 r2601  
    1818  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    1919  USE comvert_mod, ONLY: ap, bp, preff, presnivs, pressure_exner
     20  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2021
    2122  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3334  include "academic.h"
    3435  include "ener.h"
    35   include "temps.h"
    3636  include "iniprint.h"
    3737  include "logic.h"
  • LMDZ5/trunk/libf/dyn3d/integrd.F

    r2600 r2601  
    1010      use comconst_mod, only: pi
    1111      use comvert_mod, only: ap, bp
     12      USE temps_mod, ONLY: dt
    1213
    1314      IMPLICIT NONE
     
    3334      include "comgeom.h"
    3435      include "logic.h"
    35       include "temps.h"
    3636      include "iniprint.h"
    3737
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r2600 r2601  
    2222      USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
    2323      USE comconst_mod, ONLY: cpp, dtphys, dtvr, pi, ihf
     24      USE temps_mod, ONLY: jD_ref,jH_ref,itaufin,day_ini,day_ref,
     25     &                        start_time,dt
    2426
    2527      IMPLICIT NONE
     
    6163      include "comgeom.h"
    6264      include "logic.h"
    63       include "temps.h"
    6465      include "ener.h"
    6566      include "description.h"
  • LMDZ5/trunk/libf/dyn3d/temps_mod.F90

    r2600 r2601  
    22! $Id$
    33!
    4 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
    5 !                 veillez  n'utiliser que des ! pour les commentaires
    6 !                 et  bien positionner les & des lignes de continuation
    7 !                 (les placer en colonne 6 et en colonne 73)
    8 !
    9 !
    10 ! jD_ref = jour julien de la date de reference (lancement de l'experience)
    11 ! hD_ref = "heure" julienne de la date de reference
    12 !-----------------------------------------------------------------------
    13 ! INCLUDE 'temps.h'
     4MODULE temps_mod
    145
    15       COMMON/temps/ dt, jD_ref, jH_ref, start_time,                     &
    16      &             day_ini, day_end, annee_ref, day_ref,                &
    17      &             itau_dyn, itau_phy, itaufin, calend
     6IMPLICIT NONE 
    187
     8  INTEGER   itaufin ! total number of dynamical steps for the run
     9  INTEGER   itau_dyn
     10  INTEGER   itau_phy
     11  INTEGER   day_ini ! initial day # of simulation sequence
     12  INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
     13  INTEGER   annee_ref
     14  INTEGER   day_ref
     15  REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
     16  REAL      jD_ref ! reference julian day date (beginning of experiment)
     17  REAL      jH_ref ! reference julian "hour" of reference julian date
     18  REAL      start_time
     19  CHARACTER (len=10) :: calend ! calendar type
    1920
    20       INTEGER   itaufin
    21       INTEGER itau_dyn, itau_phy
    22       INTEGER day_ini, day_end, annee_ref, day_ref
    23       REAL      dt, jD_ref, jH_ref, start_time
    24       CHARACTER (len=10) :: calend
     21  ! Additionnal Mars stuff:
     22  REAL hour_ini ! initial fraction of day of simulation sequence (0=<hour_ini<1)
    2523
    26 !-----------------------------------------------------------------------
     24END MODULE temps_mod
  • LMDZ5/trunk/libf/dyn3d_common/adaptdt.F

    r2600 r2601  
    55     c                   masse)
    66
    7 !      USE control_mod
    87      USE comconst_mod, ONLY: dtvr
    98      IMPLICIT NONE
     
    1413      include "comgeom2.h"
    1514      include "logic.h"
    16       include "temps.h"
    1715      include "ener.h"
    1816      include "description.h"
  • LMDZ5/trunk/libf/dyn3d_common/iniconst.F90

    r2600 r2601  
    2424  include "dimensions.h"
    2525  include "paramet.h"
    26   include "temps.h"
    2726  include "iniprint.h"
    2827
  • LMDZ5/trunk/libf/dyn3d_common/initdynav.F90

    r2600 r2601  
    1111  USE comconst_mod, ONLY: pi
    1212  USE comvert_mod, ONLY: presnivs
     13  USE temps_mod, ONLY: itau_dyn
     14 
    1315  implicit none
    1416
     
    3739  include "paramet.h"
    3840  include "comgeom.h"
    39   include "temps.h"
    4041  include "ener.h"
    4142  include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/initfluxsto.F

    r2600 r2601  
    1111      USE comconst_mod, ONLY: pi
    1212      USE comvert_mod, ONLY: nivsigs
     13      USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
     14     
    1315      implicit none
    1416
     
    4345      include "paramet.h"
    4446      include "comgeom.h"
    45       include "temps.h"
    4647      include "ener.h"
    4748      include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/inithist.F

    r2600 r2601  
    1212       USE comconst_mod, ONLY: pi
    1313       USE comvert_mod, ONLY: presnivs
     14       USE temps_mod, ONLY: itau_dyn
     15       
    1416      implicit none
    1517
     
    4244      include "paramet.h"
    4345      include "comgeom.h"
    44       include "temps.h"
    4546      include "ener.h"
    4647      include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/interpre.F

    r2600 r2601  
    1616      include "comgeom2.h"
    1717      include "logic.h"
    18       include "temps.h"
    1918      include "ener.h"
    2019      include "description.h"
  • LMDZ5/trunk/libf/dyn3d_common/sortvarc.F

    r2600 r2601  
    3131      INCLUDE "ener.h"
    3232      INCLUDE "logic.h"
    33       INCLUDE "temps.h"
    3433      INCLUDE "iniprint.h"
    3534
  • LMDZ5/trunk/libf/dyn3d_common/traceurpole.F

    r2600 r2601  
    1111      include "comgeom2.h"
    1212      include "logic.h"
    13       include "temps.h"
    1413      include "ener.h"
    1514      include "description.h"
  • LMDZ5/trunk/libf/dyn3d_common/writedynav.F90

    r2600 r2601  
    99  use com_io_dyn_mod, only : histaveid, histvaveid, histuaveid
    1010  USE comconst_mod, ONLY: cpp
     11  USE temps_mod, ONLY: itau_dyn
    1112
    1213  implicit none
     
    3334  include "paramet.h"
    3435  include "comgeom.h"
    35   include "temps.h"
    3636  include "ener.h"
    3737  include "logic.h"
  • LMDZ5/trunk/libf/dyn3d_common/writehist.F

    r2600 r2601  
    99      USE infotrac, ONLY : nqtot, ttext
    1010      use com_io_dyn_mod, only : histid,histvid,histuid
     11      USE temps_mod, ONLY: itau_dyn
     12     
    1113      implicit none
    1214
     
    3638      include "paramet.h"
    3739      include "comgeom.h"
    38       include "temps.h"
    3940      include "ener.h"
    4041      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/advtrac_loc.F

    r2600 r2601  
    3535      include "comgeom2.h"
    3636      include "logic.h"
    37       include "temps.h"
    3837      include "ener.h"
    3938      include "description.h"
  • LMDZ5/trunk/libf/dyn3dmem/bilan_dyn_loc.F

    r2600 r2601  
    1919      USE comconst_mod, ONLY: cpp, pi
    2020      USE comvert_mod, ONLY: presnivs
     21      USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    2122     
    2223      IMPLICIT NONE
     
    2526      include "paramet.h"
    2627      include "comgeom2.h"
    27       include "temps.h"
    2828      include "iniprint.h"
    2929
  • LMDZ5/trunk/libf/dyn3dmem/call_calfis_mod.F90

    r2600 r2601  
    8484  USE comconst_mod, ONLY: dtphys
    8585  USE comvert_mod, ONLY: ap, bp, pressure_exner
     86  USE temps_mod, ONLY: day_ini, day_ref, jd_ref, jh_ref, start_time
    8687 
    8788  IMPLICIT NONE
    8889    INCLUDE "logic.h"
    89     INCLUDE "temps.h"
    9090    INCLUDE "iniprint.h"
    9191
  • LMDZ5/trunk/libf/dyn3dmem/conf_gcm.F90

    r2598 r2601  
    2222  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    2323                       alphax,alphay,taux,tauy
     24  USE temps_mod, ONLY: calend
    2425
    2526  IMPLICIT NONE
     
    4243  include "logic.h"
    4344  include "comdissnew.h"
    44   include "temps.h"
    4545  include "iniprint.h"
    4646
  • LMDZ5/trunk/libf/dyn3dmem/dynetat0_loc.f90

    r2600 r2601  
    1616                          omeg, rad
    1717  USE serre_mod, ONLY: clon, clat, grossismx, grossismy
     18  USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn, &
     19                       start_time,day_ini,hour_ini
    1820 
    1921  IMPLICIT NONE
    2022  include "dimensions.h"
    2123  include "paramet.h"
    22   include "temps.h"
    2324  include "comgeom.h"
    2425  include "ener.h"
  • LMDZ5/trunk/libf/dyn3dmem/dynredem_loc.F90

    r2600 r2601  
    1818  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    1919                       taux,tauy
     20  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itaufin, start_time
    2021
    2122  IMPLICIT NONE
     
    2324  include "paramet.h"
    2425  include "comgeom.h"
    25   include "temps.h"
    2626  include "ener.h"
    2727  include "logic.h"
     
    179179  USE dynredem_mod, ONLY: dynredem_write_u, dynredem_write_v, dynredem_read_u, &
    180180                          err, modname, fil, msg
     181  USE temps_mod, ONLY: itau_dyn, itaufin
     182 
    181183  IMPLICIT NONE
    182184  include "dimensions.h"
     
    184186  include "description.h"
    185187  include "comgeom.h"
    186   include "temps.h"
    187188  include "iniprint.h"
    188189!===============================================================================
  • LMDZ5/trunk/libf/dyn3dmem/gcm.F90

    r2600 r2601  
    2222#endif
    2323  USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
     24  USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref, &
     25                       itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end, &
     26                       dt,hour_ini,itaufin
     27
    2428  IMPLICIT NONE
    2529
     
    5862  include "comgeom.h"
    5963  include "logic.h"
    60   include "temps.h"
    6164  include "ener.h"
    6265  include "description.h"
     
    449452  !       write(78,*) 'q',q
    450453
    451   !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
     454  !!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
     455  !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/logici/,/logicl/) &
     456  !     Copy all threadprivate variables in temps_mod
     457  !$OMP COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end) &
     458  !$OMP COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend)
    452459  CALL leapfrog_loc(ucov,vcov,teta,ps,masse,phis,q,time_0)
    453460  !$OMP END PARALLEL
  • LMDZ5/trunk/libf/dyn3dmem/iniacademic_loc.F90

    r2600 r2601  
    2020  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    2121  USE comvert_mod, ONLY: ap, bp, preff, presnivs, pressure_exner
     22  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2223
    2324  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3536  include "academic.h"
    3637  include "ener.h"
    37   include "temps.h"
    3838  include "iniprint.h"
    3939  include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/initdynav_loc.F

    r2600 r2601  
    1616       USE comconst_mod, ONLY: pi
    1717       USE comvert_mod, ONLY: presnivs
     18       USE temps_mod, ONLY: itau_dyn
    1819       
    1920       implicit none
     
    4748      include "paramet.h"
    4849      include "comgeom.h"
    49       include "temps.h"
    5050      include "ener.h"
    5151      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/initfluxsto_p.F

    r2600 r2601  
    1515       USE comconst_mod, ONLY: pi
    1616       USE comvert_mod, ONLY: nivsigs
     17       USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    1718       
    1819      implicit none
     
    4849      include "paramet.h"
    4950      include "comgeom.h"
    50       include "temps.h"
    5151      include "ener.h"
    5252      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/inithist_loc.F

    r2600 r2601  
    1616       USE comconst_mod, ONLY: pi
    1717       USE comvert_mod, ONLY: presnivs
     18       USE temps_mod, ONLY: itau_dyn
    1819       
    1920       implicit none
     
    4647      include "paramet.h"
    4748      include "comgeom.h"
    48       include "temps.h"
    4949      include "ener.h"
    5050      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/integrd_loc.F

    r2600 r2601  
    1414      USE comconst_mod, ONLY: pi
    1515      USE comvert_mod, ONLY: ap, bp
     16      USE temps_mod, ONLY: dt
    1617     
    1718      IMPLICIT NONE
     
    3738      include "comgeom.h"
    3839      include "logic.h"
    39       include "temps.h"
    4040      include "iniprint.h"
    4141
  • LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F

    r2600 r2601  
    3434       USE comconst_mod, ONLY: cpp, dtvr, ihf
    3535       USE comvert_mod, ONLY: ap, bp, pressure_exner
     36       USE temps_mod, ONLY: itaufin,jD_ref,jH_ref,day_ini,
     37     &                        day_ref,start_time,dt
    3638       
    3739      IMPLICIT NONE
     
    7375      include "comgeom.h"
    7476      include "logic.h"
    75       include "temps.h"
    7677      include "ener.h"
    7778      include "description.h"
  • LMDZ5/trunk/libf/dyn3dmem/temps_mod.F90

    r2600 r2601  
    11!
    2 ! $Id$
     2! $Id: temps_mod.F90 -1   $
    33!
    4 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
    5 !                 veillez  n'utiliser que des ! pour les commentaires
    6 !                 et  bien positionner les & des lignes de continuation
    7 !                 (les placer en colonne 6 et en colonne 73)
    8 !
    9 !
    10 ! jD_ref = jour julien de la date de reference (lancement de l'experience)
    11 ! hD_ref = "heure" julienne de la date de reference
    12 !-----------------------------------------------------------------------
    13 ! INCLUDE 'temps.h'
     4MODULE temps_mod
    145
    15       COMMON/temps/ dt, jD_ref, jH_ref, start_time,                     &
    16      &             day_ini, day_end, annee_ref, day_ref,                &
    17      &             itau_dyn, itau_phy, itaufin, calend
     6IMPLICIT NONE 
    187
     8  INTEGER   itaufin ! total number of dynamical steps for the run
     9  INTEGER   itau_dyn
     10  INTEGER   itau_phy
     11  INTEGER   day_ini ! initial day # of simulation sequence
     12  INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
     13  INTEGER   annee_ref
     14  INTEGER   day_ref
     15  REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
     16  REAL      jD_ref ! reference julian day date (beginning of experiment)
     17  REAL      jH_ref ! reference julian "hour" of reference julian date
     18  REAL      start_time
     19  CHARACTER (len=10) :: calend ! calendar type
    1920
    20       INTEGER   itaufin
    21       INTEGER itau_dyn, itau_phy
    22       INTEGER day_ini, day_end, annee_ref, day_ref
    23       REAL      dt, jD_ref, jH_ref, start_time
    24       CHARACTER (len=10) :: calend
     21  ! Additionnal Mars stuff:
     22  REAL hour_ini ! initial fraction of day of simulation sequence (0=<hour_ini<1)
    2523
    26 !$OMP THREADPRIVATE(/temps/)
    27 !-----------------------------------------------------------------------
     24!$OMP THREADPRIVATE(dt,jD_ref,jH_ref,start_time,hour_ini,                        &
     25!$OMP                day_ini,day_end,annee_ref,day_ref,itau_dyn,itau_phy,itaufin,&
     26!$OMP                calend)       
     27
     28!WARNING: when adding a threadprivate variable in this module
     29!        do not forget to add it to the copyin clause when opening an OpenMP
     30!        parallel section. e.g. in gcm before call leapfrog_loc and/or
     31!        possibly in iniphysiq
     32
     33END MODULE temps_mod
  • LMDZ5/trunk/libf/dyn3dmem/writedynav_loc.F

    r2600 r2601  
    1414      use com_io_dyn_mod, only : histaveid,histvaveid,histuaveid
    1515      USE comconst_mod, ONLY: cpp
     16      USE temps_mod, ONLY: itau_dyn
     17     
    1618      implicit none
    1719
     
    4547      include "paramet.h"
    4648      include "comgeom.h"
    47       include "temps.h"
    4849      include "ener.h"
    4950      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dmem/writehist_loc.F

    r2600 r2601  
    1414      use com_io_dyn_mod, only : histid,histvid,histuid
    1515      USE comconst_mod, ONLY: cpp
     16      USE temps_mod, ONLY: itau_dyn
     17     
    1618      implicit none
    1719
     
    4547      include "paramet.h"
    4648      include "comgeom.h"
    47       include "temps.h"
    4849      include "ener.h"
    4950      include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/advtrac_p.F90

    r2600 r2601  
    2727  include "comgeom2.h"
    2828  include "logic.h"
    29   include "temps.h"
    3029  include "ener.h"
    3130  include "description.h"
  • LMDZ5/trunk/libf/dyn3dpar/bilan_dyn_p.F

    r2600 r2601  
    1919      USE comconst_mod, ONLY: cpp, pi
    2020      USE comvert_mod, ONLY: presnivs
     21      USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    2122     
    2223      IMPLICIT NONE
     
    2526#include "paramet.h"
    2627#include "comgeom2.h"
    27 #include "temps.h"
    2828#include "iniprint.h"
    2929
  • LMDZ5/trunk/libf/dyn3dpar/conf_gcm.F90

    r2598 r2601  
    2121  USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy, &
    2222                       alphax,alphay,taux,tauy
     23  USE temps_mod, ONLY: calend
    2324
    2425  IMPLICIT NONE
     
    4142  include "logic.h"
    4243  include "comdissnew.h"
    43   include "temps.h"
    4444  include "iniprint.h"
    4545
  • LMDZ5/trunk/libf/dyn3dpar/dynetat0.F

    r2600 r2601  
    1414
    1515      USE serre_mod, ONLY: clon,clat,grossismx,grossismy
     16      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,
     17     &                     start_time,day_ini,hour_ini
    1618
    1719      IMPLICIT NONE
     
    3436#include "dimensions.h"
    3537#include "paramet.h"
    36 #include "temps.h"
    3738#include "comgeom2.h"
    3839#include "ener.h"
  • LMDZ5/trunk/libf/dyn3dpar/dynredem.F

    r2600 r2601  
    1414      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
    1515     &                     taux,tauy
     16      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,itaufin,
     17     &                        start_time,hour_ini
    1618 
    1719      IMPLICIT NONE
     
    2426#include "paramet.h"
    2527#include "comgeom2.h"
    26 #include "temps.h"
    2728#include "ener.h"
    2829#include "logic.h"
     
    473474      use netcdf, only: NF90_get_VAR
    474475      use netcdf95, only: NF95_PUT_VAR
     476      USE temps_mod, ONLY: itau_dyn, itaufin
    475477 
    476478      IMPLICIT NONE
     
    483485#include "netcdf.inc"
    484486#include "comgeom.h"
    485 #include "temps.h"
    486487#include "iniprint.h"
    487488
  • LMDZ5/trunk/libf/dyn3dpar/dynredem_p.F

    r2600 r2601  
    1515      USE serre_mod, ONLY: clon,clat,grossismx,grossismy,dzoomx,dzoomy,
    1616     &                     taux,tauy
     17      USE temps_mod, ONLY: annee_ref,day_ref,itau_dyn,itaufin,
     18     &                        start_time,hour_ini
    1719 
    1820      IMPLICIT NONE
     
    2527#include "paramet.h"
    2628#include "comgeom2.h"
    27 #include "temps.h"
    2829#include "ener.h"
    2930#include "logic.h"
     
    474475      use netcdf, only: NF90_get_VAR
    475476      use netcdf95, only: NF95_PUT_VAR
     477      USE temps_mod, ONLY: itau_dyn, itaufin
    476478 
    477479      IMPLICIT NONE
     
    484486#include "netcdf.inc"
    485487#include "comgeom.h"
    486 #include "temps.h"
    487488
    488489
  • LMDZ5/trunk/libf/dyn3dpar/fluxstokenc_p.F

    r2600 r2601  
    2323#include "comgeom.h"
    2424#include "tracstoke.h"
    25 #include "temps.h"
    2625#include "iniprint.h"
    2726
  • LMDZ5/trunk/libf/dyn3dpar/gcm.F

    r2600 r2601  
    3333#endif
    3434      USE comconst_mod, ONLY: cpp, daysec, dtphys, dtvr, g, r, rad
     35      USE temps_mod, ONLY: calend,start_time,annee_ref,day_ref,
     36     &                itau_dyn,itau_phy,day_ini,jD_ref,jH_ref,day_end,
     37     &                dt,hour_ini,itaufin
    3538
    3639      IMPLICIT NONE
     
    7073#include "comgeom.h"
    7174#include "logic.h"
    72 #include "temps.h"
    7375#include "ener.h"
    7476#include "description.h"
     
    498500c       write(78,*) 'q',q
    499501
    500 c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
     502!c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/,/logici/,/logicl/)
     503c$OMP PARALLEL DEFAULT(SHARED) COPYIN(/logici/,/logicl/)
     504c        Copy all threadprivate variables from temps_mod
     505c$OMP1 COPYIN(dt,jD_ref,jH_ref,start_time,hour_ini,day_ini,day_end)
     506c$OMP1 COPYIN(annee_ref,day_ref,itau_dyn,itau_phy,itaufin,calend)
    501507      CALL leapfrog_p(ucov,vcov,teta,ps,masse,phis,q,time_0)
    502508c$OMP END PARALLEL
  • LMDZ5/trunk/libf/dyn3dpar/iniacademic.F90

    r2600 r2601  
    1818  USE comconst_mod, ONLY: cpp, kappa, g, daysec, dtvr, pi, im, jm
    1919  USE comvert_mod, ONLY: ap, bp, preff, presnivs, pressure_exner
     20  USE temps_mod, ONLY: annee_ref, day_ini, day_ref
    2021
    2122  !   Author:    Frederic Hourdin      original: 15/01/93
     
    3334  include "academic.h"
    3435  include "ener.h"
    35   include "temps.h"
    3636  include "iniprint.h"
    3737  include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/initdynav_p.F

    r2600 r2601  
    1414       USE comconst_mod, ONLY: pi
    1515       USE comvert_mod, ONLY: nivsigs
     16       USE temps_mod, ONLY: itau_dyn
    1617
    1718      implicit none
     
    4647#include "paramet.h"
    4748#include "comgeom.h"
    48 #include "temps.h"
    4949#include "ener.h"
    5050#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/initfluxsto_p.F

    r2600 r2601  
    1515       USE comconst_mod, ONLY: pi
    1616       USE comvert_mod, ONLY: nivsigs
     17       USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn
    1718       
    1819      implicit none
     
    4849#include "paramet.h"
    4950#include "comgeom.h"
    50 #include "temps.h"
    5151#include "ener.h"
    5252#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/inithist_p.F

    r2600 r2601  
    1515       USE comconst_mod, ONLY: pi
    1616       USE comvert_mod, ONLY: nivsigs
     17       USE temps_mod, ONLY: itau_dyn
    1718
    1819      implicit none
     
    4849#include "paramet.h"
    4950#include "comgeom.h"
    50 #include "temps.h"
    5151#include "ener.h"
    5252#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/integrd_p.F

    r2600 r2601  
    99      USE comconst_mod, ONLY: pi
    1010      USE comvert_mod, ONLY: ap, bp
     11      USE temps_mod, ONLY: dt
     12     
    1113      IMPLICIT NONE
    1214
     
    3133#include "comgeom.h"
    3234#include "logic.h"
    33 #include "temps.h"
    3435#include "iniprint.h"
    3536
     
    283284      ije=ij_end
    284285
    285         if (planet_type.eq."earth") then
     286        if (planet_type.eq."earth") then
    286287! Earth-specific treatment of first 2 tracers (water)
    287288c$OMP BARRIER
     
    384385          DO l = 1, llm
    385386            massem1(ijb:ije,l)=massescr(ijb:ije,l)
    386           ENDDO
    387 c$OMP END DO NOWAIT      
     387          ENDDO
     388c$OMP END DO NOWAIT 
    388389      END IF
    389390c$OMP BARRIER
  • LMDZ5/trunk/libf/dyn3dpar/leapfrog_p.F

    r2600 r2601  
    3030       USE comvert_mod, ONLY: ap,bp,pressure_exner,presnivs
    3131       USE comconst_mod, ONLY: cpp, dtvr, ihf, dtphys, pi, jmp1
     32       USE temps_mod, ONLY: itaufin,jD_ref,jH_ref,day_ini,
     33     &                        day_ref,start_time,dt
     34
    3235      IMPLICIT NONE
    3336
     
    6871#include "comgeom.h"
    6972#include "logic.h"
    70 #include "temps.h"
    7173#include "ener.h"
    7274#include "description.h"
  • LMDZ5/trunk/libf/dyn3dpar/temps_mod.F90

    r2600 r2601  
    22! $Id$
    33!
    4 !  ATTENTION!!!!: ce fichier include est compatible format fixe/format libre
    5 !                 veillez  n'utiliser que des ! pour les commentaires
    6 !                 et  bien positionner les & des lignes de continuation
    7 !                 (les placer en colonne 6 et en colonne 73)
    8 !
    9 !
    10 ! jD_ref = jour julien de la date de reference (lancement de l'experience)
    11 ! hD_ref = "heure" julienne de la date de reference
    12 !-----------------------------------------------------------------------
    13 ! INCLUDE 'temps.h'
     4MODULE temps_mod
    145
    15       COMMON/temps/ dt, jD_ref, jH_ref, start_time,                     &
    16      &             day_ini, day_end, annee_ref, day_ref,                &
    17      &             itau_dyn, itau_phy, itaufin, calend
     6IMPLICIT NONE 
    187
     8  INTEGER   itaufin ! total number of dynamical steps for the run
     9  INTEGER   itau_dyn
     10  INTEGER   itau_phy
     11  INTEGER   day_ini ! initial day # of simulation sequence
     12  INTEGER   day_end ! final day # ; i.e. day # when this simulation ends
     13  INTEGER   annee_ref
     14  INTEGER   day_ref
     15  REAL      dt ! (dynamics) time step (changes if doing Matsuno or LF step)
     16  REAL      jD_ref ! reference julian day date (beginning of experiment)
     17  REAL      jH_ref ! reference julian "hour" of reference julian date
     18  REAL      start_time
     19  CHARACTER (len=10) :: calend ! calendar type
    1920
    20       INTEGER   itaufin
    21       INTEGER itau_dyn, itau_phy
    22       INTEGER day_ini, day_end, annee_ref, day_ref
    23       REAL      dt, jD_ref, jH_ref, start_time
    24       CHARACTER (len=10) :: calend
     21  ! Additionnal Mars stuff:
     22  REAL hour_ini ! initial fraction of day of simulation sequence (0=<hour_ini<1)
    2523
    26 !$OMP THREADPRIVATE(/temps/)
    27 !-----------------------------------------------------------------------
     24!$OMP THREADPRIVATE(dt,jD_ref,jH_ref,start_time,hour_ini,                        &
     25!$OMP                day_ini,day_end,annee_ref,day_ref,itau_dyn,itau_phy,itaufin,&
     26!$OMP                calend)       
     27
     28!WARNING: when adding a threadprivate variable in this module
     29!        do not forget to add it to the copyin clause when opening an OpenMP
     30!        parallel section. e.g. in gcm before call leapfrog_loc and/or
     31!        possibly in iniphysiq
     32
     33END MODULE temps_mod
  • LMDZ5/trunk/libf/dyn3dpar/writedynav_p.F

    r2600 r2601  
    1313      USE infotrac
    1414      USE comconst_mod, ONLY: cpp
     15      USE temps_mod, ONLY: itau_dyn
     16     
    1517      implicit none
    1618
     
    4446#include "paramet.h"
    4547#include "comgeom.h"
    46 #include "temps.h"
    4748#include "ener.h"
    4849#include "logic.h"
  • LMDZ5/trunk/libf/dyn3dpar/writehist_p.F

    r2600 r2601  
    1212      USE misc_mod
    1313      USE infotrac
     14      USE temps_mod, ONLY: itau_dyn
     15     
    1416      implicit none
    1517
     
    4446#include "paramet.h"
    4547#include "comgeom.h"
    46 #include "temps.h"
    4748#include "ener.h"
    4849#include "logic.h"
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis.F

    r2600 r2601  
    9393      include "dimensions.h"
    9494      include "paramet.h"
    95       include "temps.h"
    9695
    9796      INTEGER ngridmx
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis_loc.F

    r2600 r2601  
    111111      include "dimensions.h"
    112112      include "paramet.h"
    113       include "temps.h"
    114113
    115114      INTEGER ngridmx
  • LMDZ5/trunk/libf/dynphy_lonlat/calfis_p.F

    r2600 r2601  
    107107#include "dimensions.h"
    108108#include "paramet.h"
    109 #include "temps.h"
    110109
    111110      INTEGER ngridmx
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/ce0l.F90

    r2600 r2601  
    3737                          pi, jmp1
    3838  USE comvert_mod, ONLY: pa, preff, pressure_exner
     39  USE temps_mod, ONLY: calend, day_ini, dt
    3940
    4041  IMPLICIT NONE
     
    4647  include "comgeom2.h"
    4748  include "iniprint.h"
    48   include "temps.h"
    4949  include "logic.h"
    5050  REAL               :: masque(iip1,jjp1)             !--- CONTINENTAL MASK
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/etat0dyn_netcdf.F90

    r2600 r2601  
    3838  USE comconst_mod, ONLY: pi, cpp, kappa
    3939  USE comvert_mod, ONLY: ap, bp, preff, pressure_exner
     40  USE temps_mod, ONLY: annee_ref, day_ref, itau_dyn, itau_phy
     41 
    4042  IMPLICIT NONE
    4143
     
    4749  include "paramet.h"
    4850  include "comgeom2.h"
    49   include "temps.h"
    5051  include "comdissnew.h"
    5152  REAL, SAVE :: deg2rad
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r2597 r2601  
    5454  include "comgeom2.h"
    5555  include "dimsoil.h"
    56   include "temps.h"
    5756  include "clesphys.h"
    5857  REAL, SAVE :: deg2rad
  • LMDZ5/trunk/libf/dynphy_lonlat/phylmd/iniphysiq_mod.F90

    r2600 r2601  
    3232  USE inifis_mod, ONLY: inifis
    3333  USE time_phylmdz_mod, ONLY: init_time
     34  USE temps_mod, ONLY: annee_ref, day_ini, day_ref, start_time
    3435  USE infotrac_phy, ONLY: init_infotrac_phy
    3536  USE phystokenc_mod, ONLY: init_phystokenc
     
    5253  include "dimensions.h"
    5354  include "iniprint.h"
    54   include "temps.h"
    5555  include "tracstoke.h"
    5656
     
    9898  ! --> now initialize things specific to the phylmd physics package
    9999 
    100 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     100!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     101!$OMP PARALLEL DEFAULT(SHARED) &
     102!       Copy all threadprivate variables in temps_mod
     103!$OMP COPYIN(annee_ref, day_ini, day_ref, start_time)
    101104
    102105  ! copy over preff , ap(), bp(), etc
     
    144147#endif
    145148  END IF
    146 !$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
    147149
     150!!$OMP PARALLEL DEFAULT(SHARED) COPYIN(/temps/)
     151!$OMP PARALLEL DEFAULT(SHARED)
    148152  ! Additional initializations for aquaplanets
    149153  IF (iflag_phys>=100) THEN
  • LMDZ5/trunk/libf/phylmd/dyn1d/1DUTILS.h

    r2597 r2601  
    436436      use control_mod
    437437      USE comconst_mod, ONLY: im, jm, lllm
     438      USE temps_mod, ONLY: annee_ref, day_ini, day_ref, itau_dyn
    438439
    439440      IMPLICIT NONE
     
    444445!   -------------
    445446      include "dimensions.h"
    446       include "temps.h"
    447447!!#include "control.h"
    448448      include "logic.h"
     
    580580      use control_mod
    581581      USE comconst_mod, ONLY: cpp, daysec, dtvr, g, kappa, omeg, rad
     582      USE temps_mod, ONLY: annee_ref,day_end,day_ref,itau_dyn,itaufin
    582583
    583584      IMPLICIT NONE
     
    588589!   -------------
    589590      include "dimensions.h"
    590       include "temps.h"
    591591!!#include "control.h"
    592592      include "logic.h"
  • LMDZ5/trunk/libf/phylmd/dyn1d/lmdz1d.F90

    r2600 r2601  
    3737   USE mod_const_mpi, ONLY: comm_lmdz
    3838   USE physiq_mod, ONLY: physiq
     39   USE temps_mod, ONLY: annee_ref, calend, day_end, day_ini, day_ref, &
     40                        itau_dyn, itau_phy, start_time
    3941
    4042      implicit none
    4143#include "dimensions.h"
    4244#include "YOMCST.h"
    43 #include "temps.h"
    4445!!#include "control.h"
    4546#include "clesphys.h"
Note: See TracChangeset for help on using the changeset viewer.