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 NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/FLO – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/FLO/floats.F90 @ 11960

Last change on this file since 11960 was 11960, checked in by acc, 4 years ago

Branch 2019/dev_r11943_MERGE_2019. Merge in changes from 2019/dev_r11613_ENHANCE-04_namelists_as_internalfiles. (svn merge -r 11614:11954). Resolved tree conflicts and one actual conflict. Sette tested(these changes alter the ext/AGRIF reference; remember to update). See ticket #2341

  • Property svn:keywords set to Id
File size: 6.8 KB
RevLine 
[3]1MODULE floats
2   !!======================================================================
3   !!                       ***  MODULE  floats  ***
4   !! Ocean floats : floats
5   !!======================================================================
[1601]6   !! History :  OPA  !          (CLIPPER)   original Code
7   !!   NEMO     1.0  ! 2002-06  (A. Bozec)  F90, Free form and module
8   !!----------------------------------------------------------------------
[11536]9   !!
[3]10   !!----------------------------------------------------------------------
11   !!   flo_stp   : float trajectories computation
12   !!   flo_init  : initialization of float trajectories computation
13   !!----------------------------------------------------------------------
[2528]14   USE oce             ! ocean variables
[3]15   USE flo_oce         ! floats variables
16   USE lib_mpp         ! distributed memory computing
17   USE flodom          ! initialisation Module
18   USE flowri          ! float output                     (flo_wri routine)
[3294]19   USE florst          ! float restart                    (flo_rst routine)
[3]20   USE flo4rk          ! Trajectories, Runge Kutta scheme (flo_4rk routine)
21   USE floblk          ! Trajectories, Blanke scheme      (flo_blk routine)
[9124]22   !
[2528]23   USE in_out_manager  ! I/O manager
[3294]24   USE timing          ! preformance summary
[3]25
26   IMPLICIT NONE
27   PRIVATE 
28
[1601]29   PUBLIC   flo_stp    ! routine called by step.F90
[11536]30   PUBLIC   flo_init   ! routine called by nemogcm.F90
[1601]31
[3]32   !!----------------------------------------------------------------------
[9598]33   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
[1152]34   !! $Id$
[10068]35   !! Software governed by the CeCILL license (see ./LICENSE)
[3]36   !!----------------------------------------------------------------------
37CONTAINS
38
[11949]39   SUBROUTINE flo_stp( kt, Kbb, Kmm )
[3]40      !!----------------------------------------------------------------------
41      !!                   ***  ROUTINE flo_stp  ***
42      !!                   
43      !! ** Purpose :   Compute the geographical position (lat., long., depth)
44      !!      of each float at each time step with one of the algorithm.
45      !!
46      !! ** Method  :   The position of a float is computed with Bruno Blanke
47      !!        algorithm by default and with a 4th order Runge-Kutta scheme
48      !!        if ln_flork4 =T
49      !!----------------------------------------------------------------------
[11949]50      INTEGER, INTENT( in  ) ::   kt        ! ocean time step
51      INTEGER, INTENT( in  ) ::   Kbb, Kmm  ! ocean time level indices
[3]52      !!----------------------------------------------------------------------
[1601]53      !
[9124]54      IF( ln_timing )   CALL timing_start('flo_stp')
[3294]55      !
[11949]56      IF( ln_flork4 ) THEN   ;   CALL flo_4rk( kt, Kbb, Kmm )  ! Trajectories using a 4th order Runge Kutta scheme
57      ELSE                   ;   CALL flo_blk( kt, Kbb, Kmm )  ! Trajectories using Blanke' algorithme
[3]58      ENDIF
[1601]59      !
[16]60      IF( lk_mpp )   CALL mppsync   ! synchronization of all the processor
[1601]61      !
[11949]62      CALL flo_wri( kt, Kmm ) ! trajectories ouput
[1601]63      !
[3294]64      CALL flo_rst( kt )      ! trajectories restart
65      !
[11949]66      wb(:,:,:) = ww(:,:,:)         ! Save the old vertical velocity field
[1601]67      !
[9124]68      IF( ln_timing )   CALL timing_stop('flo_stp')
[3294]69      !
[3]70   END SUBROUTINE flo_stp
71
72
[11949]73   SUBROUTINE flo_init( Kmm )
[3]74      !!----------------------------------------------------------------
75      !!                 ***  ROUTINE flo_init  ***
76      !!                   
77      !! ** Purpose :   Read the namelist of floats
78      !!----------------------------------------------------------------------
[11949]79      INTEGER, INTENT(in) :: Kmm       ! ocean time level index
80      !
[9124]81      INTEGER ::   jfl
82      INTEGER ::   ios                 ! Local integer output status for namelist read
[3294]83      !
[11536]84      NAMELIST/namflo/ ln_floats, jpnfl, jpnnewflo, ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4, ln_ariane, ln_flo_ascii
[3]85      !!---------------------------------------------------------------------
[1601]86      !
[2715]87      IF(lwp) WRITE(numout,*)
88      IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
89      IF(lwp) WRITE(numout,*) '~~~~~~~'
90
[4147]91      READ  ( numnam_ref, namflo, IOSTAT = ios, ERR = 901)
[11536]92901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namflo in reference namelist' )
[4147]93
94      READ  ( numnam_cfg, namflo, IOSTAT = ios, ERR = 902 )
[11536]95902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namflo in configuration namelist' )
[4624]96      IF(lwm) WRITE ( numond, namflo )
[1601]97      !
98      IF(lwp) THEN                  ! control print
99         WRITE(numout,*)
[3]100         WRITE(numout,*) '         Namelist floats :'
[11536]101         WRITE(numout,*) '            Activate floats or not                   ln_floats    = ', ln_floats
102         WRITE(numout,*) '               number of floats                      jpnfl        = ', jpnfl
103         WRITE(numout,*) '               number of new floats                  jpnflnewflo  = ', jpnnewflo
104         WRITE(numout,*) '               restart                               ln_rstflo    = ', ln_rstflo
105         WRITE(numout,*) '               frequency of float output file        nn_writefl   = ', nn_writefl
106         WRITE(numout,*) '               frequency of float restart file       nn_stockfl   = ', nn_stockfl
107         WRITE(numout,*) '               Argo type floats                      ln_argo      = ', ln_argo
108         WRITE(numout,*) '               Computation of T trajectories         ln_flork4    = ', ln_flork4
109         WRITE(numout,*) '               Use of ariane convention              ln_ariane    = ', ln_ariane
110         WRITE(numout,*) '               ascii output (T) or netcdf output (F) ln_flo_ascii = ', ln_flo_ascii
[3294]111
[3]112      ENDIF
[1601]113      !
[11536]114      IF( ln_floats ) THEN
115         !                             ! allocate floats arrays
116         IF( flo_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_init : unable to allocate arrays' )
117         !
118         !                             ! allocate flodom arrays
119         IF( flo_dom_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_dom : unable to allocate arrays' )
120         !
121         !                             ! allocate flowri arrays
122         IF( flo_wri_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_wri : unable to allocate arrays' )
123         !
124         !                             ! allocate florst arrays
125         IF( flo_rst_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'flo_rst : unable to allocate arrays' )
126         !
127         jpnrstflo = jpnfl-jpnnewflo   ! memory allocation
128         !
129         DO jfl = 1, jpnfl             ! vertical axe for netcdf IOM ouput
130            nfloat(jfl) = jfl 
131         END DO
132         !
[11949]133         CALL flo_dom( Kmm )           ! compute/read initial position of floats
[11536]134         !
[11949]135         wb(:,:,:) = ww(:,:,:)         ! set wb for computation of floats trajectories at the first time step
[11536]136         !
137      ENDIF
[3]138   END SUBROUTINE flo_init
139
140   !!======================================================================
141 END MODULE floats
Note: See TracBrowser for help on using the repository browser.