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

Diff of /trunk/dyn3d/limit.f

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

trunk/libf/dyn3d/limit.f90 revision 3 by guez, Wed Feb 27 13:16:39 2008 UTC trunk/dyn3d/limit.f revision 264 by guez, Mon Mar 19 10:28:42 2018 UTC
# Line 1  Line 1 
1  module limit_mod  module limit_mod
2    
   ! This module is clean: no C preprocessor directive, no include line.  
   
3    IMPLICIT none    IMPLICIT none
4    
5  contains  contains
# Line 11  contains Line 9  contains
9      ! Authors: L. Fairhead, Z. X. Li, P. Le Van      ! Authors: L. Fairhead, Z. X. Li, P. Le Van
10    
11      ! This subroutine creates files containing boundary conditions.      ! This subroutine creates files containing boundary conditions.
12      ! It uses files with climatological data.      ! It uses files with climatological data.  Both grids must be
13      ! Both grids must be regular.      ! regular.
14    
15        use conf_dat2d_m, only: conf_dat2d
16      use dimens_m, only: iim, jjm      use dimens_m, only: iim, jjm
     use comconst, only: daysec, dtvr  
     use indicesol, only: epsfra, nbsrf, is_ter, is_oce, is_lic, is_sic  
17      use dimphy, only: klon, zmasq      use dimphy, only: klon, zmasq
18      use conf_gcm_m, only: day_step      use dynetat0_m, only: rlonu, rlatv
     use comgeom, only: rlonu, rlatv  
19      use etat0_mod, only: pctsrf      use etat0_mod, only: pctsrf
     use start_init_orog_m, only: masque  
     use conf_dat2d_m, only: conf_dat2d  
     use inter_barxy_m, only: inter_barxy  
     use interpolation, only: spline, splint  
20      use grid_change, only: dyn_phy      use grid_change, only: dyn_phy
21        use indicesol, only: epsfra, is_ter, is_oce, is_lic, is_sic
22        use inter_barxy_m, only: inter_barxy
23        use netcdf95, only: NF95_CLOSE, NF95_CREATE, NF95_DEF_DIM, nf95_def_var, &
24             nf95_enddef, nf95_get_var, nf95_gw_var, nf95_inq_dimid, &
25             nf95_inq_varid, nf95_inquire_dimension, NF95_OPEN, NF95_PUT_ATT, &
26             NF95_PUT_VAR
27        use netcdf, only: NF90_CLOBBER, NF90_FLOAT, NF90_GLOBAL, NF90_NOWRITE, &
28             NF90_UNLIMITED
29        use nr_util, only: assert
30        use numer_rec_95, only: spline, splint
31        use start_init_orog_m, only: mask
32        use unit_nml_m, only: unit_nml
33    
34      use netcdf95, only: handle_err, coordin, &      ! Local:
          NF90_CLOBBER, NF95_CLOSE, NF95_DEF_DIM, nf90_def_var, nf95_enddef, &  
          NF90_FLOAT, NF90_GET_VAR, NF90_GLOBAL, NF90_NOWRITE, NF90_PUT_ATT, &  
          NF90_PUT_VAR, NF90_UNLIMITED, &  
          NF95_CREATE, nf95_inq_dimid, nf95_inquire_dimension, nf95_inq_varid, &  
          nf95_open  
   
     ! Variables local to the procedure:  
35    
36      LOGICAL:: extrap = .FALSE.      LOGICAL:: extrap = .FALSE.
37      ! (extrapolation de données, comme pour les SST lorsque le fichier      ! (extrapolation de donn\'ees, comme pour les SST lorsque le fichier
38      ! ne contient pas uniquement des points océaniques)      ! ne contient pas uniquement des points oc\'eaniques)
39    
     REAL phy_alb(klon, 360)  
     REAL phy_sst(klon, 360)  
40      REAL phy_bil(klon, 360)      REAL phy_bil(klon, 360)
     REAL phy_rug(klon, 360)  
41      REAL phy_ice(klon)      REAL phy_ice(klon)
42    
43      real pctsrf_t(klon, nbsrf, 360) ! composition of the surface      ! Pour le champ de d\'epart:
   
     ! Pour le champ de départ:  
44      INTEGER imdep, jmdep, lmdep      INTEGER imdep, jmdep, lmdep
45    
46      REAL, ALLOCATABLE:: dlon(:), dlat(:)      REAL, ALLOCATABLE:: dlon(:), dlat(:)
47      REAL, pointer:: dlon_ini(:), dlat_ini(:), timeyear(:)      REAL, ALLOCATABLE:: dlon_ini(:), dlat_ini(:), timeyear(:)
48      REAL, ALLOCATABLE:: champ(:, :)      REAL, ALLOCATABLE:: champ(:, :)
49      REAL, ALLOCATABLE:: work(:, :)      REAL, ALLOCATABLE:: work(:, :)
50    
51      ! Pour le champ interpolé 3D :      ! Pour le champ interpol\'e 3D :
52      REAL, allocatable:: champtime(:, :, :)      REAL, allocatable:: champtime(:, :, :)
53      REAL champan(iim + 1, jjm + 1, 360)      REAL champan(iim + 1, jjm + 1, 360)
54    
55      ! Pour l'inteprolation verticale :      ! Pour l'inteprolation verticale :
56      REAL, allocatable:: yder(:)      REAL, allocatable:: yder(:)
57    
58      INTEGER ierr      INTEGER ndim, ntim
59        INTEGER varid_time
     INTEGER nid, ndim, ntim  
     INTEGER dims(2), debut(2)  
     INTEGER id_tim  
60      INTEGER id_SST, id_BILS, id_RUG, id_ALB      INTEGER id_SST, id_BILS, id_RUG, id_ALB
61      INTEGER id_FOCE, id_FSIC, id_FTER, id_FLIC      INTEGER id_FOCE, id_FSIC, id_FTER, id_FLIC
62    
63      INTEGER i, j, k, l      INTEGER i, j, k, l
64      INTEGER ncid, varid, dimid      INTEGER ncid, ncid_limit, varid, dimid
65    
66      REAL, parameter:: tmidmonth(12) = (/(15. + 30. * i, i = 0, 11)/)      REAL, parameter:: tmidmonth(12) = [(15. + 30. * i, i = 0, 11)]
67    
68      namelist /limit_nml/extrap      namelist /limit_nml/extrap
69    
# Line 83  contains Line 72  contains
72      print *, "Call sequence information: limit"      print *, "Call sequence information: limit"
73    
74      print *, "Enter namelist 'limit_nml'."      print *, "Enter namelist 'limit_nml'."
75      read (unit=*, nml=limit_nml)      read(unit=*, nml=limit_nml)
76      write(unit=*, nml=limit_nml)      write(unit_nml, nml=limit_nml)
77    
78        call NF95_CREATE("limit.nc", NF90_CLOBBER, ncid_limit)
79    
80        call NF95_PUT_ATT(ncid_limit, NF90_GLOBAL, "title", &
81             "Fichier conditions aux limites")
82        call NF95_DEF_DIM(ncid_limit, "points_physiques", klon, ndim)
83        call NF95_DEF_DIM(ncid_limit, "time", NF90_UNLIMITED, ntim)
84    
85      ! Initializations:      call NF95_DEF_VAR(ncid_limit, "TEMPS", NF90_FLOAT, ntim, varid_time)
86      dtvr = daysec / real(day_step)      call NF95_PUT_ATT(ncid_limit, varid_time, "title", "Jour dans l annee")
     CALL inigeom  
87    
88      ! Process rugosity:      call NF95_DEF_VAR(ncid_limit, "FOCE", NF90_FLOAT, dimids=[ndim, ntim], &
89             varid=id_foce)
90        call NF95_PUT_ATT(ncid_limit, id_FOCE, "title", "Fraction ocean")
91    
92        call NF95_DEF_VAR(ncid_limit, "FSIC", NF90_FLOAT, dimids=[ndim, ntim], &
93             varid=id_FSIC)
94        call NF95_PUT_ATT(ncid_limit, id_FSIC, "title", "Fraction glace de mer")
95    
96        call NF95_DEF_VAR(ncid_limit, "FTER", NF90_FLOAT, dimids=[ndim, ntim], &
97             varid=id_FTER)
98        call NF95_PUT_ATT(ncid_limit, id_FTER, "title", "Fraction terre")
99    
100        call NF95_DEF_VAR(ncid_limit, "FLIC", NF90_FLOAT, dimids=[ndim, ntim], &
101             varid=id_FLIC)
102        call NF95_PUT_ATT(ncid_limit, id_FLIC, "title", "Fraction land ice")
103    
104        call NF95_DEF_VAR(ncid_limit, "SST", NF90_FLOAT, dimids=[ndim, ntim], &
105             varid=id_SST)
106        call NF95_PUT_ATT(ncid_limit, id_SST, "title",  &
107             "Temperature superficielle de la mer")
108    
109        call NF95_DEF_VAR(ncid_limit, "BILS", NF90_FLOAT, dimids=[ndim, ntim], &
110             varid=id_BILS)
111        call NF95_PUT_ATT(ncid_limit, id_BILS, "title", &
112             "Reference flux de chaleur au sol")
113    
114        call NF95_DEF_VAR(ncid_limit, "ALB", NF90_FLOAT, dimids=[ndim, ntim], &
115             varid=id_ALB)
116        call NF95_PUT_ATT(ncid_limit, id_ALB, "title", "Albedo a la surface")
117    
118        call NF95_DEF_VAR(ncid_limit, "RUG", NF90_FLOAT, dimids=[ndim, ntim], &
119             varid=id_RUG)
120        call NF95_PUT_ATT(ncid_limit, id_RUG, "title", "Rugosite")
121    
122        call NF95_ENDDEF(ncid_limit)
123    
124        call NF95_PUT_VAR(ncid_limit, varid_time, [(k, k = 1, 360)])
125        
126      PRINT *, 'Processing rugosity...'      PRINT *, 'Processing rugosity...'
127    
128      call NF95_OPEN('Rugos.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('Rugos.nc', NF90_NOWRITE, ncid)
129    
130      dlon_ini => coordin(ncid, "longitude")      ! Read coordinate variables:
131    
132        call nf95_inq_varid(ncid, "longitude", varid)
133        call nf95_gw_var(ncid, varid, dlon_ini)
134      imdep = size(dlon_ini)      imdep = size(dlon_ini)
135    
136      dlat_ini => coordin(ncid, "latitude")      call nf95_inq_varid(ncid, "latitude", varid)
137        call nf95_gw_var(ncid, varid, dlat_ini)
138      jmdep = size(dlat_ini)      jmdep = size(dlat_ini)
139    
140      timeyear => coordin(ncid, "temps")      call nf95_inq_varid(ncid, "temps", varid)
141        call nf95_gw_var(ncid, varid, timeyear)
142      lmdep = size(timeyear)      lmdep = size(timeyear)
143    
144      ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))      ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
145      allocate(dlon(imdep), dlat(jmdep))      allocate(dlon(imdep), dlat(jmdep))
146      call NF95_INQ_VARID(ncid, 'RUGOS', varid)      call NF95_INQ_VARID(ncid, 'RUGOS', varid)
147    
148      ! Compute "champtime":      ! Read the primary variable day by day and regrid horizontally,
149        ! result in "champtime":
150      DO  l = 1, lmdep      DO  l = 1, lmdep
151         ierr = NF90_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
        call handle_err("NF90_GET_VAR", ierr)  
   
152         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
153         CALL inter_barxy(dlon, dlat(:jmdep -1), LOG(champ), rlonu(:iim), &         CALL inter_barxy(dlon, dlat(:jmdep -1), LOG(champ), rlonu(:iim), &
154              rlatv, champtime(:, :, l))              rlatv, champtime(:, :, l))
155         champtime(:, :, l) = EXP(champtime(:, :, l))         champtime(:, :, l) = EXP(champtime(:, :, l))
156         where (nint(masque(:iim, :)) /= 1) champtime(:, :, l) = 0.001         where (nint(mask(:iim, :)) /= 1) champtime(:, :, l) = 0.001
157      end do      end do
158    
159      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
160    
161      DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)      DEALLOCATE(dlon, dlat, champ)
162      allocate(yder(lmdep))      allocate(yder(lmdep))
163    
164        ! Interpolate monthly values to daily values, at each horizontal position:
165      DO j = 1, jjm + 1      DO j = 1, jjm + 1
166         DO i = 1, iim         DO i = 1, iim
167            yder(:) = SPLINE(timeyear, champtime(i, j, :))            yder = SPLINE(timeyear, champtime(i, j, :))
168            DO k = 1, 360            DO k = 1, 360
169               champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &               champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &
170                    real(k-1))                    real(k-1))
# Line 135  contains Line 172  contains
172         ENDDO         ENDDO
173      ENDDO      ENDDO
174    
175      deallocate(timeyear, champtime, yder)      deallocate(champtime, yder)
176      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
     forall (k = 1:360) phy_rug(:, k) = pack(champan(:, :, k), dyn_phy)  
177    
178      ! Process sea ice:      DO k = 1, 360
179           call NF95_PUT_VAR(ncid_limit, id_RUG, pack(champan(:, :, k), dyn_phy), &
180                start=[1, k])
181        ENDDO
182    
183      PRINT *, 'Processing sea ice...'      PRINT *, 'Processing sea ice...'
184      call NF95_OPEN('amipbc_sic_1x1.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('amipbc_sic_1x1.nc', NF90_NOWRITE, ncid)
185    
186      dlon_ini => coordin(ncid, "longitude")      call nf95_inq_varid(ncid, "longitude", varid)
187        call nf95_gw_var(ncid, varid, dlon_ini)
188      imdep = size(dlon_ini)      imdep = size(dlon_ini)
189    
190      dlat_ini => coordin(ncid, "latitude")      call nf95_inq_varid(ncid, "latitude", varid)
191        call nf95_gw_var(ncid, varid, dlat_ini)
192      jmdep = size(dlat_ini)      jmdep = size(dlat_ini)
193    
194      call nf95_inq_dimid(ncid, "time", dimid)      call nf95_inq_dimid(ncid, "time", dimid)
195      call NF95_INQuire_DIMension(ncid, dimid, len=lmdep)      call NF95_INQuire_DIMension(ncid, dimid, nclen=lmdep)
196      print *, 'lmdep = ', lmdep      print *, 'lmdep = ', lmdep
197      ! PM 28/02/2002 : nouvelle coordonnée temporelle, fichiers AMIP      ! Coordonn\'ee temporelle fichiers AMIP pas en jours. Ici on suppose
198      ! pas en jours      ! qu'on a 12 mois (de 30 jours).
199      ! Ici on suppose qu'on a 12 mois (de 30 jours).      IF (lmdep /= 12) then
200      IF (lmdep /= 12) STOP 'Unknown AMIP file: not 12 months?'         print *, 'Unknown AMIP file: not 12 months?'
201           STOP 1
202        end IF
203    
204      ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))      ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
205      ALLOCATE (dlon(imdep), dlat(jmdep))      ALLOCATE(dlon(imdep), dlat(jmdep))
206      call NF95_INQ_VARID(ncid, 'sicbcs', varid)      call NF95_INQ_VARID(ncid, 'sicbcs', varid)
207      DO l = 1, lmdep      DO l = 1, lmdep
208         ierr = NF90_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
        call handle_err("NF90_GET_VAR", ierr)  
   
209         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
210         CALL inter_barxy (dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &         CALL inter_barxy(dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &
211              champtime(:, :, l))              champtime(:, :, l))
212      ENDDO      ENDDO
213    
214      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
215    
216      DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)      DEALLOCATE(dlon, dlat, champ)
217      PRINT *, 'Interpolation temporelle'      PRINT *, 'Interpolation temporelle'
218      allocate(yder(lmdep))      allocate(yder(lmdep))
219    
220      DO j = 1, jjm + 1      DO j = 1, jjm + 1
221         DO i = 1, iim         DO i = 1, iim
222            yder(:) = SPLINE(tmidmonth, champtime(i, j, :))            yder = SPLINE(tmidmonth, champtime(i, j, :))
223            DO k = 1, 360            DO k = 1, 360
224               champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &               champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &
225                    real(k-1))                    real(k-1))
# Line 194  contains Line 235  contains
235      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
236    
237      DO k = 1, 360      DO k = 1, 360
238         phy_ice(:) = pack(champan(:, :, k), dyn_phy)         phy_ice = pack(champan(:, :, k), dyn_phy)
239    
240         ! (utilisation de la sous-maille fractionnelle tandis que l'ancien         ! (utilisation de la sous-maille fractionnelle tandis que l'ancien
241         ! codage utilisait l'indicateur du sol (0, 1, 2, 3))         ! codage utilisait l'indicateur du sol (0, 1, 2, 3))
242         ! PB en attendant de mettre fraction de terre         ! PB en attendant de mettre fraction de terre
243         WHERE(phy_ice(:) < EPSFRA) phy_ice(:) = 0.         WHERE (phy_ice < EPSFRA) phy_ice = 0.
244    
245         pctsrf_t(:, is_ter, k) = pctsrf(:, is_ter)         pctsrf(:, is_sic) = max(phy_ice - pctsrf(:, is_lic), 0.)
246         pctsrf_t(:, is_lic, k) = pctsrf(:, is_lic)         ! Il y a des cas o\`u il y a de la glace dans landiceref et
        pctsrf_t(:, is_sic, k) = max(phy_ice(:) - pctsrf_t(:, is_lic, k), 0.)  
        ! Il y a des cas où il y a de la glace dans landiceref et  
247         ! pas dans AMIP         ! pas dans AMIP
248         WHERE( 1. - zmasq(:) < EPSFRA)         WHERE (1. - zmasq < EPSFRA)
249            pctsrf_t(:, is_sic, k) = 0.            pctsrf(:, is_sic) = 0.
250            pctsrf_t(:, is_oce, k) = 0.            pctsrf(:, is_oce) = 0.
251         elsewhere         elsewhere
252            where (pctsrf_t(:, is_sic, k) >= 1 - zmasq(:))            where (pctsrf(:, is_sic) >= 1 - zmasq)
253               pctsrf_t(:, is_sic, k) = 1. - zmasq(:)               pctsrf(:, is_sic) = 1. - zmasq
254               pctsrf_t(:, is_oce, k) = 0.               pctsrf(:, is_oce) = 0.
255            ELSEwhere            ELSEwhere
256               pctsrf_t(:, is_oce, k) = 1. - zmasq(:) - pctsrf_t(:, is_sic, k)               pctsrf(:, is_oce) = 1. - zmasq - pctsrf(:, is_sic)
257               where (pctsrf_t(:, is_oce, k) < EPSFRA)               where (pctsrf(:, is_oce) < EPSFRA)
258                  pctsrf_t(:, is_oce, k) = 0.                  pctsrf(:, is_oce) = 0.
259                  pctsrf_t(:, is_sic, k) = 1 - zmasq(:)                  pctsrf(:, is_sic) = 1 - zmasq
260               end where               end where
261            end where            end where
262         end where         end where
263    
264         DO i = 1, klon         DO i = 1, klon
265            if (pctsrf_t(i, is_oce, k) < 0.) then            if (pctsrf(i, is_oce) < 0.) then
266               print *, 'Problème sous maille : pctsrf_t(', i, &               print *, "k = ", k
267                    ', is_oce, ', k, ') = ', pctsrf_t(i, is_oce, k)               print *, 'Bad surface fraction: pctsrf(', i, ', is_oce) = ', &
268                      pctsrf(i, is_oce)
269            ENDIF            ENDIF
270            IF (abs(pctsrf_t(i, is_ter, k) + pctsrf_t(i, is_lic, k) &            IF (abs(sum(pctsrf(i, :)) - 1.) > EPSFRA) THEN
271                 + pctsrf_t(i, is_oce, k) + pctsrf_t(i, is_sic, k) - 1.) &               print *, "k = ", k
272                 > EPSFRA) THEN               print *, 'Bad surface fraction:'
273               print *, 'Problème sous surface :'               print *, "pctsrf(", i, ", :) = ", pctsrf(i, :)
              print *, "pctsrf_t(", i, ", :, ", k, ") = ", &  
                   pctsrf_t(i, :, k)  
274               print *, "phy_ice(", i, ") = ", phy_ice(i)               print *, "phy_ice(", i, ") = ", phy_ice(i)
275            ENDIF            ENDIF
276         END DO         END DO
     ENDDO  
277    
278           call NF95_PUT_VAR(ncid_limit, id_FOCE, pctsrf(:, is_oce), start=[1, k])
279           call NF95_PUT_VAR(ncid_limit, id_FSIC, pctsrf(:, is_sic), start=[1, k])
280           call NF95_PUT_VAR(ncid_limit, id_FTER, pctsrf(:, is_ter), start=[1, k])
281           call NF95_PUT_VAR(ncid_limit, id_FLIC, pctsrf(:, is_lic), start=[1, k])
282        end DO
283        
284      PRINT *, 'Traitement de la sst'      PRINT *, 'Traitement de la sst'
285      call NF95_OPEN('amipbc_sst_1x1.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('amipbc_sst_1x1.nc', NF90_NOWRITE, ncid)
286    
287      dlon_ini => coordin(ncid, "longitude")      call nf95_inq_varid(ncid, "longitude", varid)
288        call nf95_gw_var(ncid, varid, dlon_ini)
289      imdep = size(dlon_ini)      imdep = size(dlon_ini)
290    
291      dlat_ini => coordin(ncid, "latitude")      call nf95_inq_varid(ncid, "latitude", varid)
292        call nf95_gw_var(ncid, varid, dlat_ini)
293      jmdep = size(dlat_ini)      jmdep = size(dlat_ini)
294    
295      call nf95_inq_dimid(ncid, "time", dimid)      call nf95_inq_dimid(ncid, "time", dimid)
296      call NF95_INQuire_DIMension(ncid, dimid, len=lmdep)      call NF95_INQuire_DIMension(ncid, dimid, nclen=lmdep)
297      print *, 'lmdep = ', lmdep      print *, 'lmdep = ', lmdep
298      !PM28/02/2002 : nouvelle coord temporelle fichiers AMIP pas en jours      ! Ici on suppose qu'on a 12 mois (de 30 jours).
299      !        Ici on suppose qu'on a 12 mois (de 30 jours).      call assert(lmdep == 12, 'limit: AMIP file does not contain 12 months')
300      IF (lmdep /= 12) stop 'Unknown AMIP file: not 12 months?'  
301        ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
302      ALLOCATE( champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))      IF (extrap) ALLOCATE(work(imdep, jmdep))
303      IF( extrap )  THEN      ALLOCATE(dlon(imdep), dlat(jmdep))
        ALLOCATE ( work(imdep, jmdep) )  
     ENDIF  
     ALLOCATE(   dlon(imdep), dlat(jmdep) )  
304      call NF95_INQ_VARID(ncid, 'tosbcs', varid)      call NF95_INQ_VARID(ncid, 'tosbcs', varid)
305    
306      DO l = 1, lmdep      DO l = 1, lmdep
307         ierr = NF90_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
        call handle_err("NF90_GET_VAR", ierr)  
   
308         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
309         IF ( extrap ) THEN         IF (extrap) &
310            CALL extrapol(champ, imdep, jmdep, 999999., .TRUE., .TRUE., 2, work)              CALL extrapol(champ, imdep, jmdep, 999999., .TRUE., .TRUE., 2, work)
311         ENDIF         CALL inter_barxy(dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &
312                champtime(:, :, l))
        CALL inter_barxy (dlon, dlat(:jmdep -1), champ, rlonu(:iim), rlatv, &  
             champtime(:, :, l) )  
313      ENDDO      ENDDO
314    
315      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
316        DEALLOCATE(dlon, dlat, champ)
     DEALLOCATE(dlon, dlat, champ, dlon_ini, dlat_ini)  
317      allocate(yder(lmdep))      allocate(yder(lmdep))
318    
319      ! interpolation temporelle      ! interpolation temporelle
320      DO j = 1, jjm + 1      DO j = 1, jjm + 1
321         DO i = 1, iim         DO i = 1, iim
322            yder(:) = SPLINE(tmidmonth, champtime(i, j, :))            yder = SPLINE(tmidmonth, champtime(i, j, :))
323            DO k = 1, 360            DO k = 1, 360
324               champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &               champan(i, j, k) = SPLINT(tmidmonth, champtime(i, j, :), yder, &
325                    real(k-1))                    real(k-1))
# Line 294  contains Line 331  contains
331      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
332    
333      !IM14/03/2002 : SST amipbc greater then 271.38      !IM14/03/2002 : SST amipbc greater then 271.38
334      PRINT *, 'SUB. limit_netcdf.F IM : SST Amipbc >= 271.38 '      PRINT *, 'limit: SST Amipbc >= 271.38 '
335    
336      DO k = 1, 360      DO k = 1, 360
337         DO j = 1, jjm + 1         DO j = 1, jjm + 1
338            DO i = 1, iim            DO i = 1, iim
339               champan(i, j, k) = amax1(champan(i, j, k), 271.38)               champan(i, j, k) = max(champan(i, j, k), 271.38)
340            ENDDO            ENDDO
341              
342            champan(iim + 1, j, k) = champan(1, j, k)            champan(iim + 1, j, k) = champan(1, j, k)
343         ENDDO         ENDDO
344      ENDDO      ENDDO
345      forall (k = 1:360) phy_sst(:, k) = pack(champan(:, :, k), dyn_phy)      
346        DO k = 1, 360
347      ! Traitement de l'albedo         call NF95_PUT_VAR(ncid_limit, id_SST, pack(champan(:, :, k), dyn_phy), &
348                start=[1, k])
349        end DO
350    
351      PRINT *, 'Traitement de l albedo'      PRINT *, "Traitement de l'albedo..."
352      call NF95_OPEN('Albedo.nc', NF90_NOWRITE, ncid)      call NF95_OPEN('Albedo.nc', NF90_NOWRITE, ncid)
353    
354      dlon_ini => coordin(ncid, "longitude")      call nf95_inq_varid(ncid, "longitude", varid)
355        call nf95_gw_var(ncid, varid, dlon_ini)
356      imdep = size(dlon_ini)      imdep = size(dlon_ini)
357    
358      dlat_ini => coordin(ncid, "latitude")      call nf95_inq_varid(ncid, "latitude", varid)
359        call nf95_gw_var(ncid, varid, dlat_ini)
360      jmdep = size(dlat_ini)      jmdep = size(dlat_ini)
361    
362      timeyear => coordin(ncid, "temps")      call nf95_inq_varid(ncid, "temps", varid)
363        call nf95_gw_var(ncid, varid, timeyear)
364      lmdep = size(timeyear)      lmdep = size(timeyear)
365    
366      ALLOCATE ( champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))      ALLOCATE(champ(imdep, jmdep), champtime(iim, jjm + 1, lmdep))
367      ALLOCATE (   dlon(imdep), dlat(jmdep) )      ALLOCATE(dlon(imdep), dlat(jmdep))
368      call NF95_INQ_VARID(ncid, 'ALBEDO', varid)      call NF95_INQ_VARID(ncid, 'ALBEDO', varid)
369    
370      DO l = 1, lmdep      DO l = 1, lmdep
371         PRINT *, 'Lecture temporelle et int. horizontale ', l, timeyear(l)         PRINT *, "timeyear(", l, ") =", timeyear(l)
372         ierr = NF90_GET_VAR(ncid, varid, champ, start=(/1, 1, l/))         call NF95_GET_VAR(ncid, varid, champ, start=[1, 1, l])
        call handle_err("NF90_GET_VAR", ierr)  
   
373         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)         CALL conf_dat2d(dlon_ini, dlat_ini, dlon, dlat, champ)
374         CALL inter_barxy(dlon, dlat(:jmdep-1), champ, rlonu(:iim), rlatv, &         CALL inter_barxy(dlon, dlat(:jmdep-1), champ, rlonu(:iim), rlatv, &
375              champtime(:, :, l) )              champtime(:, :, l))
376      ENDDO      ENDDO
377    
378      call NF95_CLOSE(ncid)      call NF95_CLOSE(ncid)
379    
     deallocate(dlon_ini, dlat_ini)  
380      allocate(yder(lmdep))      allocate(yder(lmdep))
381    
382      ! interpolation temporelle      ! interpolation temporelle
383      DO j = 1, jjm + 1      DO j = 1, jjm + 1
384         DO i = 1, iim         DO i = 1, iim
385            yder(:) = SPLINE(timeyear, champtime(i, j, :))            yder = SPLINE(timeyear, champtime(i, j, :))
386            DO k = 1, 360            DO k = 1, 360
387               champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &               champan(i, j, k) = SPLINT(timeyear, champtime(i, j, :), yder, &
388                    real(k-1))                    real(k-1))
389            ENDDO            ENDDO
390         ENDDO         ENDDO
391      ENDDO      ENDDO
     deallocate(timeyear)  
392    
393      champan(iim + 1, :, :) = champan(1, :, :)      champan(iim + 1, :, :) = champan(1, :, :)
     forall (k = 1:360) phy_alb(:, k) = pack(champan(:, :, k), dyn_phy)  
394    
395      DO k = 1, 360      DO k = 1, 360
396         DO i = 1, klon         call NF95_PUT_VAR(ncid_limit, id_ALB, pack(champan(:, :, k), dyn_phy), &
397            phy_bil(i, k) = 0.0              start=[1, k])
398         ENDDO      end DO
     ENDDO  
399    
400      PRINT *, 'Ecriture du fichier limit'      phy_bil = 0.
401        call NF95_PUT_VAR(ncid_limit, id_BILS, phy_bil)
     call NF95_CREATE("limit.nc", NF90_CLOBBER, nid)  
   
     ierr = NF90_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)  
   
     dims(1) = ndim  
     dims(2) = ntim  
   
     ierr = NF90_DEF_VAR (nid, "TEMPS", NF90_FLOAT, ntim, id_tim)  
     ierr = NF90_PUT_ATT (nid, id_tim, "title",  &  
          "Jour dans l annee")  
     ierr = NF90_DEF_VAR (nid, "FOCE", NF90_FLOAT, dims, id_FOCE)  
     ierr = NF90_PUT_ATT (nid, id_FOCE, "title", &  
          "Fraction ocean")  
   
     ierr = NF90_DEF_VAR (nid, "FSIC", NF90_FLOAT, dims, id_FSIC)  
     ierr = NF90_PUT_ATT (nid, id_FSIC, "title", &  
          "Fraction glace de mer")  
   
     ierr = NF90_DEF_VAR (nid, "FTER", NF90_FLOAT, dims, id_FTER)  
     ierr = NF90_PUT_ATT (nid, id_FTER, "title", &  
          "Fraction terre")  
   
     ierr = NF90_DEF_VAR (nid, "FLIC", NF90_FLOAT, dims, id_FLIC)  
     ierr = NF90_PUT_ATT (nid, id_FLIC, "title", &  
          "Fraction land ice")  
   
     ierr = NF90_DEF_VAR (nid, "SST", NF90_FLOAT, dims, id_SST)  
     ierr = NF90_PUT_ATT (nid, id_SST, "title",  &  
          "Temperature superficielle de la mer")  
     ierr = NF90_DEF_VAR (nid, "BILS", NF90_FLOAT, dims, id_BILS)  
     ierr = NF90_PUT_ATT (nid, id_BILS, "title", &  
          "Reference flux de chaleur au sol")  
     ierr = NF90_DEF_VAR (nid, "ALB", NF90_FLOAT, dims, id_ALB)  
     ierr = NF90_PUT_ATT (nid, id_ALB, "title", &  
          "Albedo a la surface")  
     ierr = NF90_DEF_VAR (nid, "RUG", NF90_FLOAT, dims, id_RUG)  
     ierr = NF90_PUT_ATT (nid, id_RUG, "title", &  
          "Rugosite")  
   
     call NF95_ENDDEF(nid)  
   
     DO k = 1, 360  
        debut(1) = 1  
        debut(2) = k  
   
        ierr = NF90_PUT_VAR(nid, id_tim, FLOAT(k), (/k/))  
        ierr = NF90_PUT_VAR(nid, id_FOCE, pctsrf_t(:, is_oce, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_FSIC, pctsrf_t(:, is_sic, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_FTER, pctsrf_t(:, is_ter, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_FLIC, pctsrf_t(:, is_lic, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_SST, phy_sst(:, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_BILS, phy_bil(:, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_ALB, phy_alb(:, k), debut)  
        ierr = NF90_PUT_VAR (nid, id_RUG, phy_rug(:, k), debut)  
     ENDDO  
402    
403      call NF95_CLOSE(nid)      call NF95_CLOSE(ncid_limit)
404    
405    END SUBROUTINE limit    END SUBROUTINE limit
406    

Legend:
Removed from v.3  
changed lines
  Added in v.264

  ViewVC Help
Powered by ViewVC 1.1.21