nemogcm.F90 32 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703
  1. MODULE nemogcm
  2. !!======================================================================
  3. !! *** MODULE nemogcm ***
  4. !! Off-line Ocean : passive tracer evolution, dynamics read in files
  5. !!======================================================================
  6. !! History : 3.3 ! 2010-05 (C. Ethe) Full reorganization of the off-line: phasing with the on-line
  7. !! 4.0 ! 2011-01 (C. Ethe, A. R. Porter, STFC Daresbury) dynamical allocation
  8. !!----------------------------------------------------------------------
  9. !!----------------------------------------------------------------------
  10. !! nemo_gcm : off-line: solve ocean tracer only
  11. !! nemo_init : initialization of the nemo model
  12. !! nemo_ctl : initialisation of algorithm flag
  13. !! nemo_closefile : close remaining files
  14. !!----------------------------------------------------------------------
  15. USE dom_oce ! ocean space domain variables
  16. USE oce ! dynamics and tracers variables
  17. USE c1d ! 1D configuration
  18. USE domcfg ! domain configuration (dom_cfg routine)
  19. USE domain ! domain initialization from coordinate & bathymetry (dom_init routine)
  20. USE domrea ! domain initialization from mesh_mask (dom_init routine)
  21. USE eosbn2 ! equation of state (eos bn2 routine)
  22. ! ! ocean physics
  23. USE ldftra ! lateral diffusivity setting (ldf_tra_init routine)
  24. USE ldfslp ! slopes of neutral surfaces (ldf_slp_init routine)
  25. USE traqsr ! solar radiation penetration (tra_qsr_init routine)
  26. USE trabbl ! bottom boundary layer (tra_bbl_init routine)
  27. USE zdfini ! vertical physics: initialization
  28. USE sbcmod ! surface boundary condition (sbc_init routine)
  29. USE phycst ! physical constant (par_cst routine)
  30. USE dtadyn ! Lecture and Interpolation of the dynamical fields
  31. USE trcini ! Initilization of the passive tracers
  32. USE daymod ! calendar (day routine)
  33. USE trcstp ! passive tracer time-stepping (trc_stp routine)
  34. USE dtadyn ! Lecture and interpolation of the dynamical fields
  35. ! ! I/O & MPP
  36. USE iom ! I/O library
  37. USE in_out_manager ! I/O manager
  38. USE mppini ! shared/distributed memory setting (mpp_init routine)
  39. USE lib_mpp ! distributed memory computing
  40. #if defined key_iomput
  41. USE xios
  42. #endif
  43. USE prtctl ! Print control (prt_ctl_init routine)
  44. USE timing ! Timing
  45. USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
  46. USE lbcnfd, ONLY: isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges
  47. USE trc
  48. USE trcnam
  49. USE trcrst
  50. IMPLICIT NONE
  51. PRIVATE
  52. PUBLIC nemo_gcm ! called by nemo.F90
  53. CHARACTER (len=64) :: cform_aaa="( /, 'AAAAAAAA', / ) " ! flag for output listing
  54. !!----------------------------------------------------------------------
  55. !! NEMO/OFF 3.3 , NEMO Consortium (2010)
  56. !! $Id: nemogcm.F90 7522 2017-01-02 10:06:49Z cetlod $
  57. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  58. !!----------------------------------------------------------------------
  59. CONTAINS
  60. SUBROUTINE nemo_gcm
  61. !!----------------------------------------------------------------------
  62. !! *** ROUTINE nemo_gcm ***
  63. !!
  64. !! ** Purpose : nemo solves the primitive equations on an orthogonal
  65. !! curvilinear mesh on the sphere.
  66. !!
  67. !! ** Method : - model general initialization
  68. !! - launch the time-stepping (dta_dyn and trc_stp)
  69. !! - finalize the run by closing files and communications
  70. !!
  71. !! References : Madec, Delecluse,Imbard, and Levy, 1997: internal report, IPSL.
  72. !! Madec, 2008, internal report, IPSL.
  73. !!----------------------------------------------------------------------
  74. INTEGER :: istp, indic ! time step index
  75. !!----------------------------------------------------------------------
  76. CALL nemo_init ! Initializations
  77. ! check that all process are still there... If some process have an error,
  78. ! they will never enter in step and other processes will wait until the end of the cpu time!
  79. IF( lk_mpp ) CALL mpp_max( nstop )
  80. ! !-----------------------!
  81. ! !== time stepping ==!
  82. ! !-----------------------!
  83. istp = nit000
  84. indic = 0
  85. !
  86. DO WHILE ( istp <= nitend .AND. nstop == 0 ) ! time stepping
  87. !
  88. IF( istp == nit000 ) CALL iom_init( cxios_context ) ! iom_put initialization
  89. IF( istp /= nit000 ) CALL day ( istp ) ! Calendar (day was already called at nit000 in day_init)
  90. CALL iom_setkt ( istp - nit000 + 1, cxios_context ) ! say to iom that we are at time step kstp
  91. CALL trc_rst_opn( istp ) ! Open tracer ! restart file
  92. CALL dta_dyn ( istp ) ! Interpolation of the dynamical fields
  93. CALL trc_stp ( istp, indic ) ! time-stepping
  94. IF( lk_vvl ) CALL dta_dyn_swp( istp ) ! swap of sea surface height and vertical scale factors
  95. CALL stp_ctl ( istp, indic ) ! Time loop: control and print
  96. #if defined key_iomput
  97. IF( istp == nitend .OR. indic < 0 ) CALL iom_context_finalize( cxios_context ) ! needed for XIOS+AGRIF
  98. #endif
  99. istp = istp + 1
  100. IF( lk_mpp ) CALL mpp_max( nstop )
  101. END DO
  102. ! !------------------------!
  103. ! !== finalize the run ==!
  104. ! !------------------------!
  105. IF(lwp) WRITE(numout,cform_aaa) ! Flag AAAAAAA
  106. IF( nstop /= 0 .AND. lwp ) THEN ! error print
  107. WRITE(numout,cform_err)
  108. WRITE(numout,*) nstop, ' error have been found'
  109. ENDIF
  110. !
  111. IF( nn_timing == 1 ) CALL timing_finalize
  112. !
  113. CALL nemo_closefile
  114. !
  115. # if defined key_iomput
  116. CALL xios_finalize ! end mpp communications
  117. # else
  118. IF( lk_mpp ) CALL mppstop ! end mpp communications
  119. # endif
  120. !
  121. END SUBROUTINE nemo_gcm
  122. SUBROUTINE nemo_init
  123. !!----------------------------------------------------------------------
  124. !! *** ROUTINE nemo_init ***
  125. !!
  126. !! ** Purpose : initialization of the nemo model in off-line mode
  127. !!----------------------------------------------------------------------
  128. INTEGER :: ji ! dummy loop indices
  129. INTEGER :: ilocal_comm ! local integer
  130. INTEGER :: ios
  131. LOGICAL :: llexist
  132. CHARACTER(len=80), DIMENSION(16) :: cltxt
  133. !!
  134. NAMELIST/namctl/ ln_ctl , nn_print, nn_ictls, nn_ictle, &
  135. & nn_isplt, nn_jsplt, nn_jctls, nn_jctle, &
  136. & nn_bench, nn_timing
  137. NAMELIST/namcfg/ cp_cfg, cp_cfz, jp_cfg, jpidta, jpjdta, jpkdta, jpiglo, jpjglo, &
  138. & jpizoom, jpjzoom, jperio, ln_use_jattr
  139. !!----------------------------------------------------------------------
  140. cltxt = ''
  141. cxios_context = 'nemo'
  142. !
  143. ! ! Open reference namelist and configuration namelist files
  144. CALL ctl_opn( numnam_ref, 'namelist_ref', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. )
  145. CALL ctl_opn( numnam_cfg, 'namelist_cfg', 'OLD', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE. )
  146. !
  147. REWIND( numnam_ref ) ! Namelist namctl in reference namelist : Control prints & Benchmark
  148. READ ( numnam_ref, namctl, IOSTAT = ios, ERR = 901 )
  149. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in reference namelist', .TRUE. )
  150. REWIND( numnam_cfg ) ! Namelist namctl in confguration namelist : Control prints & Benchmark
  151. READ ( numnam_cfg, namctl, IOSTAT = ios, ERR = 902 )
  152. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namctl in configuration namelist', .TRUE. )
  153. !
  154. REWIND( numnam_ref ) ! Namelist namcfg in reference namelist : Control prints & Benchmark
  155. READ ( numnam_ref, namcfg, IOSTAT = ios, ERR = 903 )
  156. 903 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in reference namelist', .TRUE. )
  157. REWIND( numnam_cfg ) ! Namelist namcfg in confguration namelist : Control prints & Benchmark
  158. READ ( numnam_cfg, namcfg, IOSTAT = ios, ERR = 904 )
  159. 904 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namcfg in configuration namelist', .TRUE. )
  160. !
  161. ! !--------------------------------------------!
  162. ! ! set communicator & select the local node !
  163. ! ! NB: mynode also opens output.namelist.dyn !
  164. ! ! on unit number numond on first proc !
  165. ! !--------------------------------------------!
  166. #if defined key_iomput
  167. CALL xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm )
  168. narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) ! Nodes selection
  169. #else
  170. ilocal_comm = 0
  171. narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) ! Nodes selection (control print return in cltxt)
  172. #endif
  173. narea = narea + 1 ! mynode return the rank of proc (0 --> jpnij -1 )
  174. lwm = (narea == 1) ! control of output namelists
  175. lwp = (narea == 1) .OR. ln_ctl ! control of all listing output print
  176. IF(lwm) THEN
  177. ! write merged namelists from earlier to output namelist now that the
  178. ! file has been opened in call to mynode. nammpp has already been
  179. ! written in mynode (if lk_mpp_mpi)
  180. WRITE( numond, namctl )
  181. WRITE( numond, namcfg )
  182. ENDIF
  183. ! If dimensions of processor grid weren't specified in the namelist file
  184. ! then we calculate them here now that we have our communicator size
  185. IF( (jpni < 1) .OR. (jpnj < 1) )THEN
  186. #if defined key_mpp_mpi
  187. CALL nemo_partition(mppsize)
  188. #else
  189. jpni = 1
  190. jpnj = 1
  191. jpnij = jpni*jpnj
  192. #endif
  193. END IF
  194. ! Calculate domain dimensions given calculated jpni and jpnj
  195. ! This used to be done in par_oce.F90 when they were parameters rather
  196. ! than variables
  197. jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci ! first dim.
  198. jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ! second dim.
  199. jpk = jpkdta ! third dim
  200. jpim1 = jpi-1 ! inner domain indices
  201. jpjm1 = jpj-1 ! " "
  202. jpkm1 = jpk-1 ! " "
  203. jpij = jpi*jpj ! jpi x j
  204. IF(lwp) THEN ! open listing units
  205. !
  206. CALL ctl_opn( numout, 'ocean.output', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, 6, .FALSE., narea )
  207. !
  208. WRITE(numout,*)
  209. WRITE(numout,*) ' CNRS - NERC - Met OFFICE - MERCATOR-ocean - INGV - CMCC'
  210. WRITE(numout,*) ' NEMO team'
  211. WRITE(numout,*) ' Ocean General Circulation Model'
  212. WRITE(numout,*) ' version 3.6 (2015) '
  213. WRITE(numout,*)
  214. WRITE(numout,*)
  215. DO ji = 1, SIZE(cltxt)
  216. IF( TRIM(cltxt(ji)) /= '' ) WRITE(numout,*) cltxt(ji) ! control print of mynode
  217. END DO
  218. WRITE(numout,cform_aaa) ! Flag AAAAAAA
  219. !
  220. ENDIF
  221. ! Now we know the dimensions of the grid and numout has been set we can
  222. ! allocate arrays
  223. CALL nemo_alloc()
  224. ! !--------------------------------!
  225. ! ! Model general initialization !
  226. ! !--------------------------------!
  227. CALL nemo_ctl ! Control prints & Benchmark
  228. ! ! Domain decomposition
  229. IF( jpni*jpnj == jpnij ) THEN ; CALL mpp_init ! standard cutting out
  230. ELSE ; CALL mpp_init2 ! eliminate land processors
  231. ENDIF
  232. !
  233. IF( nn_timing == 1 ) CALL timing_init
  234. !
  235. ! ! General initialization
  236. IF( nn_timing == 1 ) CALL timing_start( 'nemo_init')
  237. !
  238. CALL phy_cst ! Physical constants
  239. CALL eos_init ! Equation of state
  240. IF( lk_c1d ) CALL c1d_init ! 1D column configuration
  241. CALL dom_cfg ! Domain configuration
  242. !
  243. !
  244. INQUIRE( FILE='coordinates.nc', EXIST = llexist ) ! Check if coordinate file exist
  245. !
  246. IF( llexist ) THEN ; CALL dom_init ! compute the grid from coordinates and bathymetry
  247. ELSE ; CALL dom_rea ! read grid from the meskmask
  248. ENDIF
  249. CALL istate_init ! ocean initial state (Dynamics and tracers)
  250. IF( ln_nnogather ) CALL nemo_northcomms ! Initialise the northfold neighbour lists (must be done after the masks are defined)
  251. IF( ln_ctl ) CALL prt_ctl_init ! Print control
  252. CALL sbc_init ! Forcings : surface module
  253. #if ! defined key_degrad
  254. CALL ldf_tra_init ! Lateral ocean tracer physics
  255. #endif
  256. IF( lk_ldfslp ) CALL ldf_slp_init ! slope of lateral mixing
  257. CALL tra_qsr_init ! penetrative solar radiation qsr
  258. IF( lk_trabbl ) CALL tra_bbl_init ! advective (and/or diffusive) bottom boundary layer scheme
  259. CALL trc_nam_run ! Needed to get restart parameters for passive tracers
  260. CALL trc_rst_cal( nit000, 'READ' ) ! calendar
  261. CALL dta_dyn_init ! Initialization for the dynamics
  262. CALL trc_init ! Passive tracers initialization
  263. ! ! in various advection and diffusion routines
  264. IF(lwp) WRITE(numout,cform_aaa) ! Flag AAAAAAA
  265. !
  266. IF( nn_timing == 1 ) CALL timing_stop( 'nemo_init')
  267. !
  268. END SUBROUTINE nemo_init
  269. SUBROUTINE nemo_ctl
  270. !!----------------------------------------------------------------------
  271. !! *** ROUTINE nemo_ctl ***
  272. !!
  273. !! ** Purpose : control print setting
  274. !!
  275. !! ** Method : - print namctl information and check some consistencies
  276. !!----------------------------------------------------------------------
  277. !
  278. IF(lwp) THEN ! Parameter print
  279. WRITE(numout,*)
  280. WRITE(numout,*) 'nemo_flg: Control prints & Benchmark'
  281. WRITE(numout,*) '~~~~~~~ '
  282. WRITE(numout,*) ' Namelist namctl'
  283. WRITE(numout,*) ' run control (for debugging) ln_ctl = ', ln_ctl
  284. WRITE(numout,*) ' level of print nn_print = ', nn_print
  285. WRITE(numout,*) ' Start i indice for SUM control nn_ictls = ', nn_ictls
  286. WRITE(numout,*) ' End i indice for SUM control nn_ictle = ', nn_ictle
  287. WRITE(numout,*) ' Start j indice for SUM control nn_jctls = ', nn_jctls
  288. WRITE(numout,*) ' End j indice for SUM control nn_jctle = ', nn_jctle
  289. WRITE(numout,*) ' number of proc. following i nn_isplt = ', nn_isplt
  290. WRITE(numout,*) ' number of proc. following j nn_jsplt = ', nn_jsplt
  291. WRITE(numout,*) ' benchmark parameter (0/1) nn_bench = ', nn_bench
  292. ENDIF
  293. !
  294. nprint = nn_print ! convert DOCTOR namelist names into OLD names
  295. nictls = nn_ictls
  296. nictle = nn_ictle
  297. njctls = nn_jctls
  298. njctle = nn_jctle
  299. isplt = nn_isplt
  300. jsplt = nn_jsplt
  301. nbench = nn_bench
  302. IF(lwp) THEN ! control print
  303. WRITE(numout,*)
  304. WRITE(numout,*) 'namcfg : configuration initialization through namelist read'
  305. WRITE(numout,*) '~~~~~~~ '
  306. WRITE(numout,*) ' Namelist namcfg'
  307. WRITE(numout,*) ' configuration name cp_cfg = ', TRIM(cp_cfg)
  308. WRITE(numout,*) ' configuration resolution jp_cfg = ', jp_cfg
  309. WRITE(numout,*) ' 1st lateral dimension ( >= jpi ) jpidta = ', jpidta
  310. WRITE(numout,*) ' 2nd " " ( >= jpj ) jpjdta = ', jpjdta
  311. WRITE(numout,*) ' 3nd " " jpkdta = ', jpkdta
  312. WRITE(numout,*) ' 1st dimension of global domain in i jpiglo = ', jpiglo
  313. WRITE(numout,*) ' 2nd - - in j jpjglo = ', jpjglo
  314. WRITE(numout,*) ' left bottom i index of the zoom (in data domain) jpizoom = ', jpizoom
  315. WRITE(numout,*) ' left bottom j index of the zoom (in data domain) jpizoom = ', jpjzoom
  316. WRITE(numout,*) ' lateral cond. type (between 0 and 6) jperio = ', jperio
  317. WRITE(numout,*) ' use file attribute if exists as i/p j-start ln_use_jattr = ', ln_use_jattr
  318. ENDIF
  319. ! ! Parameter control
  320. !
  321. IF( ln_ctl ) THEN ! sub-domain area indices for the control prints
  322. IF( lk_mpp ) THEN
  323. isplt = jpni ; jsplt = jpnj ; ijsplt = jpni*jpnj ! the domain is forced to the real splitted domain
  324. ELSE
  325. IF( isplt == 1 .AND. jsplt == 1 ) THEN
  326. CALL ctl_warn( ' - isplt & jsplt are equal to 1', &
  327. & ' - the print control will be done over the whole domain' )
  328. ENDIF
  329. ijsplt = isplt * jsplt ! total number of processors ijsplt
  330. ENDIF
  331. IF(lwp) WRITE(numout,*)' - The total number of processors over which the'
  332. IF(lwp) WRITE(numout,*)' print control will be done is ijsplt : ', ijsplt
  333. !
  334. ! ! indices used for the SUM control
  335. IF( nictls+nictle+njctls+njctle == 0 ) THEN ! print control done over the default area
  336. lsp_area = .FALSE.
  337. ELSE ! print control done over a specific area
  338. lsp_area = .TRUE.
  339. IF( nictls < 1 .OR. nictls > jpiglo ) THEN
  340. CALL ctl_warn( ' - nictls must be 1<=nictls>=jpiglo, it is forced to 1' )
  341. nictls = 1
  342. ENDIF
  343. IF( nictle < 1 .OR. nictle > jpiglo ) THEN
  344. CALL ctl_warn( ' - nictle must be 1<=nictle>=jpiglo, it is forced to jpiglo' )
  345. nictle = jpiglo
  346. ENDIF
  347. IF( njctls < 1 .OR. njctls > jpjglo ) THEN
  348. CALL ctl_warn( ' - njctls must be 1<=njctls>=jpjglo, it is forced to 1' )
  349. njctls = 1
  350. ENDIF
  351. IF( njctle < 1 .OR. njctle > jpjglo ) THEN
  352. CALL ctl_warn( ' - njctle must be 1<=njctle>=jpjglo, it is forced to jpjglo' )
  353. njctle = jpjglo
  354. ENDIF
  355. ENDIF
  356. ENDIF
  357. !
  358. IF( nbench == 1 ) THEN ! Benchmark
  359. SELECT CASE ( cp_cfg )
  360. CASE ( 'gyre' ) ; CALL ctl_warn( ' The Benchmark is activated ' )
  361. CASE DEFAULT ; CALL ctl_stop( ' The Benchmark is based on the GYRE configuration:', &
  362. & ' cp_cfg="gyre" in namelsit &namcfg or set nbench = 0' )
  363. END SELECT
  364. ENDIF
  365. !
  366. IF( lk_c1d .AND. .NOT.lk_iomput ) CALL ctl_stop( 'nemo_ctl: The 1D configuration must be used ', &
  367. & 'with the IOM Input/Output manager. ' , &
  368. & 'Compile with key_iomput enabled' )
  369. !
  370. IF( 1_wp /= SIGN(1._wp,-0._wp) ) CALL ctl_stop( 'nemo_ctl: The intrinsec SIGN function follows ', &
  371. & 'f2003 standard. ' , &
  372. & 'Compile with key_nosignedzero enabled' )
  373. !
  374. END SUBROUTINE nemo_ctl
  375. SUBROUTINE nemo_closefile
  376. !!----------------------------------------------------------------------
  377. !! *** ROUTINE nemo_closefile ***
  378. !!
  379. !! ** Purpose : Close the files
  380. !!----------------------------------------------------------------------
  381. !
  382. IF ( lk_mpp ) CALL mppsync
  383. !
  384. CALL iom_close ! close all input/output files managed by iom_*
  385. !
  386. IF( numstp /= -1 ) CLOSE( numstp ) ! time-step file
  387. IF( numnam_ref /= -1 ) CLOSE( numnam_ref ) ! oce reference namelist
  388. IF( numnam_cfg /= -1 ) CLOSE( numnam_cfg ) ! oce configuration namelist
  389. IF( numout /= 6 ) CLOSE( numout ) ! standard model output file
  390. numout = 6 ! redefine numout in case it is used after this point...
  391. !
  392. END SUBROUTINE nemo_closefile
  393. SUBROUTINE nemo_alloc
  394. !!----------------------------------------------------------------------
  395. !! *** ROUTINE nemo_alloc ***
  396. !!
  397. !! ** Purpose : Allocate all the dynamic arrays of the OPA modules
  398. !!
  399. !! ** Method :
  400. !!----------------------------------------------------------------------
  401. USE diawri, ONLY: dia_wri_alloc
  402. USE dom_oce, ONLY: dom_oce_alloc
  403. USE zdf_oce, ONLY: zdf_oce_alloc
  404. USE ldftra_oce, ONLY: ldftra_oce_alloc
  405. USE trc_oce, ONLY: trc_oce_alloc
  406. !
  407. INTEGER :: ierr
  408. !!----------------------------------------------------------------------
  409. !
  410. ierr = oce_alloc () ! ocean
  411. ierr = ierr + dia_wri_alloc ()
  412. ierr = ierr + dom_oce_alloc () ! ocean domain
  413. ierr = ierr + ldftra_oce_alloc() ! ocean lateral physics : tracers
  414. ierr = ierr + zdf_oce_alloc () ! ocean vertical physics
  415. !
  416. ierr = ierr + trc_oce_alloc () ! shared TRC / TRA arrays
  417. !
  418. IF( lk_mpp ) CALL mpp_sum( ierr )
  419. IF( ierr /= 0 ) CALL ctl_stop( 'STOP', 'nemo_alloc: unable to allocate standard ocean arrays' )
  420. !
  421. END SUBROUTINE nemo_alloc
  422. SUBROUTINE nemo_partition( num_pes )
  423. !!----------------------------------------------------------------------
  424. !! *** ROUTINE nemo_partition ***
  425. !!
  426. !! ** Purpose :
  427. !!
  428. !! ** Method :
  429. !!----------------------------------------------------------------------
  430. INTEGER, INTENT(in) :: num_pes ! The number of MPI processes we have
  431. !
  432. INTEGER, PARAMETER :: nfactmax = 20
  433. INTEGER :: nfact ! The no. of factors returned
  434. INTEGER :: ierr ! Error flag
  435. INTEGER :: ji
  436. INTEGER :: idiff, mindiff, imin ! For choosing pair of factors that are closest in value
  437. INTEGER, DIMENSION(nfactmax) :: ifact ! Array of factors
  438. !!----------------------------------------------------------------------
  439. ierr = 0
  440. CALL factorise( ifact, nfactmax, nfact, num_pes, ierr )
  441. IF( nfact <= 1 ) THEN
  442. WRITE (numout, *) 'WARNING: factorisation of number of PEs failed'
  443. WRITE (numout, *) ' : using grid of ',num_pes,' x 1'
  444. jpnj = 1
  445. jpni = num_pes
  446. ELSE
  447. ! Search through factors for the pair that are closest in value
  448. mindiff = 1000000
  449. imin = 1
  450. DO ji = 1, nfact-1, 2
  451. idiff = ABS( ifact(ji) - ifact(ji+1) )
  452. IF( idiff < mindiff ) THEN
  453. mindiff = idiff
  454. imin = ji
  455. ENDIF
  456. END DO
  457. jpnj = ifact(imin)
  458. jpni = ifact(imin + 1)
  459. ENDIF
  460. !
  461. jpnij = jpni*jpnj
  462. !
  463. END SUBROUTINE nemo_partition
  464. SUBROUTINE factorise( kfax, kmaxfax, knfax, kn, kerr )
  465. !!----------------------------------------------------------------------
  466. !! *** ROUTINE factorise ***
  467. !!
  468. !! ** Purpose : return the prime factors of n.
  469. !! knfax factors are returned in array kfax which is of
  470. !! maximum dimension kmaxfax.
  471. !! ** Method :
  472. !!----------------------------------------------------------------------
  473. INTEGER , INTENT(in ) :: kn, kmaxfax
  474. INTEGER , INTENT( out) :: kerr, knfax
  475. INTEGER, DIMENSION(kmaxfax), INTENT( out) :: kfax
  476. !
  477. INTEGER :: ifac, jl, inu
  478. INTEGER, PARAMETER :: ntest = 14
  479. INTEGER :: ilfax(ntest)
  480. !
  481. ! lfax contains the set of allowed factors.
  482. data (ilfax(jl),jl=1,ntest) / 16384, 8192, 4096, 2048, 1024, 512, 256, &
  483. & 128, 64, 32, 16, 8, 4, 2 /
  484. !!----------------------------------------------------------------------
  485. ! Clear the error flag and initialise output vars
  486. kerr = 0
  487. kfax = 1
  488. knfax = 0
  489. ! Find the factors of n.
  490. IF( kn == 1 ) GOTO 20
  491. ! nu holds the unfactorised part of the number.
  492. ! knfax holds the number of factors found.
  493. ! l points to the allowed factor list.
  494. ! ifac holds the current factor.
  495. inu = kn
  496. knfax = 0
  497. DO jl = ntest, 1, -1
  498. !
  499. ifac = ilfax(jl)
  500. IF( ifac > inu ) CYCLE
  501. ! Test whether the factor will divide.
  502. IF( MOD(inu,ifac) == 0 ) THEN
  503. !
  504. knfax = knfax + 1 ! Add the factor to the list
  505. IF( knfax > kmaxfax ) THEN
  506. kerr = 6
  507. write (*,*) 'FACTOR: insufficient space in factor array ', knfax
  508. return
  509. ENDIF
  510. kfax(knfax) = ifac
  511. ! Store the other factor that goes with this one
  512. knfax = knfax + 1
  513. kfax(knfax) = inu / ifac
  514. !WRITE (*,*) 'ARPDBG, factors ',knfax-1,' & ',knfax,' are ', kfax(knfax-1),' and ',kfax(knfax)
  515. ENDIF
  516. !
  517. END DO
  518. 20 CONTINUE ! Label 20 is the exit point from the factor search loop.
  519. !
  520. END SUBROUTINE factorise
  521. #if defined key_mpp_mpi
  522. SUBROUTINE nemo_northcomms
  523. !!======================================================================
  524. !! *** ROUTINE nemo_northcomms ***
  525. !! nemo_northcomms : Setup for north fold exchanges with explicit
  526. !! point-to-point messaging
  527. !!=====================================================================
  528. !!----------------------------------------------------------------------
  529. !!
  530. !! ** Purpose : Initialization of the northern neighbours lists.
  531. !!----------------------------------------------------------------------
  532. !! 1.0 ! 2011-10 (A. C. Coward, NOCS & J. Donners, PRACE)
  533. !! 2.0 ! 2013-06 Setup avoiding MPI communication (I. Epicoco, S.
  534. !Mocavero, CMCC)
  535. !!----------------------------------------------------------------------
  536. INTEGER :: sxM, dxM, sxT, dxT, jn
  537. INTEGER :: njmppmax
  538. njmppmax = MAXVAL( njmppt )
  539. !initializes the north-fold communication variables
  540. isendto(:) = 0
  541. nsndto = 0
  542. !if I am a process in the north
  543. IF ( njmpp == njmppmax ) THEN
  544. !sxM is the first point (in the global domain) needed to compute the
  545. !north-fold for the current process
  546. sxM = jpiglo - nimppt(narea) - nlcit(narea) + 1
  547. !dxM is the last point (in the global domain) needed to compute the
  548. !north-fold for the current process
  549. dxM = jpiglo - nimppt(narea) + 2
  550. !loop over the other north-fold processes to find the processes
  551. !managing the points belonging to the sxT-dxT range
  552. DO jn = 1, jpni
  553. !sxT is the first point (in the global domain) of the jn
  554. !process
  555. sxT = nfiimpp(jn, jpnj)
  556. !dxT is the last point (in the global domain) of the jn
  557. !process
  558. dxT = nfiimpp(jn, jpnj) + nfilcit(jn, jpnj) - 1
  559. IF ((sxM .gt. sxT) .AND. (sxM .lt. dxT)) THEN
  560. nsndto = nsndto + 1
  561. isendto(nsndto) = jn
  562. ELSEIF ((sxM .le. sxT) .AND. (dxM .ge. dxT)) THEN
  563. nsndto = nsndto + 1
  564. isendto(nsndto) = jn
  565. ELSEIF ((dxM .lt. dxT) .AND. (sxT .lt. dxM)) THEN
  566. nsndto = nsndto + 1
  567. isendto(nsndto) = jn
  568. END IF
  569. END DO
  570. nfsloop = 1
  571. nfeloop = nlci
  572. DO jn = 2,jpni-1
  573. IF(nfipproc(jn,jpnj) .eq. (narea - 1)) THEN
  574. IF (nfipproc(jn - 1 ,jpnj) .eq. -1) THEN
  575. nfsloop = nldi
  576. ENDIF
  577. IF (nfipproc(jn + 1,jpnj) .eq. -1) THEN
  578. nfeloop = nlei
  579. ENDIF
  580. ENDIF
  581. END DO
  582. ENDIF
  583. l_north_nogather = .TRUE.
  584. END SUBROUTINE nemo_northcomms
  585. #else
  586. SUBROUTINE nemo_northcomms ! Dummy routine
  587. WRITE(*,*) 'nemo_northcomms: You should not have seen this print! error?'
  588. END SUBROUTINE nemo_northcomms
  589. #endif
  590. SUBROUTINE istate_init
  591. !!----------------------------------------------------------------------
  592. !! *** ROUTINE istate_init ***
  593. !!
  594. !! ** Purpose : Initialization to zero of the dynamics and tracers.
  595. !!----------------------------------------------------------------------
  596. !
  597. ! now fields ! after fields !
  598. un (:,:,:) = 0._wp ; ua(:,:,:) = 0._wp !
  599. vn (:,:,:) = 0._wp ; va(:,:,:) = 0._wp !
  600. wn (:,:,:) = 0._wp ! !
  601. hdivn(:,:,:) = 0._wp ! !
  602. tsn (:,:,:,:) = 0._wp ! !
  603. !
  604. rhd (:,:,:) = 0.e0
  605. rhop (:,:,:) = 0.e0
  606. rn2 (:,:,:) = 0.e0
  607. !
  608. END SUBROUTINE istate_init
  609. SUBROUTINE stp_ctl( kt, kindic )
  610. !!----------------------------------------------------------------------
  611. !! *** ROUTINE stp_ctl ***
  612. !!
  613. !! ** Purpose : Control the run
  614. !!
  615. !! ** Method : - Save the time step in numstp
  616. !!
  617. !! ** Actions : 'time.step' file containing the last ocean time-step
  618. !!----------------------------------------------------------------------
  619. INTEGER, INTENT(in ) :: kt ! ocean time-step index
  620. INTEGER, INTENT(inout) :: kindic ! indicator of solver convergence
  621. !!----------------------------------------------------------------------
  622. !
  623. IF( kt == nit000 .AND. lwp ) THEN
  624. WRITE(numout,*)
  625. WRITE(numout,*) 'stp_ctl : time-stepping control'
  626. WRITE(numout,*) '~~~~~~~'
  627. ! open time.step file
  628. CALL ctl_opn( numstp, 'time.step', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea )
  629. ENDIF
  630. !
  631. IF(lwp) WRITE ( numstp, '(1x, i8)' ) kt !* save the current time step in numstp
  632. IF(lwp) REWIND( numstp ) ! --------------------------
  633. !
  634. END SUBROUTINE stp_ctl
  635. !!======================================================================
  636. END MODULE nemogcm