source: LMDZ6/branches/PBLSURF_GPUPORT/libf/phylmd/limit_read_mod.f90 @ 5932

Last change on this file since 5932 was 5896, checked in by yann meurdesoif, 7 weeks ago

GPU port of surf_ocean

YM

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