/[lmdze]/trunk/dyn3d/limit.f
ViewVC logotype

Diff of /trunk/dyn3d/limit.f

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

revision 254 by guez, Mon Feb 5 10:39:38 2018 UTC revision 276 by guez, Thu Jul 12 14:49:20 2018 UTC
# Line 4  module limit_mod Line 4  module limit_mod
4    
5  contains  contains
6    
7    SUBROUTINE limit    SUBROUTINE limit(pctsrf)
8    
9      ! Authors: L. Fairhead, Z. X. Li, P. Le Van      ! Authors: L. Fairhead, Z. X. Li, P. Le Van
10    
# Line 13  contains Line 13  contains
13      ! regular.      ! regular.
14    
15      use conf_dat2d_m, only: conf_dat2d      use conf_dat2d_m, only: conf_dat2d
16      use dimens_m, only: iim, jjm      use dimensions, only: iim, jjm
17      use dimphy, only: klon, zmasq      use dimphy, only: klon
18      use dynetat0_m, only: rlonu, rlatv      use dynetat0_m, only: rlonu, rlatv
     use etat0_mod, only: pctsrf  
19      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
20      use indicesol, only: epsfra, nbsrf, is_ter, is_oce, is_lic, is_sic      use indicesol, only: epsfra, is_ter, is_oce, is_lic, is_sic
21      use inter_barxy_m, only: inter_barxy      use inter_barxy_m, only: inter_barxy
22      use netcdf95, only: NF95_CLOSE, NF95_CREATE, NF95_DEF_DIM, nf95_def_var, &      use netcdf95, only: NF95_CLOSE, NF95_CREATE, NF95_DEF_DIM, nf95_def_var, &
23           nf95_enddef, nf95_get_var, nf95_gw_var, nf95_inq_dimid, &           nf95_enddef, nf95_get_var, nf95_gw_var, nf95_inq_dimid, &
# Line 28  contains Line 27  contains
27           NF90_UNLIMITED           NF90_UNLIMITED
28      use nr_util, only: assert      use nr_util, only: assert
29      use numer_rec_95, only: spline, splint      use numer_rec_95, only: spline, splint
30        use phyetat0_m, only: zmasq
31      use start_init_orog_m, only: mask      use start_init_orog_m, only: mask
32      use unit_nml_m, only: unit_nml      use unit_nml_m, only: unit_nml
33    
34        REAL, intent(inout):: pctsrf(:, :) ! (klon, nbsrf)
35        ! "pctsrf(i, :)" is the composition of the surface at horizontal
36        ! position "i".
37    
38      ! Local:      ! Local:
39    
40      LOGICAL:: extrap = .FALSE.      LOGICAL:: extrap = .FALSE.
41      ! (extrapolation de donn\'ees, comme pour les SST lorsque le fichier      ! (extrapolation de donn\'ees, comme pour les SST lorsque le fichier
42      ! ne contient pas uniquement des points oc\'eaniques)      ! ne contient pas uniquement des points oc\'eaniques)
43    
     REAL phy_alb(klon, 360)  
     REAL phy_sst(klon, 360)  
44      REAL phy_bil(klon, 360)      REAL phy_bil(klon, 360)
     REAL phy_rug(klon, 360)  
45      REAL phy_ice(klon)      REAL phy_ice(klon)
46    
     real pctsrf_t(klon, nbsrf, 360) ! composition of the surface  
   
47      ! Pour le champ de d\'epart:      ! Pour le champ de d\'epart:
48      INTEGER imdep, jmdep, lmdep      INTEGER imdep, jmdep, lmdep
49    
# Line 60  contains Line 59  contains
59      ! Pour l'inteprolation verticale :      ! Pour l'inteprolation verticale :
60      REAL, allocatable:: yder(:)      REAL, allocatable:: yder(:)
61    
62      INTEGER nid, ndim, ntim      INTEGER ndim, ntim
63      INTEGER id_tim      INTEGER varid_time
64      INTEGER id_SST, id_BILS, id_RUG, id_ALB      INTEGER id_SST, id_BILS, id_RUG, id_ALB
65      INTEGER id_FOCE, id_FSIC, id_FTER, id_FLIC      INTEGER id_FOCE, id_FSIC, id_FTER, id_FLIC
66    
67      INTEGER i, j, k, l      INTEGER i, j, k, l
68      INTEGER ncid, varid, dimid      INTEGER ncid, ncid_limit, varid, dimid
69    
70      REAL, parameter:: tmidmonth(12) = (/(15. + 30. * i, i = 0, 11)/)      REAL, parameter:: tmidmonth(12) = [(15. + 30. * i, i = 0, 11)]
71    
72      namelist /limit_nml/extrap      namelist /limit_nml/extrap
73    
# Line 80  contains Line 79  contains
79      read(unit=*, nml=limit_nml)      read(unit=*, nml=limit_nml)
80      write(unit_nml, nml=limit_nml)      write(unit_nml, nml=limit_nml)
81    
82        call NF95_CREATE("limit.nc", NF90_CLOBBER, ncid_limit)
83    
84        call NF95_PUT_ATT(ncid_limit, NF90_GLOBAL, "title", &
85             "Fichier conditions aux limites")
86        call NF95_DEF_DIM(ncid_limit, "points_physiques", klon, ndim)
87        call NF95_DEF_DIM(ncid_limit, "time", NF90_UNLIMITED, ntim)
88    
89        call NF95_DEF_VAR(ncid_limit, "TEMPS", NF90_FLOAT, ntim, varid_time)
90        call NF95_PUT_ATT(ncid_limit, varid_time, "title", "Jour dans l annee")
91    
92        call NF95_DEF_VAR(ncid_limit, "FOCE", NF90_FLOAT, dimids=[ndim, ntim], &
93             varid=id_foce)
94        call NF95_PUT_ATT(ncid_limit, id_FOCE, "title", "Fraction ocean")
95    
96        call NF95_DEF_VAR(ncid_limit, "FSIC", NF90_FLOAT, dimids=[ndim, ntim], &
97             varid=id_FSIC)
98        call NF95_PUT_ATT(ncid_limit, id_FSIC, "title", "Fraction glace de mer")
99    
100        call NF95_DEF_VAR(ncid_limit, "FTER", NF90_FLOAT, dimids=[ndim, ntim], &
101             varid=id_FTER)
102        call NF95_PUT_ATT(ncid_limit, id_FTER, "title", "Fraction terre")
103    
104        call NF95_DEF_VAR(ncid_limit, "FLIC", NF90_FLOAT, dimids=[ndim, ntim], &
105             varid=id_FLIC)
106        call NF95_PUT_ATT(ncid_limit, id_FLIC, "title", "Fraction land ice")
107    
108        call NF95_DEF_VAR(ncid_limit, "SST", NF90_FLOAT, dimids=[ndim, ntim], &
109             varid=id_SST)
110        call NF95_PUT_ATT(ncid_limit, id_SST, "title",  &
111             "Temperature superficielle de la mer")
112    
113        call NF95_DEF_VAR(ncid_limit, "BILS", NF90_FLOAT, dimids=[ndim, ntim], &
114             varid=id_BILS)
115        call NF95_PUT_ATT(ncid_limit, id_BILS, "title", &
116             "Reference flux de chaleur au sol")
117    
118        call NF95_DEF_VAR(ncid_limit, "ALB", NF90_FLOAT, dimids=[ndim, ntim], &
119             varid=id_ALB)
120        call NF95_PUT_ATT(ncid_limit, id_ALB, "title", "Albedo a la surface")
121    
122        call NF95_DEF_VAR(ncid_limit, "RUG", NF90_FLOAT, dimids=[ndim, ntim], &
123             varid=id_RUG)
124        call NF95_PUT_ATT(ncid_limit, id_RUG, "title", "Rugosite")
125    
126        call NF95_ENDDEF(ncid_limit)
127    
128        call NF95_PUT_VAR(ncid_limit, varid_time, [(k, k = 1, 360)])
129        
130      PRINT *, 'Processing rugosity...'      PRINT *, 'Processing rugosity...'
131    
132      call NF95_OPEN('Rugos.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('Rugos.nc', NF90_NOWRITE, ncid)
# Line 105  contains Line 152  contains
152      ! Read the primary variable day by day and regrid horizontally,      ! Read the primary variable day by day and regrid horizontally,
153      ! result in "champtime":      ! result in "champtime":
154      DO  l = 1, lmdep      DO  l = 1, lmdep
155         call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
156         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
157         CALL inter_barxy(dlon, dlat(:jmdep -1), LOG(champ), rlonu(:iim), &         CALL inter_barxy(dlon, dlat(:jmdep -1), LOG(champ), rlonu(:iim), &
158              rlatv, champtime(:, :, l))              rlatv, champtime(:, :, l))
# Line 131  contains Line 178  contains
178    
179      deallocate(champtime, yder)      deallocate(champtime, yder)
180      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
     forall (k = 1:360) phy_rug(:, k) = pack(champan(:, :, k), dyn_phy)  
181    
182      ! Process sea ice:      DO k = 1, 360
183           call NF95_PUT_VAR(ncid_limit, id_RUG, pack(champan(:, :, k), dyn_phy), &
184                start=[1, k])
185        ENDDO
186    
187      PRINT *, 'Processing sea ice...'      PRINT *, 'Processing sea ice...'
188      call NF95_OPEN('amipbc_sic_1x1.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('amipbc_sic_1x1.nc', NF90_NOWRITE, ncid)
# Line 160  contains Line 209  contains
209      ALLOCATE(dlon(imdep), dlat(jmdep))      ALLOCATE(dlon(imdep), dlat(jmdep))
210      call NF95_INQ_VARID(ncid, 'sicbcs', varid)      call NF95_INQ_VARID(ncid, 'sicbcs', varid)
211      DO l = 1, lmdep      DO l = 1, lmdep
212         call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
213         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
214         CALL inter_barxy(dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &         CALL inter_barxy(dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &
215              champtime(:, :, l))              champtime(:, :, l))
# Line 197  contains Line 246  contains
246         ! PB en attendant de mettre fraction de terre         ! PB en attendant de mettre fraction de terre
247         WHERE (phy_ice < EPSFRA) phy_ice = 0.         WHERE (phy_ice < EPSFRA) phy_ice = 0.
248    
249         pctsrf_t(:, is_ter, k) = pctsrf(:, is_ter)         pctsrf(:, is_sic) = max(phy_ice - pctsrf(:, is_lic), 0.)
        pctsrf_t(:, is_lic, k) = pctsrf(:, is_lic)  
        pctsrf_t(:, is_sic, k) = max(phy_ice - pctsrf_t(:, is_lic, k), 0.)  
250         ! Il y a des cas o\`u il y a de la glace dans landiceref et         ! Il y a des cas o\`u il y a de la glace dans landiceref et
251         ! pas dans AMIP         ! pas dans AMIP
252         WHERE (1. - zmasq < EPSFRA)         WHERE (1. - zmasq < EPSFRA)
253            pctsrf_t(:, is_sic, k) = 0.            pctsrf(:, is_sic) = 0.
254            pctsrf_t(:, is_oce, k) = 0.            pctsrf(:, is_oce) = 0.
255         elsewhere         elsewhere
256            where (pctsrf_t(:, is_sic, k) >= 1 - zmasq)            where (pctsrf(:, is_sic) >= 1 - zmasq)
257               pctsrf_t(:, is_sic, k) = 1. - zmasq               pctsrf(:, is_sic) = 1. - zmasq
258               pctsrf_t(:, is_oce, k) = 0.               pctsrf(:, is_oce) = 0.
259            ELSEwhere            ELSEwhere
260               pctsrf_t(:, is_oce, k) = 1. - zmasq - pctsrf_t(:, is_sic, k)               pctsrf(:, is_oce) = 1. - zmasq - pctsrf(:, is_sic)
261               where (pctsrf_t(:, is_oce, k) < EPSFRA)               where (pctsrf(:, is_oce) < EPSFRA)
262                  pctsrf_t(:, is_oce, k) = 0.                  pctsrf(:, is_oce) = 0.
263                  pctsrf_t(:, is_sic, k) = 1 - zmasq                  pctsrf(:, is_sic) = 1 - zmasq
264               end where               end where
265            end where            end where
266         end where         end where
267    
268         DO i = 1, klon         DO i = 1, klon
269            if (pctsrf_t(i, is_oce, k) < 0.) then            if (pctsrf(i, is_oce) < 0.) then
270               print *, 'Bad surface fraction: pctsrf_t(', i, &               print *, "k = ", k
271                    ', is_oce, ', k, ') = ', pctsrf_t(i, is_oce, k)               print *, 'Bad surface fraction: pctsrf(', i, ', is_oce) = ', &
272                      pctsrf(i, is_oce)
273            ENDIF            ENDIF
274            IF (abs(pctsrf_t(i, is_ter, k) + pctsrf_t(i, is_lic, k) &            IF (abs(sum(pctsrf(i, :)) - 1.) > EPSFRA) THEN
275                 + pctsrf_t(i, is_oce, k) + pctsrf_t(i, is_sic, k) - 1.) &               print *, "k = ", k
                > EPSFRA) THEN  
276               print *, 'Bad surface fraction:'               print *, 'Bad surface fraction:'
277               print *, "pctsrf_t(", i, ", :, ", k, ") = ", &               print *, "pctsrf(", i, ", :) = ", pctsrf(i, :)
                   pctsrf_t(i, :, k)  
278               print *, "phy_ice(", i, ") = ", phy_ice(i)               print *, "phy_ice(", i, ") = ", phy_ice(i)
279            ENDIF            ENDIF
280         END DO         END DO
     ENDDO  
281    
282           call NF95_PUT_VAR(ncid_limit, id_FOCE, pctsrf(:, is_oce), start=[1, k])
283           call NF95_PUT_VAR(ncid_limit, id_FSIC, pctsrf(:, is_sic), start=[1, k])
284           call NF95_PUT_VAR(ncid_limit, id_FTER, pctsrf(:, is_ter), start=[1, k])
285           call NF95_PUT_VAR(ncid_limit, id_FLIC, pctsrf(:, is_lic), start=[1, k])
286        end DO
287        
288      PRINT *, 'Traitement de la sst'      PRINT *, 'Traitement de la sst'
289      call NF95_OPEN('amipbc_sst_1x1.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('amipbc_sst_1x1.nc', NF90_NOWRITE, ncid)
290    
# Line 257  contains Line 308  contains
308      call NF95_INQ_VARID(ncid, 'tosbcs', varid)      call NF95_INQ_VARID(ncid, 'tosbcs', varid)
309    
310      DO l = 1, lmdep      DO l = 1, lmdep
311         call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
312         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
313         IF (extrap) &         IF (extrap) &
314              CALL extrapol(champ, imdep, jmdep, 999999., .TRUE., .TRUE., 2, work)              CALL extrapol(champ, imdep, jmdep, 999999., .TRUE., .TRUE., 2, work)
# Line 296  contains Line 347  contains
347         ENDDO         ENDDO
348      ENDDO      ENDDO
349            
350      forall (k = 1:360) phy_sst(:, k) = pack(champan(:, :, k), dyn_phy)      DO k = 1, 360
351           call NF95_PUT_VAR(ncid_limit, id_SST, pack(champan(:, :, k), dyn_phy), &
352                start=[1, k])
353        end DO
354    
355      PRINT *, "Traitement de l'albedo..."      PRINT *, "Traitement de l'albedo..."
356      call NF95_OPEN('Albedo.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('Albedo.nc', NF90_NOWRITE, ncid)
# Line 319  contains Line 373  contains
373    
374      DO l = 1, lmdep      DO l = 1, lmdep
375         PRINT *, "timeyear(", l, ") =", timeyear(l)         PRINT *, "timeyear(", l, ") =", timeyear(l)
376         call NF95_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
377         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
378         CALL inter_barxy(dlon, dlat(:jmdep-1), champ, rlonu(:iim), rlatv, &         CALL inter_barxy(dlon, dlat(:jmdep-1), champ, rlonu(:iim), rlatv, &
379              champtime(:, :, l))              champtime(:, :, l))
# Line 341  contains Line 395  contains
395      ENDDO      ENDDO
396    
397      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
     forall (k = 1:360) phy_alb(:, k) = pack(champan(:, :, k), dyn_phy)  
398    
399      DO k = 1, 360      DO k = 1, 360
400         DO i = 1, klon         call NF95_PUT_VAR(ncid_limit, id_ALB, pack(champan(:, :, k), dyn_phy), &
401            phy_bil(i, k) = 0.0              start=[1, k])
402         ENDDO      end DO
     ENDDO  
   
     PRINT *, 'Ecriture du fichier limit.nc...'  
   
     call NF95_CREATE("limit.nc", NF90_CLOBBER, nid)  
   
     call NF95_PUT_ATT(nid, NF90_GLOBAL, "title", &  
          "Fichier conditions aux limites")  
     call NF95_DEF_DIM(nid, "points_physiques", klon, ndim)  
     call NF95_DEF_DIM(nid, "time", NF90_UNLIMITED, ntim)  
   
     call NF95_DEF_VAR(nid, "TEMPS", NF90_FLOAT, ntim, id_tim)  
     call NF95_PUT_ATT(nid, id_tim, "title", "Jour dans l annee")  
   
     call NF95_DEF_VAR(nid, "FOCE", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_foce)  
     call NF95_PUT_ATT(nid, id_FOCE, "title", "Fraction ocean")  
   
     call NF95_DEF_VAR(nid, "FSIC", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_FSIC)  
     call NF95_PUT_ATT(nid, id_FSIC, "title", "Fraction glace de mer")  
   
     call NF95_DEF_VAR(nid, "FTER", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_FTER)  
     call NF95_PUT_ATT(nid, id_FTER, "title", "Fraction terre")  
403    
404      call NF95_DEF_VAR(nid, "FLIC", NF90_FLOAT, dimids=(/ndim, ntim/), &      phy_bil = 0.
405           varid=id_FLIC)      call NF95_PUT_VAR(ncid_limit, id_BILS, phy_bil)
     call NF95_PUT_ATT(nid, id_FLIC, "title", "Fraction land ice")  
   
     call NF95_DEF_VAR(nid, "SST", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_SST)  
     call NF95_PUT_ATT(nid, id_SST, "title",  &  
          "Temperature superficielle de la mer")  
   
     call NF95_DEF_VAR(nid, "BILS", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_BILS)  
     call NF95_PUT_ATT(nid, id_BILS, "title", "Reference flux de chaleur au sol")  
   
     call NF95_DEF_VAR(nid, "ALB", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_ALB)  
     call NF95_PUT_ATT(nid, id_ALB, "title", "Albedo a la surface")  
   
     call NF95_DEF_VAR(nid, "RUG", NF90_FLOAT, dimids=(/ndim, ntim/), &  
          varid=id_RUG)  
     call NF95_PUT_ATT(nid, id_RUG, "title", "Rugosite")  
   
     call NF95_ENDDEF(nid)  
   
     DO k = 1, 360  
        call NF95_PUT_VAR(nid, id_tim, REAL(k), (/k/))  
        call NF95_PUT_VAR(nid, id_FOCE, pctsrf_t(:, is_oce, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_FSIC, pctsrf_t(:, is_sic, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_FTER, pctsrf_t(:, is_ter, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_FLIC, pctsrf_t(:, is_lic, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_SST, phy_sst(:, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_BILS, phy_bil(:, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_ALB, phy_alb(:, k), start=(/1, k/))  
        call NF95_PUT_VAR(nid, id_RUG, phy_rug(:, k), start=(/1, k/))  
     ENDDO  
406    
407      call NF95_CLOSE(nid)      call NF95_CLOSE(ncid_limit)
408    
409    END SUBROUTINE limit    END SUBROUTINE limit
410    

Legend:
Removed from v.254  
changed lines
  Added in v.276

  ViewVC Help
Powered by ViewVC 1.1.21