SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
get_sizes_parallel.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 SUBROUTINE get_sizes_parallel (DTCO, DGU, UG, U, &
6  kproc,ksize,kprocmin,ksize_task,oshadows)
7 !
8 !
9 ! Modified by B. Decharme (08/2013): bug in KSIZE_TASK
10 !
11 ! Modif Matthieu Lafaysse 04/2014
12 ! For shadows routines, we need strictly rectangular subdomains
13 
14 !
15 !
16 !
20 USE modd_surf_atm_n, ONLY : surf_atm_t
21 !
22 #ifdef SFX_OL
23 USE modd_slope_effect, ONLY : nix,niy
24 USE modn_io_offline, ONLY : csurf_filetype
25 #endif
26 USE modi_init_io_surf_n
28 USE modi_read_gridtype
29 USE modi_get_grid_dim
30 !RJ: missing modi
31 USE modi_end_io_surf_n
32 !
33 USE yomhook ,ONLY : lhook, dr_hook
34 USE parkind1 ,ONLY : jprb
35 !
36 IMPLICIT NONE
37 !
38 !
39 !
40 TYPE(data_cover_t), INTENT(INOUT) :: dtco
41 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
42 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
43 TYPE(surf_atm_t), INTENT(INOUT) :: u
44 !
45 !
46 INTEGER, INTENT(IN) :: kproc
47 INTEGER, INTENT(IN) :: ksize
48 INTEGER, INTENT(IN) :: kprocmin
49 LOGICAL, INTENT(IN),OPTIONAL :: oshadows
50 
51 LOGICAL::gshadows
52 
53 LOGICAL :: grect
54 
55 INTEGER, DIMENSION(0:KPROC-1), INTENT(OUT) :: ksize_task
56 !
57 
58 INTEGER::iresp
59 
60 INTEGER :: isize, ireste, inreste
61 INTEGER :: j, iproc
62 INTEGER :: isize_y,iny_thread,iny_reste
63 
64 REAL(KIND=JPRB) :: zhook_handle
65 !
66 IF (lhook) CALL dr_hook('GET_SIZES_PARALLEL',0,zhook_handle)
67 !
68 
69 IF (present(oshadows)) THEN
70  gshadows=oshadows
71 ELSE
72  gshadows=.false.
73 ENDIF
74 
75 IF (gshadows) THEN
76  ! We want only rectangular subdomains
77 
78  ! Get x and y dimension lengths
79 #ifdef SFX_OL
80 !$OMP SINGLE
81  IF (nix==0) THEN
82 
83  !CALL SET_SURFEX_FILEIN(CSURF_FILETYPE,'PREP ') ! not necessary, it works with PGD or PREP file
84  CALL init_io_surf_n(dtco, dgu, u, &
85  csurf_filetype,'FULL ','SURF ','READ ')
86  CALL read_surf(&
87  csurf_filetype,'GRID_TYPE',ug%CGRID,iresp,hdir='A')
88  CALL read_gridtype(&
89  csurf_filetype,ug%CGRID,ug%NGRID_PAR,u%NDIM_FULL,.false.,hdir="A")
90  ALLOCATE(ug%XGRID_FULL_PAR(ug%NGRID_PAR))
91  CALL read_gridtype(&
92  csurf_filetype,ug%CGRID,ug%NGRID_PAR,u%NDIM_FULL,.true.,ug%XGRID_FULL_PAR,iresp,hdir="A")
93  CALL end_io_surf_n(csurf_filetype)
94  CALL get_grid_dim(ug%CGRID,SIZE(ug%XGRID_FULL_PAR),ug%XGRID_FULL_PAR,grect,nix,niy)
95  ug%XGRID_FULL_PAR=>null()
96  ENDIF
97 !$OMP END SINGLE
98 
99  !If get_sizes_parallel is called by init_index_mpi
100  !ISIZE_Y represents the number of lines of the total domain
101  !INY_THREAD represents the number of lines for 1 MPI thread
102  !If get_sizes_parallel is called by offline
103  !ISIZE_Y represents the number of lines of 1 MPI thread
104  !INY_THREAD represent the number of lines for 1 OPEN-MP thread
105 
106  isize_y=ksize/nix
107 
108  ! Number of lines (y) for one thread
109  iny_thread=isize_y/kproc
110  iny_reste=isize_y-kproc*iny_thread
111 
112  ksize_task(:)=iny_thread*nix
113 
114  DO j=kprocmin+kproc-iny_reste,kprocmin+kproc-1
115  ksize_task(mod(j,kproc))=ksize_task(mod(j,kproc))+nix
116  END DO
117 #endif
118 ELSE
119  isize = ceiling(ksize*1./kproc) !nb of points by task
120 
121  inreste = kproc*isize - ksize ! nb of tasks containing ireste points
122  IF (inreste>0) THEN
123  ireste = isize - 1
124  ELSE
125  ireste = isize
126  ENDIF
127 !
128  ksize_task(:) = isize
129  IF (inreste>0) THEN
130  DO j = kprocmin+kproc-inreste,kprocmin+kproc-1
131  ksize_task(mod(j,kproc)) = ireste
132  ENDDO
133  ENDIF
134 !
135 !so:
136 !(nproc-nreste)*isize + nreste*ireste = ndim_full
137 !if nreste==1:
138 !(nproc-1)*isize + ireste =
139 !(nproc-1)*isize + NDIM_FULL - (nproc-1)*isize = NDIM_FULL
140 !if (ireste==isize-1):
141 !nproc*isize - nreste*isize + nreste*isize - nreste =
142 !nproc*isize - nreste = NDIM_FULL
143 
144 
145 ENDIF
146 !
147 IF (lhook) CALL dr_hook('GET_SIZES_PARALLEL',1,zhook_handle)
148 !
149 END SUBROUTINE get_sizes_parallel
subroutine init_io_surf_n(DTCO, DGU, U, HPROGRAM, HMASK, HSCHEME, HACTION)
subroutine read_gridtype(HPROGRAM, HGRID, KGRID_PAR, KLU, OREAD, PGRID_PAR, KRESP, HDIR)
subroutine get_sizes_parallel(DTCO, DGU, UG, U, KPROC, KSIZE, KPROCMIN, KSIZE_TASK, OSHADOWS)
subroutine get_grid_dim(HGRID, KGRID_PAR, PGRID_PAR, ORECT, KDIM1, KDIM2)
Definition: get_grid_dim.F90:6
subroutine end_io_surf_n(HPROGRAM)
Definition: end_io_surfn.F90:6