source: LMDZ6/branches/contrails/libf/phylmd/limit_read_mod.f90 @ 5791

Last change on this file since 5791 was 5791, checked in by aborella, 4 months ago

Merge with trunk r5789

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