source: LMDZ6/trunk/libf/phylmd/limit_read_mod.f90 @ 5662

Last change on this file since 5662 was 5662, checked in by Laurent Fairhead, 3 weeks ago

Ajout du modèle thermodynamique de glace de mer interactive améliorant les flux échangés à la surface de la banquise (Doctorat de Nicolas Michalezyk, Contact : Nicolas Michaleyk, Guillaume Gastineau)

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 20.2 KB
Line 
1!
2! $Id: limit_read_mod.f90 5662 2025-05-20 14:24:41Z fairhead $
3!
4MODULE limit_read_mod
5!
6! This module reads the fichier "limit.nc" containing fields for surface forcing.
7!
8! Module subroutines :
9!  limit_read_frac    : call limit_read_tot and return the fractions
10!  limit_read_rug_alb : return rugosity and albedo, if coupled ocean call limit_read_tot first
11!  limit_read_sst     : return sea ice temperature   
12!  limit_read_tot     : read limit.nc and store the fields in local modules variables
13!
14  IMPLICIT NONE
15
16  REAL, ALLOCATABLE, DIMENSION(:,:), SAVE, PRIVATE :: pctsrf
17!$OMP THREADPRIVATE(pctsrf)
18  REAL, ALLOCATABLE, DIMENSION(:),   SAVE, PRIVATE :: rugos
19!$OMP THREADPRIVATE(rugos)
20  REAL, ALLOCATABLE, DIMENSION(:),   SAVE, PRIVATE :: albedo
21!$OMP THREADPRIVATE(albedo) 
22  REAL, ALLOCATABLE, DIMENSION(:),   SAVE, PRIVATE :: sst
23!$OMP THREADPRIVATE(sst)
24!GG
25  REAL, ALLOCATABLE, DIMENSION(:),   SAVE, PRIVATE :: sih
26!$OMP THREADPRIVATE(sih)
27!GG
28  LOGICAL,SAVE :: read_continents=.FALSE.
29!$OMP THREADPRIVATE(read_continents)
30
31CONTAINS
32!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
33!!
34!! Public subroutines :
35!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
36
37
38  SUBROUTINE init_limit_read(first_day)
39  USE mod_grid_phy_lmdz
40  USE surface_data
41  USE mod_phys_lmdz_para
42  USE lmdz_xios
43
44  IMPLICIT NONE
45    INTEGER, INTENT(IN) :: first_day
46   
47   
48    IF ( type_ocean /= 'couple') THEN
49      IF (grid_type==unstructured) THEN
50        IF (is_omp_master) CALL xios_set_file_attr("limit_read",enabled=.TRUE.,record_offset=first_day)
51      ENDIF 
52    ENDIF
53
54  END SUBROUTINE init_limit_read
55 
56  SUBROUTINE limit_read_frac(itime, dtime, jour, pctsrf_new, is_modified)
57!
58! This subroutine is called from "change_srf_frac" for case of
59! ocean=force or from ocean_slab_frac for ocean=slab.
60! The fraction for all sub-surfaces at actual time step is returned.
61
62    USE dimphy
63    USE indice_sol_mod
64
65! Input arguments
66!****************************************************************************************
67    INTEGER, INTENT(IN) :: itime   ! time step
68    INTEGER, INTENT(IN) :: jour    ! current day
69    REAL   , INTENT(IN) :: dtime   ! length of time step
70 
71! Output arguments
72!****************************************************************************************
73    REAL, DIMENSION(klon,nbsrf), INTENT(OUT) :: pctsrf_new  ! sub surface fractions
74    LOGICAL, INTENT(OUT)                     :: is_modified ! true if pctsrf is modified at this time step
75
76! End declaration
77!****************************************************************************************
78
79! 1) Read file limit.nc
80    CALL limit_read_tot(itime, dtime, jour, is_modified)
81
82! 2) Return the fraction read in limit_read_tot
83    pctsrf_new(:,:) = pctsrf(:,:)
84   
85  END SUBROUTINE limit_read_frac
86
87!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
88
89  SUBROUTINE limit_read_rug_alb(itime, dtime, jour, &
90       knon, knindex, &
91       rugos_out, alb_out)
92!
93! This subroutine is called from surf_land_bucket.
94! The flag "ok_veget" must can not be true. If coupled run, "ocean=couple"
95! then this routine will call limit_read_tot.
96!
97    USE dimphy
98    USE surface_data
99
100! Input arguments
101!****************************************************************************************
102    INTEGER, INTENT(IN) :: itime                     ! numero du pas de temps courant
103    INTEGER, INTENT(IN) :: jour                      ! jour a lire dans l'annee
104    REAL   , INTENT(IN) :: dtime                     ! pas de temps de la physique (en s)
105    INTEGER, INTENT(IN) :: knon                      ! nomber of points on compressed grid
106    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex  ! grid point number for compressed grid
107! Output arguments
108!****************************************************************************************
109    REAL, DIMENSION(klon), INTENT(OUT) :: rugos_out
110    REAL, DIMENSION(klon), INTENT(OUT) :: alb_out
111   
112! Local variables
113!****************************************************************************************
114    INTEGER :: i
115    LOGICAL :: is_modified
116!****************************************************************************************
117
118IF (type_ocean == 'couple'.OR. &
119         (type_ocean == 'slab' .AND. version_ocean == 'sicINT')) THEN
120       ! limit.nc has not yet been read. Do it now!
121       CALL limit_read_tot(itime, dtime, jour, is_modified)
122    END IF
123
124    DO i=1,knon
125       rugos_out(i) = rugos(knindex(i))
126       alb_out(i)  = albedo(knindex(i))
127    END DO
128
129  END SUBROUTINE limit_read_rug_alb
130
131!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
132
133  SUBROUTINE limit_read_sst(knon, knindex, sst_out)
134!
135! This subroutine returns the sea surface temperature already read from limit.nc.
136!
137    USE dimphy, ONLY : klon
138
139    INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
140    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex  ! grid point number for compressed grid
141    REAL, DIMENSION(klon), INTENT(OUT)   :: sst_out
142
143    INTEGER :: i
144
145    DO i = 1, knon
146       sst_out(i) = sst(knindex(i))
147    END DO
148
149  END SUBROUTINE limit_read_sst
150
151!GG
152  SUBROUTINE limit_read_hice(knon, knindex, hice_out)
153!
154! This subroutine returns the sea surface temperature already read from limit.nc.
155!
156    USE dimphy, ONLY : klon
157
158    INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
159    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex  ! grid point number for compressed grid
160    REAL, DIMENSION(klon), INTENT(OUT)   :: hice_out
161
162    INTEGER :: i
163
164    DO i = 1, knon
165       hice_out(i) = sih(knindex(i))
166    END DO
167
168  END SUBROUTINE limit_read_hice
169!GG
170!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
171!!
172!! Private subroutine :
173!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
174
175  SUBROUTINE limit_read_tot(itime, dtime, jour, is_modified)
176!
177! Read everything needed from limit.nc
178!
179! 0) Initialize
180! 1) Open the file limit.nc, if it is time
181! 2) Read fraction, if not type_ocean=couple
182! 3) Read sea surface temperature, if not type_ocean=couple
183! 4) Read albedo and rugosity for land surface, only in case of no vegetation model
184! 5) Close file and distribuate variables to all processus
185
186    USE dimphy
187    USE mod_grid_phy_lmdz
188    USE mod_phys_lmdz_para
189    !GG USE surface_data, ONLY : type_ocean, ok_veget
190    USE surface_data, ONLY : type_ocean, ok_veget, iflag_seaice, amax_n, amax_s
191    !GG
192    USE netcdf
193    USE indice_sol_mod
194    USE phys_cal_mod, ONLY : calend, year_len
195    USE print_control_mod, ONLY: lunout, prt_level
196    USE lmdz_xios, ONLY: xios_recv_field, using_xios
197   
198    IMPLICIT NONE
199   
200! In- and ouput arguments
201!****************************************************************************************
202    INTEGER, INTENT(IN) :: itime   ! numero du pas de temps courant
203    INTEGER, INTENT(IN) :: jour    ! jour a lire dans l'annee
204    REAL   , INTENT(IN) :: dtime   ! pas de temps de la physique (en s)
205
206    LOGICAL, INTENT(OUT) :: is_modified  ! true if pctsrf is modified at this time step
207
208! Locals variables with attribute SAVE
209!****************************************************************************************
210! frequence de lecture des conditions limites (en pas de physique)
211    INTEGER,SAVE                              :: lmt_pas
212!$OMP THREADPRIVATE(lmt_pas)
213    LOGICAL, SAVE                             :: first_call=.TRUE.
214!$OMP THREADPRIVATE(first_call) 
215    INTEGER, SAVE                             :: jour_lu = -1
216!$OMP THREADPRIVATE(jour_lu) 
217! Locals variables
218!****************************************************************************************
219    INTEGER                                   :: nid, nvarid, ndimid, nn
220    INTEGER                                   :: ii, ierr
221    INTEGER, DIMENSION(2)                     :: start, epais
222    REAL, DIMENSION(klon_glo,nbsrf)           :: pct_glo  ! fraction at global grid
223    REAL, DIMENSION(klon_glo)                 :: sst_glo  ! sea-surface temperature at global grid
224    REAL, DIMENSION(klon_glo)                 :: rug_glo  ! rugosity at global grid
225    REAL, DIMENSION(klon_glo)                 :: alb_glo  ! albedo at global grid
226
227    REAL, DIMENSION(klon_mpi,nbsrf)           :: pct_mpi  ! fraction at global grid
228    REAL, DIMENSION(klon_mpi)                 :: sst_mpi  ! sea-surface temperature at global grid
229    REAL, DIMENSION(klon_mpi)                 :: rug_mpi  ! rugosity at global grid
230    REAL, DIMENSION(klon_mpi)                 :: alb_mpi  ! albedo at global grid
231!GG
232    REAL, DIMENSION(klon_glo)                 :: sih_glo  ! albedo at global grid
233    REAL, DIMENSION(klon_mpi)                 :: sih_mpi  ! albedo at global grid
234!GG
235
236    CHARACTER(len=20)                         :: modname='limit_read_mod'     
237    CHARACTER(LEN=99)                         :: abort_message, calendar, str
238
239! End declaration
240!****************************************************************************************
241
242!****************************************************************************************
243! 0) Initialization
244!
245!****************************************************************************************
246    IF (first_call) THEN
247       first_call=.FALSE.
248       ! calculate number of time steps for one day
249       lmt_pas = NINT(86400./dtime * 1.0)
250       
251       ! Allocate module save variables
252       IF ( type_ocean /= 'couple' ) THEN
253          ALLOCATE(pctsrf(klon,nbsrf), sst(klon), stat=ierr)
254          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating pctsrf and sst',1)
255       END IF
256
257       !GG
258       IF (iflag_seaice==1) THEN
259             ALLOCATE(sih(klon), stat=ierr)
260             IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating sih',1)
261       ENDIF
262       !GG
263
264       IF ( .NOT. ok_veget ) THEN
265          ALLOCATE(rugos(klon), albedo(klon), stat=ierr)
266          IF (ierr /= 0) CALL abort_physic(modname, 'PB in allocating rugos and albedo',1)
267       END IF
268
269!$OMP MASTER  ! Only master thread
270       IF (is_mpi_root) THEN ! Only master processus
271          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
272          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
273               'Pb d''ouverture du fichier de conditions aux limites',1)
274
275          !--- WARNING IF CALENDAR IS KNOWN AND DOES NOT MATCH THE ONE OF LMDZ
276          ierr=NF90_INQ_VARID(nid, 'TEMPS', nvarid)
277          ierr=NF90_GET_ATT(nid, nvarid, 'calendar', calendar)
278          IF(ierr==NF90_NOERR.AND.calendar/=calend.AND.prt_level>=1) THEN
279             WRITE(lunout,*)'BEWARE: gcm and limit.nc calendars differ: '
280             WRITE(lunout,*)'  '//TRIM(calend)//' for gcm'
281             WRITE(lunout,*)'  '//TRIM(calendar)//' for limit.nc file'
282          END IF
283
284          !--- ERROR IF FILE RECORDS NUMBER IS NOT EQUAL TO EXPECTED NUMBER OF DAYS         
285          IF (grid_type==unstructured) THEN
286            ierr=NF90_INQ_DIMID(nid,"time_year",ndimid)
287          ELSE
288            ierr=NF90_INQUIRE(nid, UnlimitedDimID=ndimid)
289          ENDIF
290          ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn)
291          WRITE(abort_message,'(a,2(i0,a))')'limit.nc records number (',nn,') does no'//&
292            't match year length (',year_len,')'
293          IF(nn/=year_len) CALL abort_physic(modname,abort_message,1)
294
295          !--- ERROR IF FILES AND LMDZ HORIZONTAL RESOLUTIONS DO NOT MATCH
296          IF (grid_type==unstructured) THEN
297            ierr=NF90_INQ_DIMID(nid, 'cell', ndimid)
298          ELSE
299            ierr=NF90_INQ_DIMID(nid, 'points_physiques', ndimid)
300          ENDIF
301          ierr=NF90_INQUIRE_DIMENSION(nid, ndimid, len=nn)
302          WRITE(abort_message,'(a,2(i0,a))')'limit.nc horizontal number of cells (',nn, &
303            ') does not match LMDZ klon_glo (',klon_glo,')'
304          IF(nn/=klon_glo) CALL abort_physic(modname,abort_message,1)
305
306          ierr = NF90_CLOSE(nid)
307          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
308       END IF ! is_mpi_root
309!$OMP END MASTER
310!$OMP BARRIER
311    END IF
312
313!****************************************************************************************
314! 1) Open the file limit.nc if it is the right moment to read, once a day.
315!    The file is read only by the master thread of the master mpi process(is_mpi_root)
316!    Check by the way if the number of records is correct.
317!
318!****************************************************************************************
319
320    is_modified = .FALSE.
321!ym    IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN   ! time to read
322!  not REALLY PERIODIC
323    IF (MOD(itime-1, lmt_pas) == 0 .OR. (jour_lu /= jour .AND. grid_type /= unstructured)) THEN   ! time to read
324!    IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
325       jour_lu = jour
326       is_modified = .TRUE.
327
328      IF (grid_type==unstructured) THEN
329
330        IF ( type_ocean /= 'couple') THEN
331
332           IF (is_omp_master) CALL xios_recv_field("foce_limin",pct_mpi(:,is_oce))
333           IF (is_omp_master) CALL xios_recv_field("fsic_limin",pct_mpi(:,is_sic))
334  !         IF (read_continents .OR. itime == 1) THEN
335           IF (is_omp_master) CALL xios_recv_field("fter_limin",pct_mpi(:,is_ter))
336           IF (is_omp_master) CALL xios_recv_field("flic_limin",pct_mpi(:,is_lic))
337  !         ENDIF
338         ENDIF! type_ocean /= couple
339         
340         IF ( type_ocean /= 'couple') THEN                   
341             IF (is_omp_master) CALL xios_recv_field("sst_limin",sst_mpi)
342             !GG
343             IF (is_omp_master) CALL xios_recv_field("sih_limin",sih_mpi)
344             !GG
345         ENDIF
346       
347         IF (.NOT. ok_veget) THEN
348           IF (is_omp_master) CALL xios_recv_field("alb_limin",alb_mpi)
349           IF (is_omp_master) CALL xios_recv_field("rug_limin",rug_mpi)
350         ENDIF
351
352       IF ( type_ocean /= 'couple') THEN
353          CALL Scatter_omp(sst_mpi,sst)
354          !GG
355          CALL Scatter_omp(sih_mpi,sih)
356          !GG
357          CALL Scatter_omp(pct_mpi(:,is_oce),pctsrf(:,is_oce))
358          CALL Scatter_omp(pct_mpi(:,is_sic),pctsrf(:,is_sic))
359!          IF (read_continents .OR. itime == 1) THEN
360             CALL Scatter_omp(pct_mpi(:,is_ter),pctsrf(:,is_ter))
361             CALL Scatter_omp(pct_mpi(:,is_lic),pctsrf(:,is_lic))
362!          END IF
363       END IF
364
365       IF (.NOT. ok_veget) THEN
366          CALL Scatter_omp(alb_mpi, albedo)
367          CALL Scatter_omp(rug_mpi, rugos)
368       END IF
369 
370     ELSE      ! grid_type==regular
371
372!$OMP MASTER  ! Only master thread
373       IF (is_mpi_root) THEN ! Only master processus!
374
375          ierr = NF90_OPEN ('limit.nc', NF90_NOWRITE, nid)
376          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,&
377               'Pb d''ouverture du fichier de conditions aux limites',1)
378
379          ! La tranche de donnees a lire:
380          start(1) = 1
381          start(2) = jour
382          epais(1) = klon_glo
383          epais(2) = 1
384
385
386!****************************************************************************************
387! 2) Read fraction if not type_ocean=couple
388!
389!****************************************************************************************
390
391          IF ( type_ocean /= 'couple') THEN
392!
393! Ocean fraction
394             ierr = NF90_INQ_VARID(nid, 'FOCE', nvarid)
395             IF (ierr /= NF90_NOERR) CALL abort_physic(modname, 'Le champ <FOCE> est absent',1)
396             
397             ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_oce),start,epais)
398             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FOCE>' ,1)
399!
400! Sea-ice fraction
401             ierr = NF90_INQ_VARID(nid, 'FSIC', nvarid)
402             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FSIC> est absent',1)
403
404             ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_sic),start,epais)
405             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FSIC>' ,1)
406
407! GG
408! Account for leads
409             IF (iflag_seaice>0) THEN
410               DO ii=1,klon_glo/2
411                 if (pct_glo(ii,is_sic)>amax_n) THEN
412                    pct_glo(ii,is_oce)=pct_glo(ii,is_oce)+(pct_glo(ii,is_sic)-amax_n)
413                    pct_glo(ii,is_sic)=amax_n
414                 end if
415               ENDDO
416               DO ii=klon_glo/2,klon_glo
417               if (pct_glo(ii,is_sic)>amax_s) THEN
418                    pct_glo(ii,is_oce)=pct_glo(ii,is_oce)+(pct_glo(ii,is_sic)-amax_s)
419                    pct_glo(ii,is_sic)=amax_s
420               end if
421               ENDDO
422             ENDIF
423!GG
424
425! Read land and continentals fraction only if asked for
426             IF (read_continents .OR. itime == 1) THEN
427!
428! Land fraction
429                ierr = NF90_INQ_VARID(nid, 'FTER', nvarid)
430                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FTER> est absent',1)
431               
432                ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_ter),start,epais)
433                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FTER>',1)
434!
435! Continentale ice fraction
436                ierr = NF90_INQ_VARID(nid, 'FLIC', nvarid)
437                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <FLIC> est absent',1)
438
439                ierr = NF90_GET_VAR(nid,nvarid,pct_glo(:,is_lic),start,epais)
440                IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <FLIC>',1)
441             END IF
442
443          END IF ! type_ocean /= couple
444
445!****************************************************************************************
446! 3) Read sea-surface temperature, if not coupled ocean
447!
448!****************************************************************************************
449          IF ( type_ocean /= 'couple') THEN
450
451             ierr = NF90_INQ_VARID(nid, 'SST', nvarid)
452             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <SST> est absent',1)
453
454             ierr = NF90_GET_VAR(nid,nvarid,sst_glo,start,epais)
455             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <SST>',1)
456           !GG
457             IF (iflag_seaice == 1) THEN
458               ierr = NF90_INQ_VARID(nid, 'HICE', nvarid)
459               IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <HICE> est absent',1)
460
461               ierr = NF90_GET_VAR(nid,nvarid,sih_glo(:),start,epais)
462               IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <HICE>' ,1)
463             ENDIF
464            !GG
465          END IF
466
467!****************************************************************************************
468! 4) Read albedo and rugosity for land surface, only in case of no vegetation model
469!
470!****************************************************************************************
471
472          IF (.NOT. ok_veget) THEN
473!
474! Read albedo
475             ierr = NF90_INQ_VARID(nid, 'ALB', nvarid)
476             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <ALB> est absent',1)
477
478             ierr = NF90_GET_VAR(nid,nvarid,alb_glo,start,epais)
479             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <ALB>',1)
480!
481! Read rugosity
482             ierr = NF90_INQ_VARID(nid, 'RUG', nvarid)
483             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Le champ <RUG> est absent',1)
484
485             ierr = NF90_GET_VAR(nid,nvarid,rug_glo,start,epais)
486             IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Lecture echouee pour <RUG>',1)
487
488          END IF
489
490!****************************************************************************************
491! 5) Close file and distribuate variables to all processus
492!
493!****************************************************************************************
494          ierr = NF90_CLOSE(nid)
495          IF (ierr /= NF90_NOERR) CALL abort_physic(modname,'Pb when closing file', 1)
496       ENDIF ! is_mpi_root
497
498!$OMP END MASTER
499!$OMP BARRIER
500
501       IF ( type_ocean /= 'couple') THEN
502          CALL Scatter(sst_glo,sst)
503          !GG
504          IF (iflag_seaice==1) THEN
505             CALL Scatter(sih_glo,sih)
506          END IF
507          !GG
508          CALL Scatter(pct_glo(:,is_oce),pctsrf(:,is_oce))
509          CALL Scatter(pct_glo(:,is_sic),pctsrf(:,is_sic))
510          IF (read_continents .OR. itime == 1) THEN
511             CALL Scatter(pct_glo(:,is_ter),pctsrf(:,is_ter))
512             CALL Scatter(pct_glo(:,is_lic),pctsrf(:,is_lic))
513          END IF
514       END IF
515
516       IF (.NOT. ok_veget) THEN
517          CALL Scatter(alb_glo, albedo)
518          CALL Scatter(rug_glo, rugos)
519       END IF
520
521      ENDIF ! Grid type
522
523    ENDIF ! time to read
524
525  END SUBROUTINE limit_read_tot
526
527END MODULE limit_read_mod
Note: See TracBrowser for help on using the repository browser.