source: trunk/LMDZ.VENUS/libf/phyvenus/phyredem.F90 @ 1543

Last change on this file since 1543 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

File size: 3.2 KB
Line 
1!
2! $Id: $
3!
4      SUBROUTINE phyredem (fichnom)
5
6      USE dimphy
7      USE mod_grid_phy_lmdz
8      USE mod_phys_lmdz_para
9      USE iophy
10      USE phys_state_var_mod
11      USE iostart, only : open_restartphy,close_restartphy, &
12                          put_var,put_field
13      USE infotrac
14      use geometry_mod, only: longitude, latitude
15      USE time_phylmdz_mod, only: day_end, annee_ref, itau_phy, raz_date
16
17      implicit none
18!======================================================================
19! Auteur(s) Z.X. Li (LMD/CNRS) date: 19930818
20! Objet: Lecture de l'etat initial pour la physique
21!======================================================================
22#include "netcdf.inc"
23#include "dimsoil.h"
24#include "clesphys.h"
25#include "tabcontrol.h"
26!======================================================================
27
28character(len=*),intent(in) :: fichnom
29REAL    :: tab_cntrl(length)
30integer :: isoil
31CHARACTER(len=2) :: str2
32
33
34! open file
35
36      CALL open_restartphy(fichnom)
37
38! tab_cntrl() contains run parameters
39
40      tab_cntrl(:)=0.0
41 
42      tab_cntrl(1) = dtime
43      tab_cntrl(2) = radpas
44      tab_cntrl(3) = 0.0
45      tab_cntrl(4) = solaire
46      tab_cntrl(5) = 0
47      tab_cntrl(6) = nbapp_rad
48
49      IF( cycle_diurne ) tab_cntrl( 7 ) = 1.
50      IF(   soil_model ) tab_cntrl( 8 ) = 1.
51      IF(     ok_orodr ) tab_cntrl(10 ) = 1.
52      IF(     ok_orolf ) tab_cntrl(11 ) = 1.
53      IF( ok_gw_nonoro ) tab_cntrl(12 ) = 1.
54
55      tab_cntrl(13) = day_end
56      tab_cntrl(14) = annee_ref
57      tab_cntrl(15) = itau_phy
58
59      CALL put_var("controle","Parametres de controle",tab_cntrl)
60
61! coordinates
62
63      CALL put_field("longitude", &
64                     "Longitudes de la grille physique",longitude)
65     
66      CALL put_field("latitude", &
67                     "Latitudes de la grille physique",latitude)
68
69! variables
70
71      CALL put_field("TS","Temperature de surface",ftsol)
72
73      DO isoil=1, nsoilmx
74        IF (isoil.LE.99) THEN
75        WRITE(str2,'(i2.2)') isoil
76        CALL put_field("Tsoil"//str2, &
77                       "Temperature du sol No."//str2,ftsoil(:,isoil))
78        ELSE
79        PRINT*, "Trop de couches"
80        CALL abort
81        ENDIF
82      ENDDO
83
84      CALL put_field("ALBE","albedo de surface",falbe)
85      CALL put_field("solsw","Rayonnement solaire a la surface",solsw)
86      CALL put_field("sollw","Rayonnement IR a la surface",sollw)
87      CALL put_field("fder","Derive de flux",fder)
88      CALL put_field("dlw","Derivee flux IR",dlw)
89      CALL put_field("sollwdown","Flux IR vers le bas a la surface",sollwdown)
90      CALL put_field("RADS","Rayonnement net a la surface",radsol)
91      CALL put_field("ZMEA","zmea Orographie sous-maille",zmea)
92      CALL put_field("ZSTD","zstd Orographie sous-maille",zstd)
93      CALL put_field("ZSIG","zsig Orographie sous-maille",zsig)
94      CALL put_field("ZGAM","zgam Orographie sous-maille",zgam)
95      CALL put_field("ZTHE","zthe Orographie sous-maille",zthe)
96      CALL put_field("ZPIC","zpic Orographie sous-maille",zpic)
97      CALL put_field("ZVAL","zval Orographie sous-maille",zval)
98
99      CALL put_field("TANCIEN","T Previous iteration",t_ancien)
100
101! close file
102
103      CALL close_restartphy
104!$OMP BARRIER
105
106      END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.