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/NEMOGCM/NEMO/OPA_SRC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/module_example @ 2733

Last change on this file since 2733 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

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