/[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 67 by guez, Tue Oct 2 15:50:56 2012 UTC revision 68 by guez, Wed Nov 14 16:59:30 2012 UTC
# Line 21  contains Line 21  contains
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
     use disvert_m, only: ap, bp, preff, pa  
24      use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref      use conf_gcm_m, only: day_step, iphysiq, dayref, anneeref
25      use dimens_m, only: iim, jjm, llm, nqmx      use dimens_m, only: iim, jjm, llm, nqmx
26      use dimphy, only: zmasq      use dimphy, only: zmasq
27      use dimsoil, only: nsoilmx      use dimsoil, only: nsoilmx
28        use disvert_m, only: ap, bp, preff, pa
29      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
30      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
31      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
     USE flincom, only: flinclo, flinopen_nozoom, flininfo  
32      use geopot_m, only: geopot      use geopot_m, only: geopot
33      use grid_atob, only: grille_m      use grid_atob, only: grille_m
34      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
# Line 41  contains Line 40  contains
40      use inigeom_m, only: inigeom      use inigeom_m, only: inigeom
41      use massdair_m, only: massdair      use massdair_m, only: massdair
42      use netcdf, only: nf90_nowrite      use netcdf, only: nf90_nowrite
43      use netcdf95, only: nf95_open, nf95_close, nf95_get_var, nf95_inq_varid      use netcdf95, only: nf95_close, nf95_get_var, nf95_gw_var, &
44             nf95_inq_varid, nf95_open
45      use nr_util, only: pi      use nr_util, only: pi
46      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
47      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
# Line 50  contains Line 50  contains
50      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz      use regr_lat_time_coefoz_m, only: regr_lat_time_coefoz
51      use regr_pr_o3_m, only: regr_pr_o3      use regr_pr_o3_m, only: regr_pr_o3
52      use serre, only: alphax      use serre, only: alphax
53        use startdyn, only: start_init_dyn
54      USE start_init_orog_m, only: start_init_orog, mask, phis      USE start_init_orog_m, only: start_init_orog, mask, phis
55      use start_init_phys_m, only: start_init_phys      use start_init_phys_m, only: start_init_phys
     use startdyn, only: start_init_dyn  
56      use start_inter_3d_m, only: start_inter_3d      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    
# Line 65  contains Line 65  contains
65      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, tpot      REAL, dimension(iim + 1, jjm + 1, llm):: ucov, t3d, tpot
66      REAL vcov(iim + 1, jjm, llm)      REAL vcov(iim + 1, jjm, llm)
67    
68      REAL q3d(iim + 1, jjm + 1, llm, nqmx)      REAL q(iim + 1, jjm + 1, llm, nqmx)
69      ! (mass fractions of trace species      ! (mass fractions of trace species
70      ! "q3d(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)"      ! "q(i, j, l)" is at longitude "rlonv(i)", latitude "rlatu(j)"
71      ! and pressure level "pls(i, j, l)".)      ! and pressure level "pls(i, j, l)".)
72    
73      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor      real qsat(iim + 1, jjm + 1, llm) ! mass fraction of saturating water vapor
# Line 93  contains Line 93  contains
93      REAL t_ancien(klon, llm), q_ancien(klon, llm)      !      REAL t_ancien(klon, llm), q_ancien(klon, llm)      !
94      REAL run_off_lic_0(klon)      REAL run_off_lic_0(klon)
95      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)      real clwcon(klon, llm), rnebcon(klon, llm), ratqs(klon, llm)
96      ! déclarations pour lecture glace de mer  
97      INTEGER iml_lic, jml_lic, llm_tmp, ttm_tmp      ! Déclarations pour lecture glace de mer :
98      INTEGER itaul(1), fid, ncid, varid      INTEGER iml_lic, jml_lic
99      REAL lev(1), date      INTEGER ncid, varid
100      REAL, ALLOCATABLE:: lon_lic(:, :), lat_lic(:, :)      REAL, pointer:: dlon_lic(:), dlat_lic(:)
     REAL, ALLOCATABLE:: dlon_lic(:), dlat_lic(:)  
101      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice      REAL, ALLOCATABLE:: fraclic(:, :) ! fraction land ice
102      REAL flic_tmp(iim + 1, jjm + 1) !fraction land ice temporary      REAL flic_tmp(iim + 1, jjm + 1) ! fraction land ice temporary
103    
104      INTEGER l, ji      INTEGER l, ji
105    
# Line 112  contains Line 111  contains
111      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)      REAL pbaru(ip1jmp1, llm), pbarv(ip1jm, llm)
112      REAL w(ip1jmp1, llm)      REAL w(ip1jmp1, llm)
113      REAL phystep      REAL phystep
     real trash  
114    
115      !---------------------------------      !---------------------------------
116    
# Line 186  contains Line 184  contains
184      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
185    
186      ! Water vapor:      ! Water vapor:
187      call start_inter_3d('R', rlonu, rlatv, pls, q3d(:, :, :, 1))      call start_inter_3d('R', rlonu, rlatv, pls, q(:, :, :, 1))
188      q3d(:, :, :, 1) = 0.01 * q3d(:, :, :, 1) * qsat      q(:, :, :, 1) = 0.01 * q(:, :, :, 1) * qsat
189      WHERE (q3d(:, :, :, 1) < 0.) q3d(:, :, :, 1) = 1E-10      WHERE (q(:, :, :, 1) < 0.) q(:, :, :, 1) = 1E-10
190      DO l = 1, llm      DO l = 1, llm
191         q3d(:, 1, l, 1) = SUM(aire_2d(:, 1) * q3d(:, 1, l, 1)) / apoln         q(:, 1, l, 1) = SUM(aire_2d(:, 1) * q(:, 1, l, 1)) / apoln
192         q3d(:, jjm + 1, l, 1) &         q(:, jjm + 1, l, 1) &
193              = SUM(aire_2d(:, jjm + 1) * q3d(:, jjm + 1, l, 1)) / apols              = SUM(aire_2d(:, jjm + 1) * q(:, jjm + 1, l, 1)) / apols
194      ENDDO      ENDDO
195    
196      q3d(:, :, :, 2:4) = 0. ! liquid water, radon and lead      q(:, :, :, 2:4) = 0. ! liquid water, radon and lead
197    
198      if (nqmx >= 5) then      if (nqmx >= 5) then
199         ! Ozone:         ! Ozone:
200         call regr_lat_time_coefoz         call regr_lat_time_coefoz
201         call regr_pr_o3(q3d(:, :, :, 5))         call regr_pr_o3(q(:, :, :, 5))
202         ! Convert from mole fraction to mass fraction:         ! Convert from mole fraction to mass fraction:
203         q3d(:, :, :, 5) = q3d(:, :, :, 5)  * 48. / 29.         q(:, :, :, 5) = q(:, :, :, 5)  * 48. / 29.
204      end if      end if
205    
206      tsol = pack(tsol_2d, dyn_phy)      tsol = pack(tsol_2d, dyn_phy)
# Line 223  contains Line 221  contains
221      ! On initialise les sous-surfaces.      ! On initialise les sous-surfaces.
222      ! Lecture du fichier glace de terre pour fixer la fraction de terre      ! Lecture du fichier glace de terre pour fixer la fraction de terre
223      ! et de glace de terre :      ! et de glace de terre :
224      CALL flininfo("landiceref.nc", iml_lic, jml_lic, llm_tmp, &  
          ttm_tmp, fid)  
     ALLOCATE(lat_lic(iml_lic, jml_lic))  
     ALLOCATE(lon_lic(iml_lic, jml_lic))  
     ALLOCATE(dlon_lic(iml_lic))  
     ALLOCATE(dlat_lic(jml_lic))  
     ALLOCATE(fraclic(iml_lic, jml_lic))  
     CALL flinopen_nozoom(iml_lic, jml_lic, &  
          llm_tmp, lon_lic, lat_lic, lev, ttm_tmp, itaul, date, trash,  &  
          fid)  
     CALL flinclo(fid)  
225      call nf95_open("landiceref.nc", nf90_nowrite, ncid)      call nf95_open("landiceref.nc", nf90_nowrite, ncid)
226    
227        call nf95_inq_varid(ncid, 'longitude', varid)
228        call nf95_gw_var(ncid, varid, dlon_lic)
229        iml_lic = size(dlon_lic)
230    
231        call nf95_inq_varid(ncid, 'latitude', varid)
232        call nf95_gw_var(ncid, varid, dlat_lic)
233        jml_lic = size(dlat_lic)
234    
235      call nf95_inq_varid(ncid, 'landice', varid)      call nf95_inq_varid(ncid, 'landice', varid)
236        ALLOCATE(fraclic(iml_lic, jml_lic))
237      call nf95_get_var(ncid, varid, fraclic)      call nf95_get_var(ncid, varid, fraclic)
238    
239      call nf95_close(ncid)      call nf95_close(ncid)
240    
241      ! Interpolation sur la grille T du modèle :      ! Interpolation sur la grille T du modèle :
242      PRINT *, 'Dimensions de "landice"'      PRINT *, 'Dimensions de "landiceref.nc"'
243      print *, "iml_lic = ", iml_lic      print *, "iml_lic = ", iml_lic
244      print *, "jml_lic = ", jml_lic      print *, "jml_lic = ", jml_lic
245    
246      ! Si les coordonnées sont en degrés, on les transforme :      ! Si les coordonnées sont en degrés, on les transforme :
247      IF (MAXVAL( lon_lic ) > pi)  THEN      IF (MAXVAL( dlon_lic ) > pi)  THEN
248         lon_lic = lon_lic * pi / 180.         dlon_lic = dlon_lic * pi / 180.
249      ENDIF      ENDIF
250      IF (maxval( lat_lic ) > pi) THEN      IF (maxval( dlat_lic ) > pi) THEN
251         lat_lic = lat_lic * pi/ 180.         dlat_lic = dlat_lic * pi/ 180.
252      ENDIF      ENDIF
253    
     dlon_lic = lon_lic(:, 1)  
     dlat_lic = lat_lic(1, :)  
   
254      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &      flic_tmp(:iim, :) = grille_m(dlon_lic, dlat_lic, fraclic, rlonv(:iim), &
255           rlatu)           rlatu)
256      flic_tmp(iim + 1, :) = flic_tmp(1, :)      flic_tmp(iim + 1, :) = flic_tmp(1, :)
257    
258        deallocate(dlon_lic, dlat_lic) ! pointers
259    
260      ! Passage sur la grille physique      ! Passage sur la grille physique
261      pctsrf = 0.      pctsrf = 0.
262      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)      pctsrf(:, is_lic) = pack(flic_tmp, dyn_phy)
# Line 312  contains Line 310  contains
310      CALL caldyn0(ucov, vcov, tpot, psol, masse, pk, phis, phi, w, pbaru, &      CALL caldyn0(ucov, vcov, tpot, psol, masse, pk, phis, phi, w, pbaru, &
311           pbarv)           pbarv)
312      CALL dynredem0("start.nc", dayref, phis)      CALL dynredem0("start.nc", dayref, phis)
313      CALL dynredem1("start.nc", vcov, ucov, tpot, q3d, masse, psol, itau=0)      CALL dynredem1("start.nc", vcov, ucov, tpot, q, masse, psol, itau=0)
314    
315      ! Ecriture état initial physique:      ! Ecriture état initial physique:
316      print *, "iphysiq = ", iphysiq      print *, "iphysiq = ", iphysiq

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

  ViewVC Help
Powered by ViewVC 1.1.21