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

source: branches/2011/dev_r2802_MERCATOR9_floats/NEMOGCM/NEMO/OPA_SRC/FLO/florst.F90 @ 2843

Last change on this file since 2843 was 2843, checked in by cbricaud, 13 years ago

comestic changes for flodom.F90, add call to flo_rst in floats.F90, minor correction in flo_rst

File size: 4.9 KB
Line 
1MODULE florst
2   !!======================================================================
3   !!                       ***  MODULE  florst  ***
4   !! blablabla: floteur....
5   !!======================================================================
6   !!  History :
7   !!    8.0  !  99-09  (Y. Drillet)    : Original code
8   !!         !  00-06  (J.-M. Molines) : Profiling floats for CLS
9   !!    8.5  !  02-10  (A. Bozec)  F90 : Free form and module
10   !!    3.2  !  10-08  (slaw, cbricaud): netcdf outputs and others
11   !!----------------------------------------------------------------------
12#if   defined key_floats   ||   defined key_esopa
13   !!----------------------------------------------------------------------
14   !!   'key_floats'                                     float trajectories
15   !!----------------------------------------------------------------------
16
17   !! * Modules used
18   USE flo_oce         ! ocean drifting floats
19   !USE oce             ! ocean dynamics and tracers
20   USE dom_oce         ! ocean space and time domain
21   USE lib_mpp         ! distribued memory computing library
22   USE in_out_manager  ! I/O manager
23   !USE phycst          ! physic constants
24   !USE dianam          ! build name of file (routine)
25   !USE ioipsl
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC flo_rst      ! routine called by floats.F90
31
32   !INTEGER :: jfl      ! number of floats
33   !INTEGER :: numfl   ! logical unit for floats netcdf output
34
35   !! * Substitutions
36#  include "domzgr_substitute.h90"
37   !!----------------------------------------------------------------------
38   !! NEMO/OPA 3.2 , LODYC-IPSL  (2009)
39   !! $Header:
40   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
41   !!----------------------------------------------------------------------
42
43CONTAINS
44
45   SUBROUTINE flo_rst( kt )
46      !!---------------------------------------------------------------------
47      !!                  ***  ROUTINE flo_wri ***
48      !!             
49      !! ** Purpose : 
50      !!             
51      !!   
52      !!     
53      !! ** Method  :   The frequency of  ??? is nwritefl
54      !!     
55      !!----------------------------------------------------------------------
56      !! * Arguments
57      INTEGER  :: kt                            ! time step
58
59      !! * Local declarations
60      CHARACTER (len=80)       :: clname             ! restart filename
61      INTEGER                  :: ic , jc , jpn ,jfl ! temporary integer
62      INTEGER                  :: inum               ! temporary logical unit for restart file
63      INTEGER,DIMENSION(jpnij) :: iproc              ! temporary logical
64      !!----------------------------------------------------------------------
65
66      IF(  ( MOD(kt,nn_stockfl) == 0 ) .OR. ( kt == nitend )  )THEN     
67
68         IF(lwp) THEN
69            WRITE(numout,*)
70            WRITE(numout,*) 'flo_rst : write in  restart_float file '
71            WRITE(numout,*) '~~~~~~~    '
72         ENDIF
73
74         ! file is opened and closed every time it is used.
75
76         clname = 'restart.float.'
77         ic = 1
78         DO jc = 1, 16
79            IF( cexper(jc:jc) /= ' ' ) ic = jc
80         END DO
81         clname = clname(1:14)//cexper(1:ic)
82         ic = 1
83         DO jc = 1, 48
84            IF( clname(jc:jc) /= ' ' ) ic = jc
85         END DO
86
87         CALL ctl_opn( inum, clname, 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. )
88         REWIND inum
89         !
90         DO jpn = 1, jpnij
91            iproc(jpn) = 0
92         END DO
93         !
94         IF(lwp) THEN
95            REWIND(inum)
96            WRITE (inum,*) tpifl,tpjfl,tpkfl,nisobfl,ngrpfl
97            CLOSE (inum)
98         ENDIF
99         !
100         ! Compute the number of trajectories for each processor
101         !
102         IF( lk_mpp ) THEN
103            DO jfl = 1, jpnfl
104               IF( (INT(tpifl(jfl)) >= (mig(nldi)-jpizoom+1)) .AND.   &
105                  &(INT(tpifl(jfl)) <= (mig(nlei)-jpizoom+1)) .AND.   &
106                  &(INT(tpjfl(jfl)) >= (mjg(nldj)-jpjzoom+1)) .AND.   &
107                  &(INT(tpjfl(jfl)) <= (mjg(nlej)-jpjzoom+1)) ) THEN
108                  iproc(narea) = iproc(narea)+1
109               ENDIF
110            END DO
111            CALL mpp_sum( iproc, jpnij )
112            !
113            IF(lwp) THEN
114               WRITE(numout,*) 'DATE',adatrj
115               DO jpn = 1, jpnij
116                  IF( iproc(jpn) /= 0 ) THEN
117                     WRITE(numout,*)'PROCESSOR',jpn-1,'compute',iproc(jpn), 'trajectories.'
118                  ENDIF
119               END DO
120            ENDIF
121         ENDIF
122
123      ENDIF
124
125   END SUBROUTINE flo_rst
126
127
128#  else
129   !!----------------------------------------------------------------------
130   !!   Default option                                         Empty module
131   !!----------------------------------------------------------------------
132CONTAINS
133   SUBROUTINE flo_rst                 ! Empty routine
134   END SUBROUTINE flo_rst
135#endif
136
137   !!=======================================================================
138END MODULE florst
Note: See TracBrowser for help on using the repository browser.