/[lmdze]/trunk/libf/dyn3d/etat0.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/etat0.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 48 by guez, Tue Jul 19 12:54:20 2011 UTC revision 67 by guez, Tue Oct 2 15:50:56 2012 UTC
# Line 17  contains Line 17  contains
17    
18      ! From "etat0_netcdf.F", version 1.3 2005/05/25 13:10:09      ! From "etat0_netcdf.F", version 1.3 2005/05/25 13:10:09
19    
     ! This subroutine creates "mask".  
   
20      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
21      use comconst, only: dtvr, daysec, cpp, kappa      use comconst, only: dtvr, daysec, cpp, kappa
22      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
23           cu_2d, cv_2d           cu_2d, cv_2d
24      use comvert, only: ap, bp, preff, pa      use disvert_m, only: ap, bp, preff, pa
25      use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref      use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref
26      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
27      use dimphy, only: zmasq      use dimphy, only: zmasq
# Line 35  contains Line 33  contains
33      use geopot_m, only: geopot      use geopot_m, only: geopot
34      use grid_atob, only: grille_m      use grid_atob, only: grille_m
35      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
36      use histcom, only: histclo      use histclo_m, only: histclo
37      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
38      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
39      use inidissip_m, only: inidissip      use inidissip_m, only: inidissip
40        use inifilr_m, only: inifilr
41      use inigeom_m, only: inigeom      use inigeom_m, only: inigeom
42        use massdair_m, only: massdair
43      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
44      use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid      use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid
45      use nr_util, only: pi      use nr_util, only: pi
# Line 52  contains Line 52  contains
52      use serre, only: alphax      use serre, only: alphax
53      USE start_init_orog_m, only: start_init_orog, mask, phis      USE start_init_orog_m, only: start_init_orog, mask, phis
54      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
55      use startdyn, only: start_inter_3d, start_init_dyn      use startdyn, only: start_init_dyn
56        use start_inter_3d_m, only: start_inter_3d
57      use temps, only: itau_phy, annee_ref, day_ref      use temps, only: itau_phy, annee_ref, day_ref
58    
59      ! Variables local to the procedure:      ! Variables local to the procedure:
# Line 61  contains Line 62  contains
62      ! (latitude and longitude of a point of the scalar grid identified      ! (latitude and longitude of a point of the scalar grid identified
63      ! by a simple index, in °)      ! by a simple index, in °)
64    
65      REAL, dimension(iim + 1, jjm + 1, llm):: uvent, t3d, tpot      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, tpot
66      REAL vvent(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
67    
68      REAL q3d(iim + 1, jjm + 1, llm, nqmx)      REAL q3d(iim + 1, jjm + 1, llm, nqmx)
69      ! (mass fractions of trace species      ! (mass fractions of trace species
# Line 149  contains Line 150  contains
150      ! Compute pressure on intermediate levels:      ! Compute pressure on intermediate levels:
151      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol      forall(l = 1: llm + 1) p3d(:, :, l) = ap(l) + bp(l) * psol
152      CALL exner_hyb(psol, p3d, pks, pk)      CALL exner_hyb(psol, p3d, pks, pk)
153      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'      IF (MINVAL(pk) == MAXVAL(pk)) then
154           print *, '"pk" should not be constant'
155           stop 1
156        end IF
157    
158      pls = preff * (pk / cpp)**(1. / kappa)      pls = preff * (pk / cpp)**(1. / kappa)
159      PRINT *, "minval(pls) = ", minval(pls)      PRINT *, "minval(pls) = ", minval(pls)
160      print *, "maxval(pls) = ", maxval(pls)      print *, "maxval(pls) = ", maxval(pls)
161    
162      call start_inter_3d('U', rlonv, rlatv, pls, uvent)      call start_inter_3d('U', rlonv, rlatv, pls, ucov)
163      forall (l = 1: llm) uvent(:iim, :, l) = uvent(:iim, :, l) * cu_2d(:iim, :)      forall (l = 1: llm) ucov(:iim, :, l) = ucov(:iim, :, l) * cu_2d(:iim, :)
164      uvent(iim+1, :, :) = uvent(1, :, :)      ucov(iim+1, :, :) = ucov(1, :, :)
165    
166      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vvent)      call start_inter_3d('V', rlonu, rlatu(:jjm), pls(:, :jjm, :), vcov)
167      forall (l = 1: llm) vvent(:iim, :, l) = vvent(:iim, :, l) * cv_2d(:iim, :)      forall (l = 1: llm) vcov(:iim, :, l) = vcov(:iim, :, l) * cv_2d(:iim, :)
168      vvent(iim + 1, :, :) = vvent(1, :, :)      vcov(iim + 1, :, :) = vcov(1, :, :)
169    
170      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
171      PRINT *,  'minval(t3d) = ', minval(t3d)      PRINT *,  'minval(t3d) = ', minval(t3d)
# Line 216  contains Line 220  contains
220      zpic = pack(zpic_2d, dyn_phy)      zpic = pack(zpic_2d, dyn_phy)
221      zval = pack(zval_2d, dyn_phy)      zval = pack(zval_2d, dyn_phy)
222    
223      ! On initialise les sous-surfaces:      ! On initialise les sous-surfaces.
224      ! Lecture du fichier glace de terre pour fixer la fraction de terre      ! Lecture du fichier glace de terre pour fixer la fraction de terre
225      ! et de glace de terre:      ! et de glace de terre :
226      CALL flininfo("landiceref.nc", iml_lic, jml_lic, llm_tmp, &      CALL flininfo("landiceref.nc", iml_lic, jml_lic, llm_tmp, &
227           ttm_tmp, fid)           ttm_tmp, fid)
228      ALLOCATE(lat_lic(iml_lic, jml_lic))      ALLOCATE(lat_lic(iml_lic, jml_lic))
# Line 229  contains Line 233  contains
233      CALL flinopen_nozoom(iml_lic, jml_lic, &      CALL flinopen_nozoom(iml_lic, jml_lic, &
234           llm_tmp, lon_lic, lat_lic, lev, ttm_tmp, itaul, date, trash,  &           llm_tmp, lon_lic, lat_lic, lev, ttm_tmp, itaul, date, trash,  &
235           fid)           fid)
236        CALL flinclo(fid)
237      call nf95_open("landiceref.nc", nf90_nowrite, ncid)      call nf95_open("landiceref.nc", nf90_nowrite, ncid)
238      call nf95_inq_varid(ncid, 'landice', varid)      call nf95_inq_varid(ncid, 'landice', varid)
239      call nf95_get_var(ncid, varid, fraclic)      call nf95_get_var(ncid, varid, fraclic)
240      call nf95_close(ncid)      call nf95_close(ncid)
     CALL flinclo(fid)  
241    
242      ! Interpolation sur la grille T du modèle :      ! Interpolation sur la grille T du modèle :
243      PRINT *, 'Dimensions de "landice"'      PRINT *, 'Dimensions de "landice"'
# Line 305  contains Line 309  contains
309      annee_ref = anneeref      annee_ref = anneeref
310    
311      CALL geopot(ip1jmp1, tpot, pk , pks,  phis, phi)      CALL geopot(ip1jmp1, tpot, pk , pks,  phis, phi)
312      CALL caldyn0(uvent, vvent, tpot, psol, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, tpot, psol, masse, pk, phis, phi, w, pbaru, &
313           pbarv)           pbarv)
314      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", dayref, phis)
315      CALL dynredem1("start.nc", vvent, uvent, tpot, q3d, masse, psol, itau=0)      CALL dynredem1("start.nc", vcov, ucov, tpot, q3d, masse, psol, itau=0)
316    
317      ! Ecriture état initial physique:      ! Ecriture état initial physique:
318      print *, "iphysiq = ", iphysiq      print *, "iphysiq = ", iphysiq

Legend:
Removed from v.48  
changed lines
  Added in v.67

  ViewVC Help
Powered by ViewVC 1.1.21