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.
flodom.F90 in branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/FLO – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/FLO/flodom.F90 @ 4400

Last change on this file since 4400 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

  • Property svn:keywords set to Id
File size: 20.4 KB
Line 
1MODULE flodom
2   !!======================================================================
3   !!                       ***  MODULE  flodom  ***
4   !! Ocean floats :   domain
5   !!======================================================================
6   !! History :  OPA  ! 1998-07 (Y.Drillet, CLIPPER)  Original code
7   !!----------------------------------------------------------------------
8#if   defined key_floats   ||   defined key_esopa
9   !!----------------------------------------------------------------------
10   !!   'key_floats'                                     float trajectories
11   !!----------------------------------------------------------------------
12   !!   flo_dom        : initialization of floats
13   !!   findmesh       : compute index of position
14   !!   dstnce         : compute distance between face mesh and floats
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers
17   USE dom_oce         ! ocean space and time domain
18   USE flo_oce         ! ocean drifting floats
19   USE in_out_manager  ! I/O manager
20   USE lib_mpp         ! distribued memory computing library
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   flo_dom    ! routine called by floats.F90
26
27   !! * Control permutation of array indices
28#  include "oce_ftrans.h90"
29#  include "dom_oce_ftrans.h90"
30#  include "flo_oce_ftrans.h90"
31
32   !! * Substitutions
33#  include "domzgr_substitute.h90"
34   !!----------------------------------------------------------------------
35   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
36   !! $Id$
37   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39CONTAINS
40
41   SUBROUTINE flo_dom
42      !! ---------------------------------------------------------------------
43      !!                  ***  ROUTINE flo_dom  ***
44      !!                 
45      !!  ** Purpose :   Initialisation of floats
46      !!
47      !!  ** Method  :   We put the floats  in the domain with the latitude,
48      !!               the longitude (degree) and the depth (m).
49      !!----------------------------------------------------------------------     
50      LOGICAL  ::   llinmesh
51      INTEGER  ::   ji, jj, jk   ! DO loop index on 3 directions
52      INTEGER  ::   jfl, jfl1    ! number of floats   
53      INTEGER  ::   inum         ! logical unit for file read
54      INTEGER, DIMENSION(jpnfl) ::   iimfl, ijmfl, ikmfl       ! index mesh of floats
55      INTEGER, DIMENSION(jpnfl) ::   idomfl,  ivtest, ihtest   !   -             -
56      REAL(wp) ::   zdxab, zdyad
57      REAL(wp), DIMENSION(jpnnewflo+1)  :: zgifl, zgjfl,  zgkfl
58      !!---------------------------------------------------------------------
59     
60      ! Initialisation with the geographical position or restart
61     
62      IF(lwp) WRITE(numout,*) 'flo_dom : compute initial position of floats'
63      IF(lwp) WRITE(numout,*) '~~~~~~~~'
64      IF(lwp) WRITE(numout,*) '           jpnfl = ',jpnfl
65     
66      IF(ln_rstflo) THEN
67         IF(lwp) WRITE(numout,*) '        float restart file read'
68         
69         ! open the restart file
70         CALL ctl_opn( inum, 'restart_float', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
71
72         ! read of the restart file
73         READ(inum) ( tpifl  (jfl), jfl=1, jpnrstflo),   & 
74                        ( tpjfl  (jfl), jfl=1, jpnrstflo),   &
75                        ( tpkfl  (jfl), jfl=1, jpnrstflo),   &
76                        ( nisobfl(jfl), jfl=1, jpnrstflo),   &
77                        ( ngrpfl (jfl), jfl=1, jpnrstflo)   
78         CLOSE(inum)
79
80         ! if we want a  surface drift  ( like PROVOR floats )
81         IF( ln_argo ) THEN
82            DO jfl = 1, jpnrstflo
83               nisobfl(jfl) = 0
84            END DO
85         ENDIF
86
87         IF(lwp) WRITE(numout,*)' flo_dom: END of florstlec'
88         
89         ! It is possible to add new floats.         
90         IF(lwp) WRITE(numout,*)' flo_dom:jpnfl jpnrstflo ',jpnfl,jpnrstflo
91         IF( jpnfl > jpnrstflo ) THEN
92            ! open the init file
93            CALL ctl_opn( inum, 'init_float', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
94            DO jfl = jpnrstflo+1, jpnfl
95               READ(inum,*) flxx(jfl),flyy(jfl),flzz(jfl), nisobfl(jfl),ngrpfl(jfl),jfl1
96            END DO
97            CLOSE(inum)
98            IF(lwp) WRITE(numout,*)' flodom: END reading init_float file'
99           
100            ! Test to find the grid point coordonate with the geographical position           
101            DO jfl = jpnrstflo+1, jpnfl
102               ihtest(jfl) = 0
103               ivtest(jfl) = 0
104               ikmfl(jfl) = 0
105# if   defined key_mpp_mpi
106               DO ji = MAX(nldi,2), nlei
107                  DO jj = MAX(nldj,2), nlej   ! NO vector opt.
108# else
109               DO ji = 2, jpi
110                  DO jj = 2, jpj   ! NO vector opt.
111# endif                     
112                     ! For each float we find the indexes of the mesh                     
113                     CALL findmesh(glamf(ji-1,jj-1),gphif(ji-1,jj-1),   &
114                                   glamf(ji-1,jj  ),gphif(ji-1,jj  ),   &
115                                   glamf(ji  ,jj  ),gphif(ji  ,jj  ),   &
116                                   glamf(ji  ,jj-1),gphif(ji  ,jj-1),   &
117                                   flxx(jfl)       ,flyy(jfl)       ,   &
118                                   glamt(ji  ,jj  ),gphit(ji  ,jj  ), llinmesh)
119                     IF(llinmesh) THEN
120                        iimfl(jfl) = ji
121                        ijmfl(jfl) = jj
122                        ihtest(jfl) = ihtest(jfl)+1
123                        DO jk = 1, jpk-1
124                           IF( (fsdepw(ji,jj,jk) <= flzz(jfl)) .AND. (fsdepw(ji,jj,jk+1) > flzz(jfl)) ) THEN
125                              ikmfl(jfl) = jk
126                              ivtest(jfl) = ivtest(jfl) + 1
127                           ENDIF
128                        END DO
129                     ENDIF
130                  END DO
131               END DO
132               IF(lwp) WRITE(numout,*)'   flo_dom: END findmesh'
133               
134               ! If the float is in a mesh computed by an other processor we put iimfl=ijmfl=-1               
135               IF( ihtest(jfl) ==  0 ) THEN
136                  iimfl(jfl) = -1
137                  ijmfl(jfl) = -1
138               ENDIF
139            END DO
140           
141            ! A zero in the sum of the arrays "ihtest" and "ivtest"             
142# if   defined key_mpp_mpi
143            CALL mpp_sum(ihtest,jpnfl)
144            CALL mpp_sum(ivtest,jpnfl)
145# endif
146            DO jfl = jpnrstflo+1, jpnfl
147               IF( (ihtest(jfl) > 1 ) .OR. ( ivtest(jfl) > 1) ) THEN
148                  IF(lwp) WRITE(numout,*) 'THE FLOAT',jfl,' IS NOT IN ONLY ONE MESH'
149                  STOP
150               ENDIF
151               IF( (ihtest(jfl) == 0) ) THEN
152                  IF(lwp) WRITE(numout,*)'THE FLOAT',jfl,' IS IN NO MESH'
153                  STOP
154               ENDIF
155            END DO
156           
157            ! We compute the distance between the float and the face of the mesh           
158            DO jfl = jpnrstflo+1, jpnfl               
159               ! Made only if the float is in the domain of the processor             
160               IF( (iimfl(jfl) >= 0) .AND. (ijmfl(jfl) >= 0) ) THEN
161                 
162                  ! TEST TO KNOW IF THE FLOAT IS NOT INITIALISED IN THE COAST
163                 
164                  idomfl(jfl) = 0
165                  IF( tmask(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)) == 0. ) idomfl(jfl) = 1
166                                           
167                  ! Computation of the distance between the float and the faces of the mesh
168                  !            zdxab
169                  !             .
170                  !        B----.---------C
171                  !        |    .         |
172                  !        |<------>flo   |
173                  !        |        ^     |
174                  !        |        |.....|....zdyad
175                  !        |        |     |
176                  !        A--------|-----D
177                  !
178             
179                  zdxab = dstnce( flxx(jfl), flyy(jfl), glamf(iimfl(jfl)-1,ijmfl(jfl)-1), flyy(jfl) )
180                  zdyad = dstnce( flxx(jfl), flyy(jfl), flxx(jfl), gphif(iimfl(jfl)-1,ijmfl(jfl)-1) )
181                 
182                  ! Translation of this distances (in meter) in indexes
183                 
184                  zgifl(jfl-jpnrstflo)= (iimfl(jfl)-0.5) + zdxab/e1u(iimfl(jfl)-1,ijmfl(jfl)) + (mig(1)-jpizoom)
185                  zgjfl(jfl-jpnrstflo)= (ijmfl(jfl)-0.5) + zdyad/e2v(iimfl(jfl),ijmfl(jfl)-1) + (mjg(1)-jpjzoom)
186                  zgkfl(jfl-jpnrstflo) = (( fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1) - flzz(jfl) )* ikmfl(jfl))   &
187                     &                 / (  fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1)                              &
188                     &                    - fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl) ) )                             &
189                     &                 + (( flzz(jfl)-fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)) ) *(ikmfl(jfl)+1))   &
190                     &                 / (  fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1)                              &
191                     &                    - fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)) )
192               ELSE
193                  zgifl(jfl-jpnrstflo) = 0.e0
194                  zgjfl(jfl-jpnrstflo) = 0.e0
195                  zgkfl(jfl-jpnrstflo) = 0.e0
196               ENDIF
197            END DO
198           
199            ! The sum of all the arrays zgifl, zgjfl, zgkfl give 3 arrays with the positions of all the floats.
200            IF( lk_mpp )   THEN
201               CALL mpp_sum( zgjfl, jpnnewflo )   ! sums over the global domain
202               CALL mpp_sum( zgkfl, jpnnewflo )
203               IF(lwp) WRITE(numout,*) (zgifl(jfl),jfl=1,jpnnewflo)
204               IF(lwp) WRITE(numout,*) (zgjfl(jfl),jfl=1,jpnnewflo)
205               IF(lwp) WRITE(numout,*) (zgkfl(jfl),jfl=1,jpnnewflo) 
206            ENDIF
207           
208            DO jfl = jpnrstflo+1, jpnfl
209               tpifl(jfl) = zgifl(jfl-jpnrstflo)
210               tpjfl(jfl) = zgjfl(jfl-jpnrstflo)
211               tpkfl(jfl) = zgkfl(jfl-jpnrstflo)
212            END DO
213         ENDIF
214      ELSE
215         IF(lwp) WRITE(numout,*) '                     init_float read '
216         
217         ! First initialisation of floats
218         ! the initials positions of floats are written in a file
219         ! with a variable to know if it is a isobar float a number
220         ! to identified who want the trajectories of this float and
221         ! an index for the number of the float         
222         ! open the init file
223         CALL ctl_opn( inum, 'init_float', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp )
224         READ(inum) (flxx(jfl)   , jfl=1, jpnfl),   &
225                    (flyy(jfl)   , jfl=1, jpnfl),   &
226                    (flzz(jfl)   , jfl=1, jpnfl),   &
227                    (nisobfl(jfl), jfl=1, jpnfl),   &
228                    (ngrpfl(jfl) , jfl=1, jpnfl)
229         CLOSE(inum)
230           
231         ! Test to find the grid point coordonate with the geographical position         
232         DO jfl = 1, jpnfl
233            ihtest(jfl) = 0
234            ivtest(jfl) = 0
235            ikmfl(jfl) = 0
236# if   defined key_mpp_mpi
237            DO ji = MAX(nldi,2), nlei
238               DO jj = MAX(nldj,2), nlej   ! NO vector opt.
239# else
240            DO ji = 2, jpi
241               DO jj = 2, jpj   ! NO vector opt.
242# endif                 
243                  ! for each float we find the indexes of the mesh
244                 
245                  CALL findmesh(glamf(ji-1,jj-1),gphif(ji-1,jj-1),   &
246                                glamf(ji-1,jj  ),gphif(ji-1,jj  ),   &
247                                glamf(ji  ,jj  ),gphif(ji  ,jj  ),   &
248                                glamf(ji  ,jj-1),gphif(ji  ,jj-1),   &
249                                flxx(jfl)       ,flyy(jfl)       ,   &
250                                glamt(ji  ,jj  ),gphit(ji  ,jj  ), llinmesh)
251                  IF(llinmesh) THEN
252                     iimfl(jfl)  = ji
253                     ijmfl(jfl)  = jj
254                     ihtest(jfl) = ihtest(jfl)+1
255                     DO jk = 1, jpk-1
256                        IF( (fsdepw(ji,jj,jk) <= flzz(jfl)) .AND. (fsdepw(ji,jj,jk+1) >  flzz(jfl)) ) THEN
257                           ikmfl(jfl)  = jk
258                           ivtest(jfl) = ivtest(jfl) + 1
259                        ENDIF
260                     END DO
261                  ENDIF
262               END DO
263            END DO
264           
265            ! If the float is in a mesh computed by an other processor we put iimfl=ijmfl=-1           
266            IF( ihtest(jfl) == 0 ) THEN
267               iimfl(jfl) = -1
268               ijmfl(jfl) = -1
269            ENDIF
270         END DO
271         
272         ! A zero in the sum of the arrays "ihtest" and "ivtest"         
273         IF( lk_mpp )   CALL mpp_sum(ihtest,jpnfl)   ! sums over the global domain
274         IF( lk_mpp )   CALL mpp_sum(ivtest,jpnfl)
275
276         DO jfl = 1, jpnfl
277            IF( (ihtest(jfl) > 1 ) .OR. ( ivtest(jfl) > 1 )) THEN
278               IF(lwp) WRITE(numout,*) 'THE FLOAT',jfl,' IS NOT IN ONLY ONE MESH'
279            ENDIF
280            IF( ihtest(jfl) == 0 ) THEN
281               IF(lwp) WRITE(numout,*)'THE FLOAT',jfl,' IS IN NO MESH'
282            ENDIF
283         END DO
284       
285         ! We compute the distance between the float and the face of  the mesh         
286         DO jfl = 1, jpnfl
287            ! Made only if the float is in the domain of the processor
288            IF( (iimfl(jfl) >= 0 ) .AND. ( ijmfl(jfl) >= 0 ) ) THEN
289               
290               ! TEST TO KNOW IF THE FLOAT IS NOT INITIALISED IN THE COAST
291               
292               idomfl(jfl) = 0
293               IF( tmask(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)) == 0. ) idomfl(jfl)=1
294               
295               ! Computation of the distance between the float
296               ! and the faces of the mesh
297               !            zdxab
298               !             .
299               !        B----.---------C
300               !        |    .         |
301               !        |<------>flo   |
302               !        |        ^     |
303               !        |        |.....|....zdyad
304               !        |        |     |
305               !        A--------|-----D
306               
307               zdxab = dstnce(flxx(jfl),flyy(jfl),glamf(iimfl(jfl)-1,ijmfl(jfl)-1),flyy(jfl))               
308               zdyad = dstnce(flxx(jfl),flyy(jfl),flxx(jfl),gphif(iimfl(jfl)-1,ijmfl(jfl)-1))
309               
310               ! Translation of this distances (in meter) in indexes
311               
312               tpifl(jfl) = (iimfl(jfl)-0.5)+zdxab/ e1u(iimfl(jfl)-1,ijmfl(jfl))+(mig(1)-jpizoom)
313               tpjfl(jfl) = (ijmfl(jfl)-0.5)+zdyad/ e2v(iimfl(jfl),ijmfl(jfl)-1)+(mjg(1)-jpjzoom)
314               tpkfl(jfl) = (fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1) - flzz(jfl))*(ikmfl(jfl))                     &
315                          / (fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1) - fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)))   &
316                          + (flzz(jfl) - fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)))*(ikmfl(jfl)+1)                     &
317                          / (fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)+1) - fsdepw(iimfl(jfl),ijmfl(jfl),ikmfl(jfl)))
318            ELSE
319               tpifl (jfl) = 0.e0
320               tpjfl (jfl) = 0.e0
321               tpkfl (jfl) = 0.e0
322               idomfl(jfl) = 0
323            ENDIF
324         END DO
325         
326         ! The sum of all the arrays tpifl, tpjfl, tpkfl give 3 arrays with the positions of all the floats.
327         IF( lk_mpp )   CALL mpp_sum( tpifl , jpnfl )   ! sums over the global domain
328         IF( lk_mpp )   CALL mpp_sum( tpjfl , jpnfl )
329         IF( lk_mpp )   CALL mpp_sum( tpkfl , jpnfl )
330         IF( lk_mpp )   CALL mpp_sum( idomfl, jpnfl )
331      ENDIF
332           
333      ! Print the initial positions of the floats
334      IF( .NOT. ln_rstflo ) THEN 
335         ! WARNING : initial position not in the sea         
336         DO jfl = 1, jpnfl
337            IF( idomfl(jfl) == 1 ) THEN
338               IF(lwp) WRITE(numout,*)'*****************************'
339               IF(lwp) WRITE(numout,*)'!!!!!!!  WARNING   !!!!!!!!!!'
340               IF(lwp) WRITE(numout,*)'*****************************'
341               IF(lwp) WRITE(numout,*)'The float number',jfl,'is out of the sea.'
342               IF(lwp) WRITE(numout,*)'geographical position',flxx(jfl),flyy(jfl),flzz(jfl)
343               IF(lwp) WRITE(numout,*)'index position',tpifl(jfl),tpjfl(jfl),tpkfl(jfl)
344            ENDIF
345         END DO
346      ENDIF
347
348   END SUBROUTINE flo_dom
349
350
351   SUBROUTINE findmesh( pax, pay, pbx, pby,   &
352                        pcx, pcy, pdx, pdy,   &
353                        px  ,py  ,ptx, pty, ldinmesh )
354      !! -------------------------------------------------------------
355      !!                ***  ROUTINE findmesh  ***
356      !!     
357      !! ** Purpose :   Find the index of mesh for the point spx spy
358      !!
359      !! ** Method  :
360      !!----------------------------------------------------------------------
361      REAL(wp) ::   &
362         pax, pay, pbx, pby,    &     ! ???
363         pcx, pcy, pdx, pdy,    &     ! ???
364         px, py,                &     ! longitude and latitude
365         ptx, pty                     ! ???
366      LOGICAL ::  ldinmesh            ! ???
367      !!
368      REAL(wp) ::   zabt, zbct, zcdt, zdat, zabpt, zbcpt, zcdpt, zdapt
369      !!---------------------------------------------------------------------
370      !! Statement function
371      REAL(wp) ::   fsline
372      REAL(wp) ::   psax, psay, psbx, psby, psx, psy
373      fsline( psax, psay, psbx, psby, psx, psy ) = psy  * ( psbx - psax )   &
374         &                                       - psx  * ( psby - psay )   &
375         &                                       + psax *   psby - psay * psbx
376      !!---------------------------------------------------------------------
377     
378      ! 4 semi plane defined by the 4 points and including the T point
379      zabt = fsline(pax,pay,pbx,pby,ptx,pty)
380      zbct = fsline(pbx,pby,pcx,pcy,ptx,pty)
381      zcdt = fsline(pcx,pcy,pdx,pdy,ptx,pty)
382      zdat = fsline(pdx,pdy,pax,pay,ptx,pty)
383     
384      ! 4 semi plane defined by the 4 points and including the extrememity
385      zabpt = fsline(pax,pay,pbx,pby,px,py)
386      zbcpt = fsline(pbx,pby,pcx,pcy,px,py)
387      zcdpt = fsline(pcx,pcy,pdx,pdy,px,py)
388      zdapt = fsline(pdx,pdy,pax,pay,px,py)
389       
390      ! We compare the semi plane T with the semi plane including the point
391      ! to know if it is in this  mesh.
392      ! For numerical reasons it is possible that for a point which is on
393      ! the line we don't have exactly zero with fsline function. We want
394      ! that a point can't be in 2 mesh in the same time, so we put the
395      ! coefficient to zero if it is smaller than 1.E-12
396     
397      IF( ABS(zabpt) <= 1.E-12 ) zabpt = 0.
398      IF( ABS(zbcpt) <= 1.E-12 ) zbcpt = 0.
399      IF( ABS(zcdpt) <= 1.E-12 ) zcdpt = 0.
400      IF( ABS(zdapt) <= 1.E-12 ) zdapt = 0.
401      IF( (zabt*zabpt >  0.) .AND. (zbct*zbcpt >= 0. ) .AND. ( zcdt*zcdpt >= 0. ) .AND. ( zdat*zdapt > 0. )   &
402         .AND. ( px <= MAX(pcx,pdx) ) .AND. ( px >= MIN(pax,pbx) )    &
403         .AND. ( py <= MAX(pby,pcy) ) .AND. ( py >= MIN(pay,pdy) ) ) THEN
404         ldinmesh=.TRUE.
405      ELSE
406         ldinmesh=.FALSE.
407      ENDIF
408      !
409   END SUBROUTINE findmesh
410
411
412   FUNCTION dstnce( pla1, phi1, pla2, phi2 )
413      !! -------------------------------------------------------------
414      !!                 ***  Function dstnce  ***
415      !!         
416      !! ** Purpose :   returns distance (in m) between two geographical
417      !!                points
418      !! ** Method  :
419      !!----------------------------------------------------------------------
420      REAL(wp), INTENT(in) ::   pla1, phi1, pla2, phi2   ! ???
421      !!
422      REAL(wp) ::   dly1, dly2, dlx1, dlx2, dlx, dls, dld, dpi
423      REAL(wp) ::   dstnce
424      !!---------------------------------------------------------------------
425      !
426      dpi  = 2.* ASIN(1.)
427      dls  = dpi / 180.
428      dly1 = phi1 * dls
429      dly2 = phi2 * dls
430      dlx1 = pla1 * dls
431      dlx2 = pla2 * dls
432      !
433      dlx = SIN(dly1) * SIN(dly2) + COS(dly1) * COS(dly2) * COS(dlx2-dlx1)
434      !
435      IF( ABS(dlx) > 1.0 ) dlx = 1.0
436      !
437      dld = ATAN(DSQRT( ( 1-dlx )/( 1+dlx ) )) * 222.24 / dls
438      dstnce = dld * 1000.
439      !
440   END FUNCTION dstnce
441
442#  else
443   !!----------------------------------------------------------------------
444   !!   Default option                                         Empty module
445   !!----------------------------------------------------------------------
446CONTAINS
447   SUBROUTINE flo_dom                 ! Empty routine
448   END SUBROUTINE flo_dom
449#endif
450
451   !!======================================================================
452END MODULE flodom
Note: See TracBrowser for help on using the repository browser.