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/UKMO/dev_r5021_nn_etau_revision/NEMOGCM/NEMO/OPA_SRC/FLO – NEMO

source: branches/UKMO/dev_r5021_nn_etau_revision/NEMOGCM/NEMO/OPA_SRC/FLO/florst.F90 @ 5448

Last change on this file since 5448 was 5448, checked in by davestorkey, 9 years ago

Clear SVN keywords from UKMO/dev_r5021_nn_etau_revision branch.

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