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/dyn3dmem
Files:
15 edited
1 moved

Legend:

Unmodified
Added
Removed
  • 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"
Note: See TracChangeset for help on using the changeset viewer.