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.
floats.F90 in trunk/NEMOGCM/NEMO/OPA_SRC/FLO – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/FLO/floats.F90 @ 2715

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

First attempt to put dynamic allocation on the trunk

  • Property svn:keywords set to Id
File size: 5.5 KB
Line 
1MODULE floats
2   !!======================================================================
3   !!                       ***  MODULE  floats  ***
4   !! Ocean floats : floats
5   !!======================================================================
6   !! History :  OPA  !          (CLIPPER)   original Code
7   !!   NEMO     1.0  ! 2002-06  (A. Bozec)  F90, Free form and module
8   !!----------------------------------------------------------------------
9#if   defined key_floats   ||   defined key_esopa
10   !!----------------------------------------------------------------------
11   !!   'key_floats'                                     float trajectories
12   !!----------------------------------------------------------------------
13   !!   flo_stp   : float trajectories computation
14   !!   flo_init  : initialization of float trajectories computation
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean variables
17   USE flo_oce         ! floats variables
18   USE lib_mpp         ! distributed memory computing
19   USE flodom          ! initialisation Module
20   USE flowri          ! float output                     (flo_wri routine)
21   USE flo4rk          ! Trajectories, Runge Kutta scheme (flo_4rk routine)
22   USE floblk          ! Trajectories, Blanke scheme      (flo_blk routine)
23   USE in_out_manager  ! I/O manager
24
25   IMPLICIT NONE
26   PRIVATE 
27
28   PUBLIC   flo_stp    ! routine called by step.F90
29   PUBLIC   flo_init   ! routine called by opa.F90
30
31   !!----------------------------------------------------------------------
32   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
33   !! $Id$
34   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE flo_stp( kt )
39      !!----------------------------------------------------------------------
40      !!                   ***  ROUTINE flo_stp  ***
41      !!                   
42      !! ** Purpose :   Compute the geographical position (lat., long., depth)
43      !!      of each float at each time step with one of the algorithm.
44      !!
45      !! ** Method  :   The position of a float is computed with Bruno Blanke
46      !!        algorithm by default and with a 4th order Runge-Kutta scheme
47      !!        if ln_flork4 =T
48      !!----------------------------------------------------------------------
49      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
50      !!----------------------------------------------------------------------
51      !
52      IF( ln_flork4 ) THEN   ;   CALL flo_4rk( kt )        ! Trajectories using a 4th order Runge Kutta scheme
53      ELSE                   ;   CALL flo_blk( kt )        ! Trajectories using Blanke' algorithme
54      ENDIF
55      !
56      IF( lk_mpp )   CALL mppsync   ! synchronization of all the processor
57      !
58      IF( kt == nit000 .OR. MOD( kt, nn_writefl ) == 0 )   CALL flo_wri( kt )      ! trajectories file
59      IF( kt == nitend .OR. MOD( kt, nn_stockfl ) == 0 )   CALL flo_wri( kt )      ! restart file
60      !
61      wb(:,:,:) = wn(:,:,:)         ! Save the old vertical velocity field
62      !
63   END SUBROUTINE flo_stp
64
65
66   SUBROUTINE flo_init
67      !!----------------------------------------------------------------
68      !!                 ***  ROUTINE flo_init  ***
69      !!                   
70      !! ** Purpose :   Read the namelist of floats
71      !!----------------------------------------------------------------------
72      NAMELIST/namflo/ ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4 
73      !!---------------------------------------------------------------------
74      !
75      IF(lwp) WRITE(numout,*)
76      IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
77      IF(lwp) WRITE(numout,*) '~~~~~~~'
78
79      REWIND( numnam )              ! Namelist namflo : floats
80      READ  ( numnam, namflo )
81      !
82      IF(lwp) THEN                  ! control print
83         WRITE(numout,*)
84         WRITE(numout,*) '         Namelist floats :'
85         WRITE(numout,*) '            restart                          ln_rstflo  = ', ln_rstflo
86         WRITE(numout,*) '            frequency of float output file   nn_writefl = ', nn_writefl
87         WRITE(numout,*) '            frequency of float restart file  nn_stockfl = ', nn_stockfl
88         WRITE(numout,*) '            Argo type floats                 ln_argo    = ', ln_argo
89         WRITE(numout,*) '            Computation of T trajectories    ln_flork4  = ', ln_flork4
90      ENDIF
91      !
92      !                             ! allocate floats arrays
93      IF( flo_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_init : unable to allocate arrays' )
94      !
95      !                             ! allocate flowri arrays
96      IF( flo_wri_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_wri : unable to allocate arrays' )
97      !
98      CALL flo_dom                  ! compute/read initial position of floats
99
100      wb(:,:,:) = wn(:,:,:)         ! set wb for computation of floats trajectories at the first time step
101      !
102   END SUBROUTINE flo_init
103
104#  else
105   !!----------------------------------------------------------------------
106   !!   Default option :                                       Empty module
107   !!----------------------------------------------------------------------
108CONTAINS
109   SUBROUTINE flo_stp( kt )          ! Empty routine
110      WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt
111   END SUBROUTINE flo_stp
112   SUBROUTINE flo_init          ! Empty routine
113   END SUBROUTINE flo_init
114#endif
115
116   !!======================================================================
117 END MODULE floats
Note: See TracBrowser for help on using the repository browser.