New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
dom_omp.F90 in branches/2017/wrk_OMP_test_for_Silvia/NEMOGCM/NEMO/OPA_SRC/DOM – NEMO

source: branches/2017/wrk_OMP_test_for_Silvia/NEMOGCM/NEMO/OPA_SRC/DOM/dom_omp.F90 @ 8279

Last change on this file since 8279 was 8279, checked in by mocavero, 7 years ago

Implementation of OMP coarse-grained parallelization on ZDF new package

File size: 3.1 KB
Line 
1MODULE dom_omp
2   !!======================================================================
3   !!                      ***  MODULE  domain_omp  ***
4   !! OpenMP horizontal decoposition : OpenMP threads domain decomposition
5   !!======================================================================
6   !! History :  4.0  !  2017-05  (S. Mocavero - F. Mele)  original code
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   tile_dec_2D  : initialize local threads indices
11   !!----------------------------------------------------------------------
12
13  USE par_oce        ! ocean space and time domain
14  USE in_out_manager ! I/O manager
15
16  IMPLICIT NONE
17
18  INTEGER         :: jtni 
19  INTEGER         :: jtnj
20  INTEGER         :: jtnij
21
22  INTEGER         :: tnarea
23  INTEGER         :: tnareai
24  INTEGER         :: tnareaj
25
26  INTEGER,SAVE    :: tnldi,tnldj
27  INTEGER,SAVE    :: tnlei,tnlej
28!$OMP THREADPRIVATE(tnldi,tnldj,tnlei,tnlej)
29
30CONTAINS
31  SUBROUTINE tile_dec_2D
32      !!----------------------------------------------------------------------
33      !!                     ***  ROUTINE tile_dec_2D  ***
34      !!                   
35      !! ** Purpose :   read namomp namelists and initialize local threads indices
36      !!
37      !! ** input   : - namomp namelist
38      !!----------------------------------------------------------------------
39      INTEGER :: ii,jj
40      INTEGER :: tnlci,tnlcj
41      INTEGER :: omp_get_thread_num
42      INTEGER :: omp_get_num_threads
43      INTEGER :: ios
44      !
45      NAMELIST/namomp/ jtni
46      !!----------------------------------------------------------------------
47      REWIND( numnam_cfg )
48      READ  ( numnam_cfg, namomp, IOSTAT = ios )
49
50      CALL OMP_SET_DYNAMIC(.FALSE.)
51
52!$OMP PARALLEL PRIVATE(tnarea,tnareai,tnareaj,ii,jj,tnlci,tnlcj)
53!$OMP SINGLE
54      jtnij = omp_get_num_threads()
55       
56      jtnj = jtnij / jtni          ! threads number along domain latitude
57      IF((jtni.GT.jtnij).OR.(MOD(jtnij,jtni).NE.0)) THEN
58         WRITE(*,*) ' tile_dec_2D: Error while setting OpenMP decomposition' 
59         WRITE(*,*) ' -> disabled OpenMP decomposition on  direction' 
60         jtni = 1
61         jtnj = jtnij
62      ENDIF
63!$OMP END SINGLE
64
65      tnarea = omp_get_thread_num()
66      tnareai = MOD(tnarea, jtni)
67      tnareaj = tnarea / jtni
68
69      tnlei=0
70      DO ii=0,tnareai
71         tnldi=tnlei+1
72         tnlci=jpi/jtni
73         IF (MOD(jpi,jtni)>ii) tnlci=tnlci+1
74         tnlei=tnldi+tnlci-1
75      ENDDO
76
77      tnlej=0
78      DO jj=0,tnareaj
79         tnldj=tnlej+1
80         tnlcj=jpj/jtnj
81         IF (MOD(jpj,jtnj)>jj) tnlcj=tnlcj+1
82         tnlej=tnldj+tnlcj-1
83      ENDDO
84
85      IF(tnareai == 0) THEN
86#if defined key_vectopt_loop
87         tnldi = 1
88#else
89         tnldi = 2
90#endif
91      END IF
92
93      IF(tnareaj == 0) THEN
94         tnldj = 2
95      END IF
96
97      IF(tnareai == jtni-1) THEN
98#if defined key_vectopt_loop
99         tnlei = jpi
100#else
101         tnlei = jpim1
102#endif
103      ENDIF
104
105      IF(tnareaj == jtnj-1) THEN
106         tnlej = jpjm1
107      ENDIF
108!$OMP END PARALLEL
109
110  END SUBROUTINE tile_dec_2D
111
112END MODULE dom_omp
Note: See TracBrowser for help on using the repository browser.