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 @ 1146

Last change on this file since 1146 was 1146, checked in by rblod, 16 years ago

Add svn Id (first try), see ticket #210

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 7.7 KB
Line 
1MODULE exampl
2   !!======================================================================
3   !!                       ***  MODULE  exampl  ***
4   !! Ocean physics:  brief description of the purpose of the module
5   !!                 (please no more than 2 lines)
6   !!======================================================================
7   !! History : 3.0  !  2008-06  (Author Names)  Original code
8   !!            -   !  2008-08  (Author names)  brief description of modifications
9   !!           3.1  !  2008-12  (Author names)        -              -
10   !!----------------------------------------------------------------------
11
12#if defined key_example
13   !!----------------------------------------------------------------------
14   !!   'key_example'  :                brief description of the key option
15   !!----------------------------------------------------------------------
16   !!   exa_mpl       : liste of module subroutine (caution, never use the
17   !!   exa_mpl_init  : name of the module for a routine)
18   !!   exa_mpl_stp   : Please try to use 3 letter block for routine names
19   !!----------------------------------------------------------------------
20   USE module_name1   ! brief description of the used module
21   USE module_name2   ! ....
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   exa_mpl   ! routine called in xxx.F90 module
27
28   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   var1         !: var1 description. CAUTION always use !: to describe
29   !                                                          !  a PUBLIC variable: simplify its search :
30   !                                                          !  grep var1 *90 | grep '!:'
31   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   var2, var2   !: several variable on a same line OK, but
32   !                                                          !  DO NOT use continuation lines in declaration
33
34   !                             !!! ** namelist nam_xxx **
35   LOGICAL  ::   ln_opt = 1       ! give the default value of each namelist parameter
36   CHARACTER::   cn_tex = 'T'     ! short description  of the variable
37   INTEGER  ::   nn_opt = 1       ! please respect the DOCTOR norm for namelist variable
38   REAL(wp) ::   rn_var = 2._wp   ! (it becomes easy to identify them in the code)
39
40   INTEGER                          ::   nint    ! nint  description (local permanent variable)
41   REAL(wp)                         ::   var     ! var         -                -
42   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   array   ! array       -                -
43
44   !! * Substitutions
45#  include "exampl_substitute.h90"
46   !!----------------------------------------------------------------------
47   !! NEMO/OPA 3.0 , LOCEAN-IPSL (2008)
48   !! $Id$
49   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
50   !!----------------------------------------------------------------------
51
52CONTAINS
53
54   SUBROUTINE exa_mpl( kt, pvar1, pvar2, ptab )
55      !!----------------------------------------------------------------------
56      !!                    ***  ROUTINE exa_mpl  ***
57      !!
58      !! ** Purpose :   Brief description of the routine
59      !!
60      !! ** Method  :   description of the methodoloy used to achieve the
61      !!                objectives of the routine. Be as clear as possible!
62      !!
63      !! ** Action  : - first action (share memory array/varible modified
64      !!                in this routine
65      !!              - second action .....
66      !!              - .....
67      !!
68      !! References :   Author et al., Short_name_review, Year
69      !!                Give references if exist otherwise suppress these lines
70      !!----------------------------------------------------------------------
71      USE toto_module      ! description od the module
72      !!
73      INTEGER , INTENT(in   )                     ::   kt      ! short description
74      INTEGER , INTENT(inout)                     ::   pvar1   !   -         -
75      REAL(wp), INTENT(  out)                     ::   pvar2   !   -         -
76      REAL(wp), INTENT(  out), DIMENSION(jpi,jpj) ::   pvar2   !   -         -
77      !!
78      INTEGER  ::   ji, jj, jk       ! dummy loop arguments  (DOCTOR : start with j, but not jp)
79      INTEGER  ::   itoto, itata     ! temporary integers    (DOCTOR : start with i
80      REAL(wp) ::   zmlmin, zbbrau   ! temporary scalars     (DOCTOR : start with z)
81      REAL(wp) ::   zfact1, zfact2   ! do not use continuation lines in declaration
82      REAL(wp), DIMENSION(jpi,jpk) ::   ztoto   ! 2D workspace
83      !!--------------------------------------------------------------------
84
85      IF( kt == nit000  )   CALL exa_mpl_init    ! Initialization (first time-step only)
86
87      zmlmin = 1.e-8                             ! Local constant initialization
88      zbbrau =  .5 * ebb / rau0
89      zfact1 = -.5 * rdt * efave
90      zfact2 = 1.5 * rdt * ediss
91
92      SELECT CASE ( npdl )                       ! short description of the action
93      !
94      CASE ( 0 )                                      ! describe case 1
95         DO jk = 2, jpkm1
96            DO jj = 2, jpjm1
97               DO ji = fs_2, fs_jpim1   ! vector opt.
98                  avmv(ji,jj,jk) = ....
99               END DO
100            END DO
101         END DO
102         !
103      CASE ( 1 )                                      ! describe case 2
104         DO jk = 2, jpkm1
105            DO jj = 2, jpjm1
106               DO ji = fs_2, fs_jpim1   ! vector opt.
107                  avmv(ji,jj,jk) = ...
108               END DO
109            END DO
110         END DO
111         !
112      END SELECT
113
114      CALL mpplnk2( avmu, 'U', 1. )              ! Lateral boundary conditions (avmu)   (unchanged sign)
115      !
116   END SUBROUTINE exa_mpl
117
118
119   SUBROUTINE exa_mpl_init
120      !!----------------------------------------------------------------------
121      !!                  ***  ROUTINE exa_mpl_init  ***
122      !!                   
123      !! ** Purpose :   initialization of ....
124      !!
125      !! ** Method  :   blah blah blah ...
126      !!
127      !! ** input   :   Namlist namexa
128      !!
129      !! ** Action  :   ... 
130      !!----------------------------------------------------------------------
131      INTEGER ::   ji, jj, jk, jit   ! dummy loop indices
132      !!
133      NAMELIST/namexa/ exa_v1, exa_v2, nexa_0       
134      !!----------------------------------------------------------------------
135      !
136      REWIND ( numnam )                          ! Read Namelist namexa : example parameters
137      READ   ( numnam, namexa )
138      !
139      IF(lwp) THEN                               ! Control print
140         WRITE(numout,*)
141         WRITE(numout,*) 'exa_mpl_init : example '
142         WRITE(numout,*) '~~~~~~~~~~~~'
143         WRITE(numout,*) '          Namelist namexa : set example parameters'
144         WRITE(numout,*) '             brief desciption               exa_v1  = ', exa_v1
145         WRITE(numout,*) '             brief desciption               exa_v1  = ', exa_v1
146         WRITE(numout,*) '             brief desciption               nexa_0  = ', nexa_0
147      ENDIF
148      !
149      !                                          ! Parameter control
150      IF( ln_opt  )   CALL ctl_stop( 'this work and option xxx are incompatible'   )
151      IF( ln_opt2 )   CALL ctl_warn( 'this work and option yyy may cause problems' )
152      ENDIF
153      !
154   END SUBROUTINE exa_mpl_init
155
156#else
157   !!----------------------------------------------------------------------
158   !!   Default option :                                         NO example
159   !!----------------------------------------------------------------------
160CONTAINS
161   SUBROUTINE exa_mpl( kt, pvar1, pvar2, ptab )              ! Empty routine
162      REAL::   ptab(:,:)
163      WRITE(*,*) 'exa_mpl: You should not have seen this print! error?', kt, pvar1, pvar2, ptab(1,1)
164   END SUBROUTINE exa_mpl
165#endif
166
167   !!======================================================================
168END MODULE exampl
Note: See TracBrowser for help on using the repository browser.