source: trunk/LMDZ.TITAN/libf/phytitan/phyredem.F90 @ 1545

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

Venus and Titan GCMs:

Adaptation wrt previous changes for Titan and Venus where
longitude and latitude arrays (in phycommon/geometry_mod) were overwritten
with values from startphy.nc files, where values are given in degrees.
For the sake of homegeneity with other physics package, revert to "default"
behaviour: longitude/latitude are in radians and longitude_deg/latitude_deg
are in degrees.
Also added checking in phyetat0 that the longitude/latitude read in the
restartphy.nc files match the ones provided by the dynamics.

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_deg, latitude_deg
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) = chimpas
45      tab_cntrl(4) = solaire
46      tab_cntrl(5) = 0
47      tab_cntrl(6) = nbapp_rad
48      tab_cntrl(16)= nbapp_chim
49      tab_cntrl(17)= lsinit
50
51      IF( cycle_diurne ) tab_cntrl( 7 ) = 1.
52      IF(   soil_model ) tab_cntrl( 8 ) = 1.
53      IF(     ok_orodr ) tab_cntrl(10 ) = 1.
54      IF(     ok_orolf ) tab_cntrl(11 ) = 1.
55      IF( ok_gw_nonoro ) tab_cntrl(12 ) = 1.
56
57      tab_cntrl(13) = day_end
58      tab_cntrl(14) = annee_ref
59      tab_cntrl(15) = itau_phy
60
61      CALL put_var("controle","Parametres de controle",tab_cntrl)
62
63! coordinates
64
65      CALL put_field("longitude", &
66                     "Longitudes de la grille physique",longitude_deg)
67     
68      CALL put_field("latitude", &
69                     "Latitudes de la grille physique",latitude_deg)
70
71! variables
72
73      CALL put_field("TS","Temperature de surface",ftsol)
74
75      DO isoil=1, nsoilmx
76        IF (isoil.LE.99) THEN
77        WRITE(str2,'(i2.2)') isoil
78        CALL put_field("Tsoil"//str2, &
79                       "Temperature du sol No."//str2,ftsoil(:,isoil))
80        ELSE
81        PRINT*, "Trop de couches"
82        CALL abort
83        ENDIF
84      ENDDO
85
86      CALL put_field("ALBE","albedo de surface",falbe)
87      CALL put_field("solsw","Rayonnement solaire a la surface",solsw)
88      CALL put_field("sollw","Rayonnement IR a la surface",sollw)
89      CALL put_field("fder","Derive de flux",fder)
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("RESCH4","Reservoir CH4 a la surface",resch4)
100
101      CALL put_field("TANCIEN","T Previous iteration",t_ancien)
102
103! close file
104
105      CALL close_restartphy
106!$OMP BARRIER
107
108      END SUBROUTINE phyredem
Note: See TracBrowser for help on using the repository browser.