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.
module_example in trunk/NEMO/OPA_SRC – NEMO

source: trunk/NEMO/OPA_SRC/module_example @ 3

Last change on this file since 3 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.5 KB
Line 
1MODULE exampl
2   !!======================================================================
3   !!                       ***  MODULE  example  ***
4   !! Ocean physics:  brief description of the purpose of the module
5   !!                 (please no more than 2 lines)
6   !!=====================================================================
7#if defined key_example
8   !!----------------------------------------------------------------------
9   !!   'key_example'  :                brief description of the key option
10   !!----------------------------------------------------------------------
11   !!   exa_mpl      : liste of module subroutine (caution, never use the
12   !!   exa_mpl_init : name of the module for a routine)
13   !!   exa_mpl_stp  : Please try to use 3 letter block for routine names
14   !!----------------------------------------------------------------------
15   !! * Modules used
16   USE module_name1            ! brief description of the used module
17   USE module_name2            ! ....
18
19   IMPLICIT NONE
20   PRIVATE
21
22   !! *  Routine accessibility
23   PUBLIC exa_mpl    ! routine called in xxx.F90 module
24
25   !! * Share Module variables
26   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &
27      var1    ,   &  !: var1 description (CAUTION always use !: to describe a
28      !              !  PUBLIC variable simplify the search of where it is declared
29      var2           !: var2 description
30
31   !! * Module variables
32   INTEGER ::                 & !!! ** toto namelist (namtoto) **
33      nflag  =  1                ! default value of nflag
34   REAL(wp) ::                & !!! ** toto namlist (namtoto) **
35      var3  = 2._wp / 9._wp      ! default value of var3
36   REAL(wp) ::   & 
37      var4          ! var4 description (local permanent variable)
38   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   &
39      tab1          ! coefficient used for horizontal smoothing
40
41   !! * Substitutions
42#  include "exampl_substitute.h90"
43   !!----------------------------------------------------------------------
44   !!   OPA 9.0 , LODYC-IPSL  (2003)
45   !!----------------------------------------------------------------------
46
47CONTAINS
48
49# if defined key_autotasking
50   !!----------------------------------------------------------------------
51   !!   'key_autotasking'                              autotasking (j-slab)
52   !!----------------------------------------------------------------------
53#  include "exampl_autotsk.h90"
54
55# else
56   !!----------------------------------------------------------------------
57   !!   Default option :                           vector opt. (k-j-i loop)
58   !!----------------------------------------------------------------------
59
60   SUBROUTINE exa_mpl( kt )
61      !!----------------------------------------------------------------------
62      !!                    ***  ROUTINE exa_mpl  ***
63      !!
64      !! ** Purpose :   Brief description of the routine
65      !!
66      !! ** Method  :   description of the methodoloy used to achieve the
67      !!      objectives of the routine. Be as clear as possible!
68      !!
69      !! ** Action  : - first action (share memory array/varible modified
70      !!                in this routine
71      !!              - second action .....
72      !!              - .....
73      !!
74      !! References :
75      !!   Give references if exist otherwise suppress these lines
76      !!
77      !! History :
78      !!   9.0  !  03-08  (Autor Names)  Original code
79      !!        !  02-08  (Author names)  brief description of modifications
80      !!----------------------------------------------------------------------
81      !! * Modules used
82      USE toto_module                ! description od the module
83
84      !! * arguments
85      INTEGER, INTENT( in  ) ::   & 
86         kt                          ! describe it!!!
87
88      !! * local declarations
89      INTEGER ::   ji, jj, jk        ! dummy loop arguments
90      INTEGER ::   &
91         itoto, itata,            &  ! temporary integers
92         ititi                       ! please do not forget the DOCTOR rule:
93         !                           ! local integer: name start with i
94      REAL(wp) ::   &
95         zmlmin, zbbrau,          &  ! temporary scalars
96         zfact1, zfact2, zfact3,  &  !    "         "
97         zbn2, zesurf,            &  ! local scalar: name start with z
98         zemxl                       !
99      REAL(wp), DIMENSION(jpi,jpk) ::   &
100         ztoto                       ! temporary workspace
101      !!--------------------------------------------------------------------
102
103
104
105      IF( kt == nit000  )   CALL zdf_tke_init    ! Initialization (first time-step only)
106
107      ! Local constant initialization
108      zmlmin = 1.e-8
109      zbbrau =  .5 * ebb / rau0
110      zfact1 = -.5 * rdt * efave
111      zfact2 = 1.5 * rdt * ediss
112      zfact3 = 0.5 * rdt * ediss
113
114
115      SELECT CASE ( npdl )
116
117      CASE ( 0 )           ! describe case 1
118         DO jk = 2, jpkm1
119            DO jj = 2, jpjm1
120               DO ji = fs_2, fs_jpim1   ! vector opt.
121                  avmv(ji,jj,jk) = ....
122               END DO
123            END DO
124         END DO
125
126      CASE ( 1 )           ! describe case 2
127         DO jk = 2, jpkm1
128            DO jj = 2, jpjm1
129               DO ji = fs_2, fs_jpim1   ! vector opt.
130                  avmv(ji,jj,jk) = ...
131               END DO
132            END DO
133         END DO
134
135      END SELECT
136
137      ! Lateral boundary conditions (avmu)   (unchanged sign)
138      CALL mpplnk2( avmu, 'U', 1. )
139
140   END SUBROUTINE exa_mpl
141
142# endif
143
144   SUBROUTINE exa_mpl_init
145      !!----------------------------------------------------------------------
146      !!                  ***  ROUTINE exa_mpl_init  ***
147      !!                   
148      !! ** Purpose :   initialization of ....
149      !!
150      !! ** Method  :   blah blah blah ...
151      !!
152      !! ** input   :   Namlist namexa
153      !!
154      !! ** Action  :   ... 
155      !!
156      !! history :
157      !!   9.0  !  03-08  (Autor Names)  Original code
158      !!----------------------------------------------------------------------
159      !! * local declarations
160      INTEGER ::   ji, jj, jk, jit   ! dummy loop indices
161
162      NAMELIST/namexa/ exa_v1, exa_v2, nexa_0 
163      !!----------------------------------------------------------------------
164
165      ! Read Namelist namexa : example parameters
166      REWIND ( numnam )
167      READ   ( numnam, namexa )
168
169
170      ! Control print
171      IF(lwp) THEN
172         WRITE(numout,*)
173         WRITE(numout,*) 'exa_mpl_init : example '
174         WRITE(numout,*) '~~~~~~~~~~~~'
175         WRITE(numout,*) '          Namelist namexa : set example parameters'
176         WRITE(numout,*) '             brief desciption               exa_v1  = ', exa_v1
177         WRITE(numout,*) '             brief desciption               exa_v1  = ', exa_v1
178         WRITE(numout,*) '             brief desciption               nexa_0  = ', nexa_0
179      ENDIF
180
181      ! Parameter control
182#if defined key_toto
183      IF(lwp) WRITE(numout,cform_err)
184      IF(lwp) WRITE(numout,*) '          this part and key_toto are incompatible'
185      nstop = nstop + 1
186#endif
187
188      ! Check nexa_0 values
189      IF( nexa_0 < 0 ) THEN
190         IF(lwp) WRITE(numout,cform_err)
191         IF(lwp) WRITE(numout,*) '          bad flag: nmxl is < 0 or > 3 '
192         nstop = nstop + 1
193      ENDIF
194
195   END SUBROUTINE zdf_tke_init
196
197#else
198   !!----------------------------------------------------------------------
199   !!   Default option :                                       Empty module
200   !!----------------------------------------------------------------------
201CONTAINS
202   SUBROUTINE exa_mpl              ! Empty routine
203   END SUBROUTINE exa_mpl
204#endif
205
206   !!======================================================================
207END MODULE exampl
Note: See TracBrowser for help on using the repository browser.