floats.F90 7.4 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155
  1. MODULE 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 florst ! float restart (flo_rst routine)
  22. USE flo4rk ! Trajectories, Runge Kutta scheme (flo_4rk routine)
  23. USE floblk ! Trajectories, Blanke scheme (flo_blk routine)
  24. USE in_out_manager ! I/O manager
  25. USE timing ! preformance summary
  26. IMPLICIT NONE
  27. PRIVATE
  28. PUBLIC flo_stp ! routine called by step.F90
  29. PUBLIC flo_init ! routine called by opa.F90
  30. !!----------------------------------------------------------------------
  31. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  32. !! $Id: floats.F90 4624 2014-04-28 12:09:03Z acc $
  33. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  34. !!----------------------------------------------------------------------
  35. CONTAINS
  36. SUBROUTINE flo_stp( kt )
  37. !!----------------------------------------------------------------------
  38. !! *** ROUTINE flo_stp ***
  39. !!
  40. !! ** Purpose : Compute the geographical position (lat., long., depth)
  41. !! of each float at each time step with one of the algorithm.
  42. !!
  43. !! ** Method : The position of a float is computed with Bruno Blanke
  44. !! algorithm by default and with a 4th order Runge-Kutta scheme
  45. !! if ln_flork4 =T
  46. !!----------------------------------------------------------------------
  47. INTEGER, INTENT( in ) :: kt ! ocean time step
  48. !!----------------------------------------------------------------------
  49. !
  50. IF( nn_timing == 1 ) CALL timing_start('flo_stp')
  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. CALL flo_wri( kt ) ! trajectories ouput
  59. !
  60. CALL flo_rst( kt ) ! trajectories restart
  61. !
  62. wb(:,:,:) = wn(:,:,:) ! Save the old vertical velocity field
  63. !
  64. IF( nn_timing == 1 ) CALL timing_stop('flo_stp')
  65. !
  66. END SUBROUTINE flo_stp
  67. SUBROUTINE flo_init
  68. !!----------------------------------------------------------------
  69. !! *** ROUTINE flo_init ***
  70. !!
  71. !! ** Purpose : Read the namelist of floats
  72. !!----------------------------------------------------------------------
  73. INTEGER :: jfl
  74. INTEGER :: ios ! Local integer output status for namelist read
  75. !
  76. NAMELIST/namflo/ jpnfl, jpnnewflo, ln_rstflo, nn_writefl, nn_stockfl, ln_argo, ln_flork4, ln_ariane, ln_flo_ascii
  77. !!---------------------------------------------------------------------
  78. !
  79. IF( nn_timing == 1 ) CALL timing_start('flo_init')
  80. !
  81. IF(lwp) WRITE(numout,*)
  82. IF(lwp) WRITE(numout,*) 'flo_stp : call floats routine '
  83. IF(lwp) WRITE(numout,*) '~~~~~~~'
  84. REWIND( numnam_ref ) ! Namelist namflo in reference namelist : Floats
  85. READ ( numnam_ref, namflo, IOSTAT = ios, ERR = 901)
  86. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namflo in reference namelist', lwp )
  87. REWIND( numnam_cfg ) ! Namelist namflo in configuration namelist : Floats
  88. READ ( numnam_cfg, namflo, IOSTAT = ios, ERR = 902 )
  89. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namflo in configuration namelist', lwp )
  90. IF(lwm) WRITE ( numond, namflo )
  91. !
  92. IF(lwp) THEN ! control print
  93. WRITE(numout,*)
  94. WRITE(numout,*) ' Namelist floats :'
  95. WRITE(numout,*) ' number of floats jpnfl = ', jpnfl
  96. WRITE(numout,*) ' number of new floats jpnflnewflo = ', jpnnewflo
  97. WRITE(numout,*) ' restart ln_rstflo = ', ln_rstflo
  98. WRITE(numout,*) ' frequency of float output file nn_writefl = ', nn_writefl
  99. WRITE(numout,*) ' frequency of float restart file nn_stockfl = ', nn_stockfl
  100. WRITE(numout,*) ' Argo type floats ln_argo = ', ln_argo
  101. WRITE(numout,*) ' Computation of T trajectories ln_flork4 = ', ln_flork4
  102. WRITE(numout,*) ' Use of ariane convention ln_ariane = ', ln_ariane
  103. WRITE(numout,*) ' ascii output (T) or netcdf output (F) ln_flo_ascii = ', ln_flo_ascii
  104. ENDIF
  105. !
  106. ! ! allocate floats arrays
  107. IF( flo_oce_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'flo_init : unable to allocate arrays' )
  108. !
  109. ! ! allocate flodom arrays
  110. IF( flo_dom_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'flo_dom : unable to allocate arrays' )
  111. !
  112. ! ! allocate flowri arrays
  113. IF( flo_wri_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'flo_wri : unable to allocate arrays' )
  114. !
  115. ! ! allocate florst arrays
  116. IF( flo_rst_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'flo_rst : unable to allocate arrays' )
  117. !
  118. !memory allocation
  119. jpnrstflo = jpnfl-jpnnewflo
  120. !vertical axe for netcdf IOM ouput
  121. DO jfl=1,jpnfl ; nfloat(jfl)=jfl ; ENDDO
  122. !
  123. CALL flo_dom ! compute/read initial position of floats
  124. wb(:,:,:) = wn(:,:,:) ! set wb for computation of floats trajectories at the first time step
  125. !
  126. IF( nn_timing == 1 ) CALL timing_stop('flo_init')
  127. !
  128. END SUBROUTINE flo_init
  129. # else
  130. !!----------------------------------------------------------------------
  131. !! Default option : Empty module
  132. !!----------------------------------------------------------------------
  133. CONTAINS
  134. SUBROUTINE flo_stp( kt ) ! Empty routine
  135. WRITE(*,*) 'flo_stp: You should not have seen this print! error?', kt
  136. END SUBROUTINE flo_stp
  137. SUBROUTINE flo_init ! Empty routine
  138. END SUBROUTINE flo_init
  139. #endif
  140. !!======================================================================
  141. END MODULE floats