LMDZ
dynetat0_loc.f90
Go to the documentation of this file.
1 SUBROUTINE dynetat0_loc(fichnom,vcov,ucov,teta,q,masse,ps,phis,time)
2 !
3 !-------------------------------------------------------------------------------
4 ! Authors: P. Le Van , L.Fairhead
5 !-------------------------------------------------------------------------------
6 ! Purpose: Initial state reading.
7 !-------------------------------------------------------------------------------
8  USE parallel_lmdz
9  USE infotrac
10  USE netcdf, ONLY: nf90_open, nf90_inquire_dimension, nf90_inq_varid, &
11  nf90_nowrite, nf90_close, nf90_inquire_variable, nf90_get_var, nf90_noerr
12  USE control_mod, ONLY: planet_type
13  USE assert_eq_m, ONLY: assert_eq
14  IMPLICIT NONE
15  include "dimensions.h"
16  include "paramet.h"
17  include "temps.h"
18  include "comconst.h"
19  include "comvert.h"
20  include "comgeom.h"
21  include "ener.h"
22  include "description.h"
23  include "serre.h"
24  include "logic.h"
25  include "iniprint.h"
26 !===============================================================================
27 ! Arguments:
28  CHARACTER(LEN=*), INTENT(IN) :: fichnom !--- FILE NAME
29  REAL, INTENT(OUT) :: vcov(ijb_v:ije_v,llm) !--- V COVARIANT WIND
30  REAL, INTENT(OUT) :: ucov(ijb_u:ije_u,llm) !--- U COVARIANT WIND
31  REAL, INTENT(OUT) :: teta(ijb_u:ije_u,llm) !--- POTENTIAL TEMP.
32  REAL, INTENT(OUT) :: q(ijb_u:ije_u,llm,nqtot)!--- TRACERS
33  REAL, INTENT(OUT) :: masse(ijb_u:ije_u,llm) !--- MASS PER CELL
34  REAL, INTENT(OUT) :: ps(ijb_u:ije_u) !--- GROUND PRESSURE
35  REAL, INTENT(OUT) :: phis(ijb_u:ije_u) !--- GEOPOTENTIAL
36 !===============================================================================
37 ! Local variables:
38  CHARACTER(LEN=256) :: msg, var, modname
39  INTEGER, PARAMETER :: length=100
40  INTEGER :: iq, fID, vID, idecal, ierr
41  REAL :: time, tab_cntrl(length) !--- RUN PARAMS TABLE
42  REAL, ALLOCATABLE :: vcov_glo(:,:),masse_glo(:,:), ps_glo(:)
43  REAL, ALLOCATABLE :: ucov_glo(:,:), q_glo(:,:), phis_glo(:)
44  REAL, ALLOCATABLE :: teta_glo(:,:)
45 !-------------------------------------------------------------------------------
46  modname="dynetat0_loc"
47 
48 !--- Initial state file opening
49  var=fichnom
50  CALL err(nf90_open(var,nf90_nowrite,fid),"open",var)
51  CALL get_var1("controle",tab_cntrl)
52 
53 !!! AS: idecal is a hack to be able to read planeto starts...
54 !!! .... while keeping everything OK for LMDZ EARTH
55  IF(planet_type=="generic") THEN
56  WRITE(lunout,*)'NOTE NOTE NOTE : Planeto-like start files'
57  idecal = 4
58  annee_ref = 2000
59  ELSE
60  WRITE(lunout,*)'NOTE NOTE NOTE : Earth-like start files'
61  idecal = 5
62  annee_ref = tab_cntrl(5)
63  END IF
64  im = tab_cntrl(1)
65  jm = tab_cntrl(2)
66  lllm = tab_cntrl(3)
67  day_ref = tab_cntrl(4)
68  rad = tab_cntrl(idecal+1)
69  omeg = tab_cntrl(idecal+2)
70  g = tab_cntrl(idecal+3)
71  cpp = tab_cntrl(idecal+4)
72  kappa = tab_cntrl(idecal+5)
73  daysec = tab_cntrl(idecal+6)
74  dtvr = tab_cntrl(idecal+7)
75  etot0 = tab_cntrl(idecal+8)
76  ptot0 = tab_cntrl(idecal+9)
77  ztot0 = tab_cntrl(idecal+10)
78  stot0 = tab_cntrl(idecal+11)
79  ang0 = tab_cntrl(idecal+12)
80  pa = tab_cntrl(idecal+13)
81  preff = tab_cntrl(idecal+14)
82 !
83  clon = tab_cntrl(idecal+15)
84  clat = tab_cntrl(idecal+16)
85  grossismx = tab_cntrl(idecal+17)
86  grossismy = tab_cntrl(idecal+18)
87 !
88  IF ( tab_cntrl(idecal+19)==1. ) THEN
89  fxyhypb = .true.
90 ! dzoomx = tab_cntrl(25)
91 ! dzoomy = tab_cntrl(26)
92 ! taux = tab_cntrl(28)
93 ! tauy = tab_cntrl(29)
94  ELSE
95  fxyhypb = .false.
96  ysinus = tab_cntrl(idecal+22)==1.
97  END IF
98 
99  day_ini = tab_cntrl(30)
100  itau_dyn = tab_cntrl(31)
101 ! start_time = tab_cntrl(32) ????
102 
103 !-------------------------------------------------------------------------------
104  WRITE(lunout,*)trim(modname)//': rad,omeg,g,cpp,kappa',rad,omeg,g,cpp,kappa
105  CALL check_dim(im,iim,'im','im')
106  CALL check_dim(jm,jjm,'jm','jm')
107  CALL check_dim(lllm,llm,'lm','lllm')
108  CALL get_var1("rlonu",rlonu)
109  CALL get_var1("rlatu",rlatu)
110  CALL get_var1("rlonv",rlonv)
111  CALL get_var1("rlatv",rlatv)
112  CALL get_var1("cu" ,cu)
113  CALL get_var1("cv" ,cv)
114  CALL get_var1("aire",aire)
115 
116  var="temps"
117  IF(nf90_inq_varid(fid,var,vid)/=nf90_noerr) THEN
118  WRITE(lunout,*)trim(modname)//": missing field <temps>"
119  WRITE(lunout,*)trim(modname)//": trying with <Time>"; var="Time"
120  CALL err(nf90_inq_varid(fid,var,vid),"inq",var)
121  END IF
122  CALL err(nf90_get_var(fid,vid,time),"get",var)
123 
124  ALLOCATE(phis_glo(ip1jmp1))
125  CALL get_var1("phisinit",phis_glo)
126  phis(ijb_u:ije_u) =phis_glo(ijb_u:ije_u); DEALLOCATE(phis_glo)
127 
128  ALLOCATE(ucov_glo(ip1jmp1,llm))
129  CALL get_var2("ucov",ucov_glo)
130  ucov(ijb_u:ije_u,:)=ucov_glo(ijb_u:ije_u,:); DEALLOCATE(ucov_glo)
131 
132  ALLOCATE(vcov_glo(ip1jm,llm))
133  CALL get_var2("vcov",vcov_glo)
134  vcov(ijb_v:ije_v,:)=vcov_glo(ijb_v:ije_v,:); DEALLOCATE(vcov_glo)
135 
136  ALLOCATE(teta_glo(ip1jmp1,llm))
137  CALL get_var2("teta",teta_glo)
138  teta(ijb_u:ije_u,:)=teta_glo(ijb_u:ije_u,:); DEALLOCATE(teta_glo)
139 
140  ALLOCATE(masse_glo(ip1jmp1,llm))
141  CALL get_var2("masse",masse_glo)
142  masse(ijb_u:ije_u,:)=masse_glo(ijb_u:ije_u,:); DEALLOCATE(masse_glo)
143 
144  ALLOCATE(ps_glo(ip1jmp1))
145  CALL get_var1("ps",ps_glo)
146  ps(ijb_u:ije_u) = ps_glo(ijb_u:ije_u); DEALLOCATE(ps_glo)
147 
148 !--- Tracers
149  ALLOCATE(q_glo(ip1jmp1,llm))
150  DO iq=1,nqtot
151  var=tname(iq)
152  IF(nf90_inq_varid(fid,var,vid)==nf90_noerr) THEN
153  CALL get_var2(var,q_glo); q(ijb_u:ije_u,:,iq)=q_glo(ijb_u:ije_u,:); cycle
154  END IF
155  WRITE(lunout,*)trim(modname)//": Tracer <"//trim(var)//"> is missing"
156  WRITE(lunout,*)" It is hence initialized to zero"
157  q(ijb_u:ije_u,:,iq)=0.
158  !--- CRisi: for isotops, theoretical initialization using very simplified
159  ! Rayleigh distillation las.
160  IF(ok_isotopes.AND.iso_num(iq)>0) THEN
161  IF(zone_num(iq)==0) q(:,:,iq)=q(:,:,iqpere(iq))*tnat(iso_num(iq)) &
162  & *(q(:,:,iqpere(iq))/30.e-3)**(alpha_ideal(iso_num(iq))-1)
163  IF(zone_num(iq)==1) q(:,:,iq)=q(:,:,iqiso(iso_indnum(iq),phase_num(iq)))
164  END IF
165  END DO
166  DEALLOCATE(q_glo)
167  CALL err(nf90_close(fid),"close",fichnom)
168  day_ini=day_ini+int(time)
169  time=time-int(time)
170 
171 
172  CONTAINS
173 
174 
175 SUBROUTINE check_dim(n1,n2,str1,str2)
176  INTEGER, INTENT(IN) :: n1, n2
177  CHARACTER(LEN=*), INTENT(IN) :: str1, str2
178  CHARACTER(LEN=256) :: s1, s2
179  IF(n1/=n2) THEN
180  s1='value of '//trim(str1)//' ='
181  s2=' read in starting file differs from parametrized '//trim(str2)//' ='
182  WRITE(msg,'(10x,a,i4,2x,a,i4)'),s1,n1,s2,n2
183  CALL abort_gcm(trim(modname),trim(msg),1)
184  END IF
185 END SUBROUTINE check_dim
186 
187 
188 SUBROUTINE get_var1(var,v)
189  CHARACTER(LEN=*), INTENT(IN) :: var
190  REAL, INTENT(OUT) :: v(:)
191  REAL, ALLOCATABLE :: w2(:,:), w3(:,:,:)
192  INTEGER :: nn(3), dids(3), k, nd, ntot
193 
194  CALL err(nf90_inq_varid(fid,var,vid),"inq",var)
195  ierr=nf90_inquire_variable(fid,vid,ndims=nd)
196  IF(nd==1) THEN
197  CALL err(nf90_get_var(fid,vid,v),"get",var); RETURN
198  END IF
199  ierr=nf90_inquire_variable(fid,vid,dimids=dids)
200  DO k=1,nd; ierr=nf90_inquire_dimension(fid,dids(k),len=nn(k)); END DO
201  ntot=product(nn(1:nd))
202  SELECT CASE(nd)
203  CASE(2); ALLOCATE(w2(nn(1),nn(2)))
204  CALL err(nf90_get_var(fid,vid,w2),"get",var)
205  v=reshape(w2,[ntot]); DEALLOCATE(w2)
206  CASE(3); ALLOCATE(w3(nn(1),nn(2),nn(3)))
207  CALL err(nf90_get_var(fid,vid,w3),"get",var)
208  v=reshape(w3,[ntot]); DEALLOCATE(w3)
209  END SELECT
210 END SUBROUTINE get_var1
211 
212 
213 SUBROUTINE get_var2(var,v)
214  CHARACTER(LEN=*), INTENT(IN) :: var
215  REAL, INTENT(OUT) :: v(:,:)
216  REAL, ALLOCATABLE :: w4(:,:,:,:)
217  INTEGER :: nn(4), dids(4), k, nd
218  CALL err(nf90_inq_varid(fid,var,vid),"inq",var)
219  ierr=nf90_inquire_variable(fid,vid,dimids=dids,ndims=nd)
220  DO k=1,nd; ierr=nf90_inquire_dimension(fid,dids(k),len=nn(k)); END DO
221  ALLOCATE(w4(nn(1),nn(2),nn(3),nn(4)))
222  CALL err(nf90_get_var(fid,vid,w4),"get",var)
223  v=reshape(w4,[nn(1)*nn(2),nn(3)]); DEALLOCATE(w4)
224 END SUBROUTINE get_var2
225 
226 
227 SUBROUTINE err(ierr,typ,nam)
228  INTEGER, INTENT(IN) :: ierr !--- NetCDF ERROR CODE
229  CHARACTER(LEN=*), INTENT(IN) :: typ !--- TYPE OF OPERATION
230  CHARACTER(LEN=*), INTENT(IN) :: nam !--- FIELD/FILE NAME
231  IF(ierr==nf90_noerr) RETURN
232  SELECT CASE(typ)
233  CASE('inq'); msg="Field <"//trim(nam)//"> is missing"
234  CASE('get'); msg="Reading failed for <"//trim(nam)//">"
235  CASE('open'); msg="File opening failed for <"//trim(nam)//">"
236  CASE('close'); msg="File closing failed for <"//trim(nam)//">"
237  END SELECT
238  CALL abort_gcm(trim(modname),trim(msg),ierr)
239 END SUBROUTINE err
240 
241 END SUBROUTINE dynetat0_loc
!$Id && itau_dyn
Definition: temps.h:15
!$Header llmm1 INTEGER ip1jmp1
Definition: paramet.h:14
!$Header!c!c!c include serre h!c REAL && grossismx
Definition: serre.h:8
!$Id mode_top_bound COMMON comconstr g
Definition: comconst.h:7
real, dimension(niso_possibles), save tnat
Definition: infotrac.F90:47
!$Id preff
Definition: comvert.h:8
subroutine get_var1(var, v)
Definition: dynetat0.f90:165
!$Id mode_top_bound COMMON comconstr kappa
Definition: comconst.h:7
!$Header!c!c!c include serre h!c REAL clon
Definition: serre.h:8
!$Id mode_top_bound COMMON comconstr omeg dissip_zref ihf INTEGER im
Definition: comconst.h:7
!$Id jm
Definition: comconst.h:7
integer, dimension(:), allocatable, save phase_num
Definition: infotrac.F90:53
character(len=10), save planet_type
Definition: control_mod.F90:32
subroutine abort_gcm(modname, message, ierr)
Definition: abort_gcm.F:7
!$Id Turb_fcg_gcssold get_uvd hqturb_gcssold endif!large scale llm day day1 day day1 *dt_toga endif!time annee_ref dt_toga u_toga vq_toga w_prof vq_prof llm day day1 day day1 *dt_dice endif!time annee_ref dt_dice swup_dice vg_dice omega_dice tg_prof vg_profd w_profd omega_profd!do llm!print llm l llm
!$Header!CDK comgeom COMMON comgeom aire
Definition: comgeom.h:25
!$Header!CDK comgeom COMMON comgeom rlatu
Definition: comgeom.h:25
integer, save nqtot
Definition: infotrac.F90:6
integer, dimension(:,:), allocatable, save iqiso
Definition: infotrac.F90:49
integer, save ijb_v
!$Header llmm1 INTEGER ip1jm
Definition: paramet.h:14
!$Id && day_ini
Definition: temps.h:15
subroutine err(ierr, typ, nam)
Definition: dynetat0.f90:189
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
!$Id etot0
Definition: ener.h:11
!$Id mode_top_bound COMMON comconstr rad
Definition: comconst.h:7
subroutine get_var2(var, v)
Definition: dynetat0.f90:173
!$Id day_ref
Definition: temps.h:15
!$Id fxyhypb
Definition: logic.h:10
integer, dimension(:), allocatable, save zone_num
Definition: infotrac.F90:52
!$Id mode_top_bound COMMON comconstr cpp
Definition: comconst.h:7
!$Id mode_top_bound COMMON comconstr daysec
Definition: comconst.h:7
!$Header!CDK comgeom COMMON comgeom rlonu
Definition: comgeom.h:25
!$Id ztot0
Definition: ener.h:11
!$Header!CDK comgeom COMMON comgeom rlatv
Definition: comgeom.h:25
character(len=20), dimension(:), allocatable, save tname
Definition: infotrac.F90:18
!$Id && pa
Definition: comvert.h:8
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
!$Id!Parameters for parameters that control the rate of approach!to quasi equilibrium noff nlm real tlcrit real entp real sigd real coeffs real dtmax real cu real betad real damp real delta COMMON cvparam nlm tlcrit sigd coeffs cu
Definition: cvparam.h:12
!$Id lllm
Definition: comconst.h:7
integer, save ije_v
!$Header!c!c!c include serre h!c REAL grossismy
Definition: serre.h:8
!$Id mode_top_bound COMMON comconstr dtvr
Definition: comconst.h:7
real, dimension(niso_possibles), save alpha_ideal
Definition: infotrac.F90:47
c c zjulian c cym CALL iim cym klev iim
Definition: ini_bilKP_ave.h:24
!$Id stot0
Definition: ener.h:11
!$Header!c!c!c include serre h!c REAL clat
Definition: serre.h:8
logical, save ok_isotopes
Definition: infotrac.F90:44
subroutine dynetat0_loc(fichnom, vcov, ucov, teta, q, masse, ps, phis, time)
Definition: dynetat0_loc.f90:2
integer, dimension(:), allocatable, save iqpere
Definition: infotrac.F90:33
!$Header!CDK comgeom COMMON comgeom cv
Definition: comgeom.h:25
integer, save ije_u
integer, dimension(:), allocatable, save iso_num
Definition: infotrac.F90:50
!$Id ptot0
Definition: ener.h:11
integer, dimension(:), allocatable, save iso_indnum
Definition: infotrac.F90:51
!$Id annee_ref
Definition: temps.h:15
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7
integer, save ijb_u
subroutine check_dim(n1, n2, str1, str2)
Definition: dynetat0.f90:152
!$Header!CDK comgeom COMMON comgeom rlonv
Definition: comgeom.h:25