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

source: trunk/NEMO/OPA_SRC/FLO/flodom.F90 @ 719

Last change on this file since 719 was 719, checked in by ctlod, 17 years ago

get back to the nemo_v2_3 version for trunk

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