MODULE florst !!====================================================================== !! *** MODULE florst *** !! blablabla: floteur.... !!====================================================================== !! History : !! 8.0 ! 99-09 (Y. Drillet) : Original code !! ! 00-06 (J.-M. Molines) : Profiling floats for CLS !! 8.5 ! 02-10 (A. Bozec) F90 : Free form and module !! 3.2 ! 10-08 (slaw, cbricaud): netcdf outputs and others !!---------------------------------------------------------------------- #if defined key_floats || defined key_esopa !!---------------------------------------------------------------------- !! 'key_floats' float trajectories !!---------------------------------------------------------------------- !! * Modules used USE flo_oce ! ocean drifting floats !USE oce ! ocean dynamics and tracers USE dom_oce ! ocean space and time domain USE lib_mpp ! distribued memory computing library USE in_out_manager ! I/O manager !USE phycst ! physic constants !USE dianam ! build name of file (routine) !USE ioipsl IMPLICIT NONE PRIVATE PUBLIC flo_rst ! routine called by floats.F90 !INTEGER :: jfl ! number of floats !INTEGER :: numfl ! logical unit for floats netcdf output !! * Substitutions # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/OPA 3.2 , LODYC-IPSL (2009) !! $Header: !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt !!---------------------------------------------------------------------- CONTAINS SUBROUTINE flo_rst( kt ) !!--------------------------------------------------------------------- !! *** ROUTINE flo_wri *** !! !! ** Purpose : !! !! !! !! ** Method : The frequency of ??? is nwritefl !! !!---------------------------------------------------------------------- !! * Arguments INTEGER :: kt ! time step !! * Local declarations CHARACTER (len=80) :: clname ! restart filename INTEGER :: ic , jc , jpn ,jfl ! temporary integer INTEGER :: inum ! temporary logical unit for restart file INTEGER,DIMENSION(jpnij) :: iproc ! temporary logical !!---------------------------------------------------------------------- IF( ( MOD(kt,nn_stockfl) == 0 ) .OR. ( kt == nitend ) )THEN IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'flo_rst : write in restart_float file ' WRITE(numout,*) '~~~~~~~ ' ENDIF ! file is opened and closed every time it is used. clname = 'restart.float.' ic = 1 DO jc = 1, 16 IF( cexper(jc:jc) /= ' ' ) ic = jc END DO clname = clname(1:14)//cexper(1:ic) ic = 1 DO jc = 1, 48 IF( clname(jc:jc) /= ' ' ) ic = jc END DO CALL ctl_opn( inum, clname, 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, .FALSE. ) REWIND inum ! DO jpn = 1, jpnij iproc(jpn) = 0 END DO ! IF(lwp) THEN REWIND(inum) WRITE (inum,*) tpifl,tpjfl,tpkfl,nisobfl,ngrpfl CLOSE (inum) ENDIF ! ! Compute the number of trajectories for each processor ! IF( lk_mpp ) THEN DO jfl = 1, jpnfl IF( (INT(tpifl(jfl)) >= (mig(nldi)-jpizoom+1)) .AND. & &(INT(tpifl(jfl)) <= (mig(nlei)-jpizoom+1)) .AND. & &(INT(tpjfl(jfl)) >= (mjg(nldj)-jpjzoom+1)) .AND. & &(INT(tpjfl(jfl)) <= (mjg(nlej)-jpjzoom+1)) ) THEN iproc(narea) = iproc(narea)+1 ENDIF END DO CALL mpp_sum( iproc, jpnij ) ! IF(lwp) THEN WRITE(numout,*) 'DATE',adatrj DO jpn = 1, jpnij IF( iproc(jpn) /= 0 ) THEN WRITE(numout,*)'PROCESSOR',jpn-1,'compute',iproc(jpn), 'trajectories.' ENDIF END DO ENDIF ENDIF ENDIF END SUBROUTINE flo_rst # else !!---------------------------------------------------------------------- !! Default option Empty module !!---------------------------------------------------------------------- CONTAINS SUBROUTINE flo_rst ! Empty routine END SUBROUTINE flo_rst #endif !!======================================================================= END MODULE florst