sbcice_cice.F90 45 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116
  1. MODULE sbcice_cice
  2. !!======================================================================
  3. !! *** MODULE sbcice_cice ***
  4. !! To couple with sea ice model CICE (LANL)
  5. !!=====================================================================
  6. #if defined key_cice
  7. !!----------------------------------------------------------------------
  8. !! 'key_cice' : CICE sea-ice model
  9. !!----------------------------------------------------------------------
  10. !! sbc_ice_cice : sea-ice model time-stepping and update ocean sbc over ice-covered area
  11. !!
  12. !!
  13. !!----------------------------------------------------------------------
  14. USE oce ! ocean dynamics and tracers
  15. USE dom_oce ! ocean space and time domain
  16. USE domvvl
  17. USE phycst, only : rcp, rau0, r1_rau0, rhosn, rhoic
  18. USE in_out_manager ! I/O manager
  19. USE iom, ONLY : iom_put,iom_use ! I/O manager library !!Joakim edit
  20. USE lib_mpp ! distributed memory computing library
  21. USE lbclnk ! ocean lateral boundary conditions (or mpp link)
  22. USE wrk_nemo ! work arrays
  23. USE timing ! Timing
  24. USE daymod ! calendar
  25. USE fldread ! read input fields
  26. USE sbc_oce ! Surface boundary condition: ocean fields
  27. USE sbc_ice ! Surface boundary condition: ice fields
  28. USE sbcblk_core ! Surface boundary condition: CORE bulk
  29. USE sbccpl
  30. USE ice_kinds_mod
  31. USE ice_blocks
  32. USE ice_domain
  33. USE ice_domain_size
  34. USE ice_boundary
  35. USE ice_constants
  36. USE ice_gather_scatter
  37. USE ice_calendar, only: dt
  38. USE ice_state, only: aice,aicen,uvel,vvel,vsno,vsnon,vice,vicen
  39. # if defined key_cice4
  40. USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow, &
  41. strocnxT,strocnyT, &
  42. sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_gbm, &
  43. fresh_gbm,fhocn_gbm,fswthru_gbm,frzmlt, &
  44. flatn_f,fsurfn_f,fcondtopn_f, &
  45. uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl, &
  46. swvdr,swvdf,swidr,swidf
  47. USE ice_therm_vertical, only: calc_Tsfc
  48. #else
  49. USE ice_flux, only: strax,stray,strocnx,strocny,frain,fsnow, &
  50. strocnxT,strocnyT, &
  51. sst,sss,uocn,vocn,ss_tltx,ss_tlty,fsalt_ai, &
  52. fresh_ai,fhocn_ai,fswthru_ai,frzmlt, &
  53. flatn_f,fsurfn_f,fcondtopn_f, &
  54. uatm,vatm,wind,fsw,flw,Tair,potT,Qa,rhoa,zlvl, &
  55. swvdr,swvdf,swidr,swidf
  56. USE ice_therm_shared, only: calc_Tsfc
  57. #endif
  58. USE ice_forcing, only: frcvdr,frcvdf,frcidr,frcidf
  59. USE ice_atmo, only: calc_strair
  60. USE CICE_InitMod
  61. USE CICE_RunMod
  62. USE CICE_FinalMod
  63. IMPLICIT NONE
  64. PRIVATE
  65. !! * Routine accessibility
  66. PUBLIC cice_sbc_init ! routine called by sbc_init
  67. PUBLIC cice_sbc_final ! routine called by sbc_final
  68. PUBLIC sbc_ice_cice ! routine called by sbc
  69. INTEGER :: ji_off
  70. INTEGER :: jj_off
  71. INTEGER , PARAMETER :: jpfld = 13 ! maximum number of files to read
  72. INTEGER , PARAMETER :: jp_snow = 1 ! index of snow file
  73. INTEGER , PARAMETER :: jp_rain = 2 ! index of rain file
  74. INTEGER , PARAMETER :: jp_sblm = 3 ! index of sublimation file
  75. INTEGER , PARAMETER :: jp_top1 = 4 ! index of category 1 topmelt file
  76. INTEGER , PARAMETER :: jp_top2 = 5 ! index of category 2 topmelt file
  77. INTEGER , PARAMETER :: jp_top3 = 6 ! index of category 3 topmelt file
  78. INTEGER , PARAMETER :: jp_top4 = 7 ! index of category 4 topmelt file
  79. INTEGER , PARAMETER :: jp_top5 = 8 ! index of category 5 topmelt file
  80. INTEGER , PARAMETER :: jp_bot1 = 9 ! index of category 1 botmelt file
  81. INTEGER , PARAMETER :: jp_bot2 = 10 ! index of category 2 botmelt file
  82. INTEGER , PARAMETER :: jp_bot3 = 11 ! index of category 3 botmelt file
  83. INTEGER , PARAMETER :: jp_bot4 = 12 ! index of category 4 botmelt file
  84. INTEGER , PARAMETER :: jp_bot5 = 13 ! index of category 5 botmelt file
  85. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf ! structure of input fields (file informations, fields read)
  86. REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:), PRIVATE :: png ! local array used in sbc_cice_ice
  87. !! * Substitutions
  88. # include "domzgr_substitute.h90"
  89. !! $Id: sbcice_cice.F90 2544 2015-08-24 09:00:45Z ufla $
  90. CONTAINS
  91. INTEGER FUNCTION sbc_ice_cice_alloc()
  92. !!----------------------------------------------------------------------
  93. !! *** FUNCTION sbc_ice_cice_alloc ***
  94. !!----------------------------------------------------------------------
  95. ALLOCATE( png(jpi,jpj,jpnij), STAT=sbc_ice_cice_alloc )
  96. IF( lk_mpp ) CALL mpp_sum ( sbc_ice_cice_alloc )
  97. IF( sbc_ice_cice_alloc > 0 ) CALL ctl_warn('sbc_ice_cice_alloc: allocation of arrays failed.')
  98. END FUNCTION sbc_ice_cice_alloc
  99. SUBROUTINE sbc_ice_cice( kt, ksbc )
  100. !!---------------------------------------------------------------------
  101. !! *** ROUTINE sbc_ice_cice ***
  102. !!
  103. !! ** Purpose : update the ocean surface boundary condition via the
  104. !! CICE Sea Ice Model time stepping
  105. !!
  106. !! ** Method : - Get any extra forcing fields for CICE
  107. !! - Prepare forcing fields
  108. !! - CICE model time stepping
  109. !! - call the routine that computes mass and
  110. !! heat fluxes at the ice/ocean interface
  111. !!
  112. !! ** Action : - time evolution of the CICE sea-ice model
  113. !! - update all sbc variables below sea-ice:
  114. !! utau, vtau, qns , qsr, emp , sfx
  115. !!---------------------------------------------------------------------
  116. INTEGER, INTENT(in) :: kt ! ocean time step
  117. INTEGER, INTENT(in) :: ksbc ! surface forcing type
  118. !!----------------------------------------------------------------------
  119. !
  120. IF( nn_timing == 1 ) CALL timing_start('sbc_ice_cice')
  121. !
  122. ! !----------------------!
  123. IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! Ice time-step only !
  124. ! !----------------------!
  125. ! Make sure any fluxes required for CICE are set
  126. IF ( ksbc == jp_flx ) THEN
  127. CALL cice_sbc_force(kt)
  128. ELSE IF ( ksbc == jp_purecpl ) THEN
  129. CALL sbc_cpl_ice_flx( 1.0-fr_i )
  130. ENDIF
  131. CALL cice_sbc_in ( kt, ksbc )
  132. CALL CICE_Run
  133. CALL cice_sbc_out ( kt, ksbc )
  134. IF ( ksbc == jp_purecpl ) CALL cice_sbc_hadgam(kt+1)
  135. ENDIF ! End sea-ice time step only
  136. !
  137. IF( nn_timing == 1 ) CALL timing_stop('sbc_ice_cice')
  138. END SUBROUTINE sbc_ice_cice
  139. SUBROUTINE cice_sbc_init (ksbc)
  140. !!---------------------------------------------------------------------
  141. !! *** ROUTINE cice_sbc_init ***
  142. !! ** Purpose: Initialise ice related fields for NEMO and coupling
  143. !!
  144. INTEGER, INTENT( in ) :: ksbc ! surface forcing type
  145. REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2
  146. REAL(wp) :: zcoefu, zcoefv, zcoeff ! local scalar
  147. INTEGER :: ji, jj, jl, jk ! dummy loop indices
  148. !!---------------------------------------------------------------------
  149. IF( nn_timing == 1 ) CALL timing_start('cice_sbc_init')
  150. !
  151. CALL wrk_alloc( jpi,jpj, ztmp1, ztmp2 )
  152. !
  153. IF(lwp) WRITE(numout,*)'cice_sbc_init'
  154. ji_off = INT ( (jpiglo - nx_global) / 2 )
  155. jj_off = INT ( (jpjglo - ny_global) / 2 )
  156. #if defined key_nemocice_decomp
  157. ! Pass initial SST from NEMO to CICE so ice is initialised correctly if
  158. ! there is no restart file.
  159. ! Values from a CICE restart file would overwrite this
  160. IF ( .NOT. ln_rstart ) THEN
  161. CALL nemo2cice( tsn(:,:,1,jp_tem) , sst , 'T' , 1.)
  162. ENDIF
  163. #endif
  164. ! Initialize CICE
  165. CALL CICE_Initialize
  166. ! Do some CICE consistency checks
  167. IF ( (ksbc == jp_flx) .OR. (ksbc == jp_purecpl) ) THEN
  168. IF ( calc_strair .OR. calc_Tsfc ) THEN
  169. CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=F and calc_Tsfc=F in ice_in' )
  170. ENDIF
  171. ELSEIF (ksbc == jp_core) THEN
  172. IF ( .NOT. (calc_strair .AND. calc_Tsfc) ) THEN
  173. CALL ctl_stop( 'STOP', 'cice_sbc_init : Forcing option requires calc_strair=T and calc_Tsfc=T in ice_in' )
  174. ENDIF
  175. ENDIF
  176. ! allocate sbc_ice and sbc_cice arrays
  177. IF( sbc_ice_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate arrays' )
  178. IF( sbc_ice_cice_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_cice_alloc : unable to allocate cice arrays' )
  179. ! Ensure ocean temperatures are nowhere below freezing if not a NEMO restart
  180. IF( .NOT. ln_rstart ) THEN
  181. tsn(:,:,:,jp_tem) = MAX (tsn(:,:,:,jp_tem),Tocnfrz)
  182. tsb(:,:,:,jp_tem) = tsn(:,:,:,jp_tem)
  183. ENDIF
  184. fr_iu(:,:)=0.0
  185. fr_iv(:,:)=0.0
  186. CALL cice2nemo(aice,fr_i, 'T', 1. )
  187. IF ( (ksbc == jp_flx) .OR. (ksbc == jp_purecpl) ) THEN
  188. DO jl=1,ncat
  189. CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. )
  190. ENDDO
  191. ENDIF
  192. ! T point to U point
  193. ! T point to V point
  194. DO jj=1,jpjm1
  195. DO ji=1,jpim1
  196. fr_iu(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji+1,jj))*umask(ji,jj,1)
  197. fr_iv(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji,jj+1))*vmask(ji,jj,1)
  198. ENDDO
  199. ENDDO
  200. CALL lbc_lnk ( fr_iu , 'U', 1. )
  201. CALL lbc_lnk ( fr_iv , 'V', 1. )
  202. ! ! embedded sea ice
  203. IF( nn_ice_embd /= 0 ) THEN ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass
  204. CALL cice2nemo(vsno(:,:,:),ztmp1,'T', 1. )
  205. CALL cice2nemo(vice(:,:,:),ztmp2,'T', 1. )
  206. snwice_mass (:,:) = ( rhosn * ztmp1(:,:) + rhoic * ztmp2(:,:) )
  207. snwice_mass_b(:,:) = snwice_mass(:,:)
  208. ELSE
  209. snwice_mass (:,:) = 0.0_wp ! no mass exchanges
  210. snwice_mass_b(:,:) = 0.0_wp ! no mass exchanges
  211. ENDIF
  212. IF( .NOT. ln_rstart ) THEN
  213. IF( nn_ice_embd == 2 ) THEN ! full embedment (case 2) deplete the initial ssh below sea-ice area
  214. sshn(:,:) = sshn(:,:) - snwice_mass(:,:) * r1_rau0
  215. sshb(:,:) = sshb(:,:) - snwice_mass(:,:) * r1_rau0
  216. #if defined key_vvl
  217. ! key_vvl necessary? clem: yes for compilation purpose
  218. DO jk = 1,jpkm1 ! adjust initial vertical scale factors
  219. fse3t_n(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshn(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) )
  220. fse3t_b(:,:,jk) = e3t_0(:,:,jk)*( 1._wp + sshb(:,:)*tmask(:,:,1)/(ht_0(:,:) + 1.0 - tmask(:,:,1)) )
  221. ENDDO
  222. fse3t_a(:,:,:) = fse3t_b(:,:,:)
  223. ! Reconstruction of all vertical scale factors at now and before time
  224. ! steps
  225. ! =============================================================================
  226. ! Horizontal scale factor interpolations
  227. ! --------------------------------------
  228. CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3u_b(:,:,:), 'U' )
  229. CALL dom_vvl_interpol( fse3t_b(:,:,:), fse3v_b(:,:,:), 'V' )
  230. CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3u_n(:,:,:), 'U' )
  231. CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3v_n(:,:,:), 'V' )
  232. CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3f_n(:,:,:), 'F' )
  233. ! Vertical scale factor interpolations
  234. ! ------------------------------------
  235. CALL dom_vvl_interpol( fse3t_n(:,:,:), fse3w_n (:,:,:), 'W' )
  236. CALL dom_vvl_interpol( fse3u_n(:,:,:), fse3uw_n(:,:,:), 'UW' )
  237. CALL dom_vvl_interpol( fse3v_n(:,:,:), fse3vw_n(:,:,:), 'VW' )
  238. CALL dom_vvl_interpol( fse3u_b(:,:,:), fse3uw_b(:,:,:), 'UW' )
  239. CALL dom_vvl_interpol( fse3v_b(:,:,:), fse3vw_b(:,:,:), 'VW' )
  240. ! t- and w- points depth
  241. ! ----------------------
  242. fsdept_n(:,:,1) = 0.5_wp * fse3w_n(:,:,1)
  243. fsdepw_n(:,:,1) = 0.0_wp
  244. fsde3w_n(:,:,1) = fsdept_n(:,:,1) - sshn(:,:)
  245. DO jk = 2, jpk
  246. fsdept_n(:,:,jk) = fsdept_n(:,:,jk-1) + fse3w_n(:,:,jk)
  247. fsdepw_n(:,:,jk) = fsdepw_n(:,:,jk-1) + fse3t_n(:,:,jk-1)
  248. fsde3w_n(:,:,jk) = fsdept_n(:,:,jk ) - sshn (:,:)
  249. END DO
  250. #endif
  251. ENDIF
  252. ENDIF
  253. CALL wrk_dealloc( jpi,jpj, ztmp1, ztmp2 )
  254. !
  255. IF( nn_timing == 1 ) CALL timing_stop('cice_sbc_init')
  256. !
  257. END SUBROUTINE cice_sbc_init
  258. SUBROUTINE cice_sbc_in (kt, ksbc)
  259. !!---------------------------------------------------------------------
  260. !! *** ROUTINE cice_sbc_in ***
  261. !! ** Purpose: Set coupling fields and pass to CICE
  262. !!---------------------------------------------------------------------
  263. INTEGER, INTENT(in ) :: kt ! ocean time step
  264. INTEGER, INTENT(in ) :: ksbc ! surface forcing type
  265. INTEGER :: ji, jj, jl ! dummy loop indices
  266. REAL(wp), DIMENSION(:,:), POINTER :: ztmp, zpice
  267. REAL(wp), DIMENSION(:,:,:), POINTER :: ztmpn
  268. REAL(wp) :: zintb, zintn ! dummy argument
  269. !!---------------------------------------------------------------------
  270. IF( nn_timing == 1 ) CALL timing_start('cice_sbc_in')
  271. !
  272. CALL wrk_alloc( jpi,jpj, ztmp, zpice )
  273. CALL wrk_alloc( jpi,jpj,ncat, ztmpn )
  274. IF( kt == nit000 ) THEN
  275. IF(lwp) WRITE(numout,*)'cice_sbc_in'
  276. ENDIF
  277. ztmp(:,:)=0.0
  278. ! Aggregate ice concentration already set in cice_sbc_out (or cice_sbc_init on
  279. ! the first time-step)
  280. ! forced and coupled case
  281. IF ( (ksbc == jp_flx).OR.(ksbc == jp_purecpl) ) THEN
  282. ztmpn(:,:,:)=0.0
  283. ! x comp of wind stress (CI_1)
  284. ! U point to F point
  285. DO jj=1,jpjm1
  286. DO ji=1,jpi
  287. ztmp(ji,jj) = 0.5 * ( fr_iu(ji,jj) * utau(ji,jj) &
  288. + fr_iu(ji,jj+1) * utau(ji,jj+1) ) * fmask(ji,jj,1)
  289. ENDDO
  290. ENDDO
  291. CALL nemo2cice(ztmp,strax,'F', -1. )
  292. ! y comp of wind stress (CI_2)
  293. ! V point to F point
  294. DO jj=1,jpj
  295. DO ji=1,jpim1
  296. ztmp(ji,jj) = 0.5 * ( fr_iv(ji,jj) * vtau(ji,jj) &
  297. + fr_iv(ji+1,jj) * vtau(ji+1,jj) ) * fmask(ji,jj,1)
  298. ENDDO
  299. ENDDO
  300. CALL nemo2cice(ztmp,stray,'F', -1. )
  301. ! Surface downward latent heat flux (CI_5)
  302. IF (ksbc == jp_flx) THEN
  303. DO jl=1,ncat
  304. ztmpn(:,:,jl)=qla_ice(:,:,1)*a_i(:,:,jl)
  305. ENDDO
  306. ELSE
  307. ! emp_ice is set in sbc_cpl_ice_flx as sublimation-snow
  308. qla_ice(:,:,1)= - ( emp_ice(:,:)+sprecip(:,:) ) * Lsub
  309. ! End of temporary code
  310. DO jj=1,jpj
  311. DO ji=1,jpi
  312. IF (fr_i(ji,jj).eq.0.0) THEN
  313. DO jl=1,ncat
  314. ztmpn(ji,jj,jl)=0.0
  315. ENDDO
  316. ! This will then be conserved in CICE
  317. ztmpn(ji,jj,1)=qla_ice(ji,jj,1)
  318. ELSE
  319. DO jl=1,ncat
  320. ztmpn(ji,jj,jl)=qla_ice(ji,jj,1)*a_i(ji,jj,jl)/fr_i(ji,jj)
  321. ENDDO
  322. ENDIF
  323. ENDDO
  324. ENDDO
  325. ENDIF
  326. DO jl=1,ncat
  327. CALL nemo2cice(ztmpn(:,:,jl),flatn_f(:,:,jl,:),'T', 1. )
  328. ! GBM conductive flux through ice (CI_6)
  329. ! Convert to GBM
  330. IF (ksbc == jp_flx) THEN
  331. ztmp(:,:) = botmelt(:,:,jl)*a_i(:,:,jl)
  332. ELSE
  333. ztmp(:,:) = botmelt(:,:,jl)
  334. ENDIF
  335. CALL nemo2cice(ztmp,fcondtopn_f(:,:,jl,:),'T', 1. )
  336. ! GBM surface heat flux (CI_7)
  337. ! Convert to GBM
  338. IF (ksbc == jp_flx) THEN
  339. ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))*a_i(:,:,jl)
  340. ELSE
  341. ztmp(:,:) = (topmelt(:,:,jl)+botmelt(:,:,jl))
  342. ENDIF
  343. CALL nemo2cice(ztmp,fsurfn_f(:,:,jl,:),'T', 1. )
  344. ENDDO
  345. ELSE IF (ksbc == jp_core) THEN
  346. ! Pass CORE forcing fields to CICE (which will calculate heat fluxes etc itself)
  347. ! x comp and y comp of atmosphere surface wind (CICE expects on T points)
  348. ztmp(:,:) = wndi_ice(:,:)
  349. CALL nemo2cice(ztmp,uatm,'T', -1. )
  350. ztmp(:,:) = wndj_ice(:,:)
  351. CALL nemo2cice(ztmp,vatm,'T', -1. )
  352. ztmp(:,:) = SQRT ( wndi_ice(:,:)**2 + wndj_ice(:,:)**2 )
  353. CALL nemo2cice(ztmp,wind,'T', 1. ) ! Wind speed (m/s)
  354. ztmp(:,:) = qsr_ice(:,:,1)
  355. CALL nemo2cice(ztmp,fsw,'T', 1. ) ! Incoming short-wave (W/m^2)
  356. ztmp(:,:) = qlw_ice(:,:,1)
  357. CALL nemo2cice(ztmp,flw,'T', 1. ) ! Incoming long-wave (W/m^2)
  358. ztmp(:,:) = tatm_ice(:,:)
  359. CALL nemo2cice(ztmp,Tair,'T', 1. ) ! Air temperature (K)
  360. CALL nemo2cice(ztmp,potT,'T', 1. ) ! Potential temp (K)
  361. ! Following line uses MAX(....) to avoid problems if tatm_ice has unset halo rows
  362. ztmp(:,:) = 101000. / ( 287.04 * MAX(1.0,tatm_ice(:,:)) )
  363. ! Constant (101000.) atm pressure assumed
  364. CALL nemo2cice(ztmp,rhoa,'T', 1. ) ! Air density (kg/m^3)
  365. ztmp(:,:) = qatm_ice(:,:)
  366. CALL nemo2cice(ztmp,Qa,'T', 1. ) ! Specific humidity (kg/kg)
  367. ztmp(:,:)=10.0
  368. CALL nemo2cice(ztmp,zlvl,'T', 1. ) ! Atmos level height (m)
  369. ! May want to check all values are physically realistic (as in CICE routine
  370. ! prepare_forcing)?
  371. ! Divide shortwave into spectral bands (as in prepare_forcing)
  372. ztmp(:,:)=qsr_ice(:,:,1)*frcvdr ! visible direct
  373. CALL nemo2cice(ztmp,swvdr,'T', 1. )
  374. ztmp(:,:)=qsr_ice(:,:,1)*frcvdf ! visible diffuse
  375. CALL nemo2cice(ztmp,swvdf,'T', 1. )
  376. ztmp(:,:)=qsr_ice(:,:,1)*frcidr ! near IR direct
  377. CALL nemo2cice(ztmp,swidr,'T', 1. )
  378. ztmp(:,:)=qsr_ice(:,:,1)*frcidf ! near IR diffuse
  379. CALL nemo2cice(ztmp,swidf,'T', 1. )
  380. ENDIF
  381. ! Snowfall
  382. ! Ensure fsnow is positive (as in CICE routine prepare_forcing)
  383. IF( iom_use('snowpre') ) CALL iom_put('snowpre',MAX( (1.0-fr_i(:,:))*sprecip(:,:) ,0.0)) !!Joakim edit
  384. ztmp(:,:)=MAX(fr_i(:,:)*sprecip(:,:),0.0)
  385. CALL nemo2cice(ztmp,fsnow,'T', 1. )
  386. ! Rainfall
  387. IF( iom_use('precip') ) CALL iom_put('precip', (1.0-fr_i(:,:))*(tprecip(:,:)-sprecip(:,:)) ) !!Joakim edit
  388. ztmp(:,:)=fr_i(:,:)*(tprecip(:,:)-sprecip(:,:))
  389. CALL nemo2cice(ztmp,frain,'T', 1. )
  390. ! Freezing/melting potential
  391. ! Calculated over NEMO leapfrog timestep (hence 2*dt)
  392. nfrzmlt(:,:)=rau0*rcp*fse3t_m(:,:)*(Tocnfrz-sst_m(:,:))/(2.0*dt)
  393. ztmp(:,:) = nfrzmlt(:,:)
  394. CALL nemo2cice(ztmp,frzmlt,'T', 1. )
  395. ! SST and SSS
  396. CALL nemo2cice(sst_m,sst,'T', 1. )
  397. CALL nemo2cice(sss_m,sss,'T', 1. )
  398. ! x comp and y comp of surface ocean current
  399. ! U point to F point
  400. DO jj=1,jpjm1
  401. DO ji=1,jpi
  402. ztmp(ji,jj)=0.5*(ssu_m(ji,jj)+ssu_m(ji,jj+1))*fmask(ji,jj,1)
  403. ENDDO
  404. ENDDO
  405. CALL nemo2cice(ztmp,uocn,'F', -1. )
  406. ! V point to F point
  407. DO jj=1,jpj
  408. DO ji=1,jpim1
  409. ztmp(ji,jj)=0.5*(ssv_m(ji,jj)+ssv_m(ji+1,jj))*fmask(ji,jj,1)
  410. ENDDO
  411. ENDDO
  412. CALL nemo2cice(ztmp,vocn,'F', -1. )
  413. IF( nn_ice_embd == 2 ) THEN !== embedded sea ice: compute representative ice top surface ==!
  414. !
  415. ! average interpolation coeff as used in dynspg = (1/nn_fsbc) * {SUM[n/nn_fsbc], n=0,nn_fsbc-1}
  416. ! = (1/nn_fsbc)^2 * {SUM[n], n=0,nn_fsbc-1}
  417. zintn = REAL( nn_fsbc - 1 ) / REAL( nn_fsbc ) * 0.5_wp
  418. !
  419. ! average interpolation coeff as used in dynspg = (1/nn_fsbc) * {SUM[1-n/nn_fsbc], n=0,nn_fsbc-1}
  420. ! = (1/nn_fsbc)^2 * (nn_fsbc^2 - {SUM[n], n=0,nn_fsbc-1})
  421. zintb = REAL( nn_fsbc + 1 ) / REAL( nn_fsbc ) * 0.5_wp
  422. !
  423. zpice(:,:) = ssh_m(:,:) + ( zintn * snwice_mass(:,:) + zintb * snwice_mass_b(:,:) ) * r1_rau0
  424. !
  425. !
  426. ELSE !== non-embedded sea ice: use ocean surface for slope calculation ==!
  427. zpice(:,:) = ssh_m(:,:)
  428. ENDIF
  429. ! x comp and y comp of sea surface slope (on F points)
  430. ! T point to F point
  431. DO jj=1,jpjm1
  432. DO ji=1,jpim1
  433. ztmp(ji,jj)=0.5 * ( (zpice(ji+1,jj )-zpice(ji,jj ))/e1u(ji,jj ) &
  434. + (zpice(ji+1,jj+1)-zpice(ji,jj+1))/e1u(ji,jj+1) ) &
  435. * fmask(ji,jj,1)
  436. ENDDO
  437. ENDDO
  438. CALL nemo2cice(ztmp,ss_tltx,'F', -1. )
  439. ! T point to F point
  440. DO jj=1,jpjm1
  441. DO ji=1,jpim1
  442. ztmp(ji,jj)=0.5 * ( (zpice(ji ,jj+1)-zpice(ji ,jj))/e2v(ji ,jj) &
  443. + (zpice(ji+1,jj+1)-zpice(ji+1,jj))/e2v(ji+1,jj) ) &
  444. * fmask(ji,jj,1)
  445. ENDDO
  446. ENDDO
  447. CALL nemo2cice(ztmp,ss_tlty,'F', -1. )
  448. CALL wrk_dealloc( jpi,jpj, ztmp, zpice )
  449. CALL wrk_dealloc( jpi,jpj,ncat, ztmpn )
  450. !
  451. IF( nn_timing == 1 ) CALL timing_stop('cice_sbc_in')
  452. !
  453. END SUBROUTINE cice_sbc_in
  454. SUBROUTINE cice_sbc_out (kt,ksbc)
  455. !!---------------------------------------------------------------------
  456. !! *** ROUTINE cice_sbc_out ***
  457. !! ** Purpose: Get fields from CICE and set surface fields for NEMO
  458. !!---------------------------------------------------------------------
  459. INTEGER, INTENT( in ) :: kt ! ocean time step
  460. INTEGER, INTENT( in ) :: ksbc ! surface forcing type
  461. INTEGER :: ji, jj, jl ! dummy loop indices
  462. REAL(wp), DIMENSION(:,:), POINTER :: ztmp1, ztmp2
  463. !!---------------------------------------------------------------------
  464. IF( nn_timing == 1 ) CALL timing_start('cice_sbc_out')
  465. !
  466. CALL wrk_alloc( jpi,jpj, ztmp1, ztmp2 )
  467. IF( kt == nit000 ) THEN
  468. IF(lwp) WRITE(numout,*)'cice_sbc_out'
  469. ENDIF
  470. ! x comp of ocean-ice stress
  471. CALL cice2nemo(strocnx,ztmp1,'F', -1. )
  472. ss_iou(:,:)=0.0
  473. ! F point to U point
  474. DO jj=2,jpjm1
  475. DO ji=2,jpim1
  476. ss_iou(ji,jj) = 0.5 * ( ztmp1(ji,jj-1) + ztmp1(ji,jj) ) * umask(ji,jj,1)
  477. ENDDO
  478. ENDDO
  479. CALL lbc_lnk( ss_iou , 'U', -1. )
  480. ! y comp of ocean-ice stress
  481. CALL cice2nemo(strocny,ztmp1,'F', -1. )
  482. ss_iov(:,:)=0.0
  483. ! F point to V point
  484. DO jj=1,jpjm1
  485. DO ji=2,jpim1
  486. ss_iov(ji,jj) = 0.5 * ( ztmp1(ji-1,jj) + ztmp1(ji,jj) ) * vmask(ji,jj,1)
  487. ENDDO
  488. ENDDO
  489. CALL lbc_lnk( ss_iov , 'V', -1. )
  490. ! x and y comps of surface stress
  491. ! Combine wind stress and ocean-ice stress
  492. ! [Note that fr_iu hasn't yet been updated, so still from start of CICE timestep]
  493. ! strocnx and strocny already weighted by ice fraction in CICE so not done here
  494. utau(:,:)=(1.0-fr_iu(:,:))*utau(:,:)-ss_iou(:,:)
  495. vtau(:,:)=(1.0-fr_iv(:,:))*vtau(:,:)-ss_iov(:,:)
  496. ! Also need ice/ocean stress on T points so that taum can be updated
  497. ! This interpolation is already done in CICE so best to use those values
  498. CALL cice2nemo(strocnxT,ztmp1,'T',-1.)
  499. CALL cice2nemo(strocnyT,ztmp2,'T',-1.)
  500. ! Update taum with modulus of ice-ocean stress
  501. ! strocnxT and strocnyT are not weighted by ice fraction in CICE so must be done here
  502. taum(:,:)=(1.0-fr_i(:,:))*taum(:,:)+fr_i(:,:)*SQRT(ztmp1**2. + ztmp2**2.)
  503. ! Freshwater fluxes
  504. IF (ksbc == jp_flx) THEN
  505. ! Note that emp from the forcing files is evap*(1-aice)-(tprecip-aice*sprecip)
  506. ! What we want here is evap*(1-aice)-tprecip*(1-aice) hence manipulation below
  507. ! Not ideal since aice won't be the same as in the atmosphere.
  508. ! Better to use evap and tprecip? (but for now don't read in evap in this case)
  509. emp(:,:) = emp(:,:)+fr_i(:,:)*(tprecip(:,:)-sprecip(:,:))
  510. ELSE IF (ksbc == jp_core) THEN
  511. emp(:,:) = (1.0-fr_i(:,:))*emp(:,:)
  512. ELSE IF (ksbc == jp_purecpl) THEN
  513. ! emp_tot is set in sbc_cpl_ice_flx (called from cice_sbc_in above)
  514. ! This is currently as required with the coupling fields from the UM atmosphere
  515. emp(:,:) = emp_tot(:,:)+tprecip(:,:)*fr_i(:,:)
  516. ENDIF
  517. #if defined key_cice4
  518. CALL cice2nemo(fresh_gbm,ztmp1,'T', 1. )
  519. CALL cice2nemo(fsalt_gbm,ztmp2,'T', 1. )
  520. #else
  521. CALL cice2nemo(fresh_ai,ztmp1,'T', 1. )
  522. CALL cice2nemo(fsalt_ai,ztmp2,'T', 1. )
  523. #endif
  524. ! Check to avoid unphysical expression when ice is forming (ztmp1 negative)
  525. ! Otherwise we are effectively allowing ice of higher salinity than the ocean to form
  526. ! which has to be compensated for by the ocean salinity potentially going negative
  527. ! This check breaks conservation but seems reasonable until we have prognostic ice salinity
  528. ! Note the 1000.0 below is to convert from kg salt to g salt (needed for PSU)
  529. WHERE (ztmp1(:,:).lt.0.0) ztmp2(:,:)=MAX(ztmp2(:,:),ztmp1(:,:)*sss_m(:,:)/1000.0)
  530. sfx(:,:)=ztmp2(:,:)*1000.0
  531. emp(:,:)=emp(:,:)-ztmp1(:,:)
  532. fmmflx(:,:) = ztmp1(:,:) !!Joakim edit
  533. CALL lbc_lnk( emp , 'T', 1. )
  534. CALL lbc_lnk( sfx , 'T', 1. )
  535. ! Solar penetrative radiation and non solar surface heat flux
  536. ! Scale qsr and qns according to ice fraction (bulk formulae only)
  537. IF (ksbc == jp_core) THEN
  538. qsr(:,:)=qsr(:,:)*(1.0-fr_i(:,:))
  539. qns(:,:)=qns(:,:)*(1.0-fr_i(:,:))
  540. ENDIF
  541. ! Take into account snow melting except for fully coupled when already in qns_tot
  542. IF (ksbc == jp_purecpl) THEN
  543. qsr(:,:)= qsr_tot(:,:)
  544. qns(:,:)= qns_tot(:,:)
  545. ELSE
  546. qns(:,:)= qns(:,:)-sprecip(:,:)*Lfresh*(1.0-fr_i(:,:))
  547. ENDIF
  548. ! Now add in ice / snow related terms
  549. ! [fswthru will be zero unless running with calc_Tsfc=T in CICE]
  550. #if defined key_cice4
  551. CALL cice2nemo(fswthru_gbm,ztmp1,'T', 1. )
  552. #else
  553. CALL cice2nemo(fswthru_ai,ztmp1,'T', 1. )
  554. #endif
  555. qsr(:,:)=qsr(:,:)+ztmp1(:,:)
  556. CALL lbc_lnk( qsr , 'T', 1. )
  557. DO jj=1,jpj
  558. DO ji=1,jpi
  559. nfrzmlt(ji,jj)=MAX(nfrzmlt(ji,jj),0.0)
  560. ENDDO
  561. ENDDO
  562. #if defined key_cice4
  563. CALL cice2nemo(fhocn_gbm,ztmp1,'T', 1. )
  564. #else
  565. CALL cice2nemo(fhocn_ai,ztmp1,'T', 1. )
  566. #endif
  567. qns(:,:)=qns(:,:)+nfrzmlt(:,:)+ztmp1(:,:)
  568. CALL lbc_lnk( qns , 'T', 1. )
  569. ! Prepare for the following CICE time-step
  570. CALL cice2nemo(aice,fr_i,'T', 1. )
  571. IF ( (ksbc == jp_flx).OR.(ksbc == jp_purecpl) ) THEN
  572. DO jl=1,ncat
  573. CALL cice2nemo(aicen(:,:,jl,:),a_i(:,:,jl), 'T', 1. )
  574. ENDDO
  575. ENDIF
  576. ! T point to U point
  577. ! T point to V point
  578. DO jj=1,jpjm1
  579. DO ji=1,jpim1
  580. fr_iu(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji+1,jj))*umask(ji,jj,1)
  581. fr_iv(ji,jj)=0.5*(fr_i(ji,jj)+fr_i(ji,jj+1))*vmask(ji,jj,1)
  582. ENDDO
  583. ENDDO
  584. CALL lbc_lnk ( fr_iu , 'U', 1. )
  585. CALL lbc_lnk ( fr_iv , 'V', 1. )
  586. ! ! embedded sea ice
  587. IF( nn_ice_embd /= 0 ) THEN ! mass exchanges between ice and ocean (case 1 or 2) set the snow+ice mass
  588. CALL cice2nemo(vsno(:,:,:),ztmp1,'T', 1. )
  589. CALL cice2nemo(vice(:,:,:),ztmp2,'T', 1. )
  590. snwice_mass (:,:) = ( rhosn * ztmp1(:,:) + rhoic * ztmp2(:,:) )
  591. snwice_mass_b(:,:) = snwice_mass(:,:)
  592. snwice_fmass (:,:) = ( snwice_mass(:,:) - snwice_mass_b(:,:) ) / dt
  593. ENDIF
  594. ! Release work space
  595. CALL wrk_dealloc( jpi,jpj, ztmp1, ztmp2 )
  596. !
  597. IF( nn_timing == 1 ) CALL timing_stop('cice_sbc_out')
  598. !
  599. END SUBROUTINE cice_sbc_out
  600. SUBROUTINE cice_sbc_hadgam( kt )
  601. !!---------------------------------------------------------------------
  602. !! *** ROUTINE cice_sbc_hadgam ***
  603. !! ** Purpose: Prepare fields needed to pass to HadGAM3 atmosphere
  604. !!
  605. !!
  606. INTEGER, INTENT( in ) :: kt ! ocean time step
  607. !!---------------------------------------------------------------------
  608. INTEGER :: jl ! dummy loop index
  609. INTEGER :: ierror
  610. IF( nn_timing == 1 ) CALL timing_start('cice_sbc_hadgam')
  611. !
  612. IF( kt == nit000 ) THEN
  613. IF(lwp) WRITE(numout,*)'cice_sbc_hadgam'
  614. IF( sbc_cpl_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'sbc_cpl_alloc : unable to allocate arrays' )
  615. ENDIF
  616. ! ! =========================== !
  617. ! ! Prepare Coupling fields !
  618. ! ! =========================== !
  619. ! x and y comp of ice velocity
  620. CALL cice2nemo(uvel,u_ice,'F', -1. )
  621. CALL cice2nemo(vvel,v_ice,'F', -1. )
  622. ! Ice concentration (CO_1) = a_i calculated at end of cice_sbc_out
  623. ! Snow and ice thicknesses (CO_2 and CO_3)
  624. DO jl = 1,ncat
  625. CALL cice2nemo(vsnon(:,:,jl,:),ht_s(:,:,jl),'T', 1. )
  626. CALL cice2nemo(vicen(:,:,jl,:),ht_i(:,:,jl),'T', 1. )
  627. ENDDO
  628. !
  629. IF( nn_timing == 1 ) CALL timing_stop('cice_sbc_hadgam')
  630. !
  631. END SUBROUTINE cice_sbc_hadgam
  632. SUBROUTINE cice_sbc_final
  633. !!---------------------------------------------------------------------
  634. !! *** ROUTINE cice_sbc_final ***
  635. !! ** Purpose: Finalize CICE
  636. !!---------------------------------------------------------------------
  637. IF(lwp) WRITE(numout,*)'cice_sbc_final'
  638. CALL CICE_Finalize
  639. END SUBROUTINE cice_sbc_final
  640. SUBROUTINE cice_sbc_force (kt)
  641. !!---------------------------------------------------------------------
  642. !! *** ROUTINE cice_sbc_force ***
  643. !! ** Purpose : Provide CICE forcing from files
  644. !!
  645. !!---------------------------------------------------------------------
  646. !! ** Method : READ monthly flux file in NetCDF files
  647. !!
  648. !! snowfall
  649. !! rainfall
  650. !! sublimation rate
  651. !! topmelt (category)
  652. !! botmelt (category)
  653. !!
  654. !! History :
  655. !!----------------------------------------------------------------------
  656. !! * Modules used
  657. USE iom
  658. !! * arguments
  659. INTEGER, INTENT( in ) :: kt ! ocean time step
  660. INTEGER :: ierror ! return error code
  661. INTEGER :: ifpr ! dummy loop index
  662. !!
  663. CHARACTER(len=100) :: cn_dir ! Root directory for location of CICE forcing files
  664. TYPE(FLD_N), DIMENSION(jpfld) :: slf_i ! array of namelist informations on the fields to read
  665. TYPE(FLD_N) :: sn_snow, sn_rain, sn_sblm ! informations about the fields to be read
  666. TYPE(FLD_N) :: sn_top1, sn_top2, sn_top3, sn_top4, sn_top5
  667. TYPE(FLD_N) :: sn_bot1, sn_bot2, sn_bot3, sn_bot4, sn_bot5
  668. !!
  669. NAMELIST/namsbc_cice/ cn_dir, sn_snow, sn_rain, sn_sblm, &
  670. & sn_top1, sn_top2, sn_top3, sn_top4, sn_top5, &
  671. & sn_bot1, sn_bot2, sn_bot3, sn_bot4, sn_bot5
  672. INTEGER :: ios
  673. !!---------------------------------------------------------------------
  674. ! ! ====================== !
  675. IF( kt == nit000 ) THEN ! First call kt=nit000 !
  676. ! ! ====================== !
  677. ! namsbc_cice is not yet in the reference namelist
  678. ! set file information (default values)
  679. cn_dir = './' ! directory in which the model is executed
  680. ! (NB: frequency positive => hours, negative => months)
  681. ! ! file ! frequency ! variable ! time intep ! clim ! 'yearly' or ! weights ! rotation ! landmask
  682. ! ! name ! (hours) ! name ! (T/F) ! (T/F) ! 'monthly' ! filename ! pairs ! file
  683. sn_snow = FLD_N( 'snowfall_1m' , -1. , 'snowfall' , .true. , .true. , ' yearly' , '' , '' , '' )
  684. sn_rain = FLD_N( 'rainfall_1m' , -1. , 'rainfall' , .true. , .true. , ' yearly' , '' , '' , '' )
  685. sn_sblm = FLD_N( 'sublim_1m' , -1. , 'sublim' , .true. , .true. , ' yearly' , '' , '' , '' )
  686. sn_top1 = FLD_N( 'topmeltn1_1m' , -1. , 'topmeltn1' , .true. , .true. , ' yearly' , '' , '' , '' )
  687. sn_top2 = FLD_N( 'topmeltn2_1m' , -1. , 'topmeltn2' , .true. , .true. , ' yearly' , '' , '' , '' )
  688. sn_top3 = FLD_N( 'topmeltn3_1m' , -1. , 'topmeltn3' , .true. , .true. , ' yearly' , '' , '' , '' )
  689. sn_top4 = FLD_N( 'topmeltn4_1m' , -1. , 'topmeltn4' , .true. , .true. , ' yearly' , '' , '' , '' )
  690. sn_top5 = FLD_N( 'topmeltn5_1m' , -1. , 'topmeltn5' , .true. , .true. , ' yearly' , '' , '' , '' )
  691. sn_bot1 = FLD_N( 'botmeltn1_1m' , -1. , 'botmeltn1' , .true. , .true. , ' yearly' , '' , '' , '' )
  692. sn_bot2 = FLD_N( 'botmeltn2_1m' , -1. , 'botmeltn2' , .true. , .true. , ' yearly' , '' , '' , '' )
  693. sn_bot3 = FLD_N( 'botmeltn3_1m' , -1. , 'botmeltn3' , .true. , .true. , ' yearly' , '' , '' , '' )
  694. sn_bot4 = FLD_N( 'botmeltn4_1m' , -1. , 'botmeltn4' , .true. , .true. , ' yearly' , '' , '' , '' )
  695. sn_bot5 = FLD_N( 'botmeltn5_1m' , -1. , 'botmeltn5' , .true. , .true. , ' yearly' , '' , '' , '' )
  696. REWIND( numnam_ref ) ! Namelist namsbc_cice in reference namelist :
  697. READ ( numnam_ref, namsbc_cice, IOSTAT = ios, ERR = 901)
  698. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cice in reference namelist', lwp )
  699. REWIND( numnam_cfg ) ! Namelist namsbc_cice in configuration namelist : Parameters of the run
  700. READ ( numnam_cfg, namsbc_cice, IOSTAT = ios, ERR = 902 )
  701. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_cice in configuration namelist', lwp )
  702. IF(lwm) WRITE ( numond, namsbc_cice )
  703. ! store namelist information in an array
  704. slf_i(jp_snow) = sn_snow ; slf_i(jp_rain) = sn_rain ; slf_i(jp_sblm) = sn_sblm
  705. slf_i(jp_top1) = sn_top1 ; slf_i(jp_top2) = sn_top2 ; slf_i(jp_top3) = sn_top3
  706. slf_i(jp_top4) = sn_top4 ; slf_i(jp_top5) = sn_top5 ; slf_i(jp_bot1) = sn_bot1
  707. slf_i(jp_bot2) = sn_bot2 ; slf_i(jp_bot3) = sn_bot3 ; slf_i(jp_bot4) = sn_bot4
  708. slf_i(jp_bot5) = sn_bot5
  709. ! set sf structure
  710. ALLOCATE( sf(jpfld), STAT=ierror )
  711. IF( ierror > 0 ) THEN
  712. CALL ctl_stop( 'cice_sbc_force: unable to allocate sf structure' ) ; RETURN
  713. ENDIF
  714. DO ifpr= 1, jpfld
  715. ALLOCATE( sf(ifpr)%fnow(jpi,jpj,1) )
  716. ALLOCATE( sf(ifpr)%fdta(jpi,jpj,1,2) )
  717. END DO
  718. ! fill sf with slf_i and control print
  719. CALL fld_fill( sf, slf_i, cn_dir, 'cice_sbc_force', 'flux formulation for CICE', 'namsbc_cice' )
  720. !
  721. ENDIF
  722. CALL fld_read( kt, nn_fsbc, sf ) ! Read input fields and provides the
  723. ! ! input fields at the current time-step
  724. ! set the fluxes from read fields
  725. sprecip(:,:) = sf(jp_snow)%fnow(:,:,1)
  726. tprecip(:,:) = sf(jp_snow)%fnow(:,:,1)+sf(jp_rain)%fnow(:,:,1)
  727. ! May be better to do this conversion somewhere else
  728. qla_ice(:,:,1) = -Lsub*sf(jp_sblm)%fnow(:,:,1)
  729. topmelt(:,:,1) = sf(jp_top1)%fnow(:,:,1)
  730. topmelt(:,:,2) = sf(jp_top2)%fnow(:,:,1)
  731. topmelt(:,:,3) = sf(jp_top3)%fnow(:,:,1)
  732. topmelt(:,:,4) = sf(jp_top4)%fnow(:,:,1)
  733. topmelt(:,:,5) = sf(jp_top5)%fnow(:,:,1)
  734. botmelt(:,:,1) = sf(jp_bot1)%fnow(:,:,1)
  735. botmelt(:,:,2) = sf(jp_bot2)%fnow(:,:,1)
  736. botmelt(:,:,3) = sf(jp_bot3)%fnow(:,:,1)
  737. botmelt(:,:,4) = sf(jp_bot4)%fnow(:,:,1)
  738. botmelt(:,:,5) = sf(jp_bot5)%fnow(:,:,1)
  739. ! control print (if less than 100 time-step asked)
  740. IF( nitend-nit000 <= 100 .AND. lwp ) THEN
  741. WRITE(numout,*)
  742. WRITE(numout,*) ' read forcing fluxes for CICE OK'
  743. CALL FLUSH(numout)
  744. ENDIF
  745. END SUBROUTINE cice_sbc_force
  746. SUBROUTINE nemo2cice( pn, pc, cd_type, psgn)
  747. !!---------------------------------------------------------------------
  748. !! *** ROUTINE nemo2cice ***
  749. !! ** Purpose : Transfer field in NEMO array to field in CICE array.
  750. #if defined key_nemocice_decomp
  751. !!
  752. !! NEMO and CICE PE sub domains are identical, hence
  753. !! there is no need to gather or scatter data from
  754. !! one PE configuration to another.
  755. #else
  756. !! Automatically gather/scatter between
  757. !! different processors and blocks
  758. !! ** Method : A. Ensure all haloes are filled in NEMO field (pn)
  759. !! B. Gather pn into global array (png)
  760. !! C. Map png into CICE global array (pcg)
  761. !! D. Scatter pcg to CICE blocks (pc) + update haloes
  762. #endif
  763. !!---------------------------------------------------------------------
  764. CHARACTER(len=1), INTENT( in ) :: &
  765. cd_type ! nature of pn grid-point
  766. ! ! = T or F gridpoints
  767. REAL(wp), INTENT( in ) :: &
  768. psgn ! control of the sign change
  769. ! ! =-1 , the sign is modified following the type of b.c. used
  770. ! ! = 1 , no sign change
  771. REAL(wp), DIMENSION(jpi,jpj) :: pn
  772. #if !defined key_nemocice_decomp
  773. REAL(wp), DIMENSION(jpiglo,jpjglo) :: png2
  774. REAL (kind=dbl_kind), dimension(nx_global,ny_global) :: pcg
  775. #endif
  776. REAL (kind=dbl_kind), dimension(nx_block,ny_block,max_blocks) :: pc
  777. INTEGER (int_kind) :: &
  778. field_type, &! id for type of field (scalar, vector, angle)
  779. grid_loc ! id for location on horizontal grid
  780. ! (center, NEcorner, Nface, Eface)
  781. INTEGER :: ji, jj, jn ! dummy loop indices
  782. ! A. Ensure all haloes are filled in NEMO field (pn)
  783. CALL lbc_lnk( pn , cd_type, psgn )
  784. #if defined key_nemocice_decomp
  785. ! Copy local domain data from NEMO to CICE field
  786. pc(:,:,1)=0.0
  787. DO jj=2,ny_block-1
  788. DO ji=2,nx_block-1
  789. pc(ji,jj,1)=pn(ji-1+ji_off,jj-1+jj_off)
  790. ENDDO
  791. ENDDO
  792. #else
  793. ! B. Gather pn into global array (png)
  794. IF ( jpnij > 1) THEN
  795. CALL mppsync
  796. CALL mppgather (pn,0,png)
  797. CALL mppsync
  798. ELSE
  799. png(:,:,1)=pn(:,:)
  800. ENDIF
  801. ! C. Map png into CICE global array (pcg)
  802. ! Need to make sure this is robust to changes in NEMO halo rows....
  803. ! (may be OK but not 100% sure)
  804. IF (nproc==0) THEN
  805. ! pcg(:,:)=0.0
  806. DO jn=1,jpnij
  807. DO jj=nldjt(jn),nlejt(jn)
  808. DO ji=nldit(jn),nleit(jn)
  809. png2(ji+nimppt(jn)-1,jj+njmppt(jn)-1)=png(ji,jj,jn)
  810. ENDDO
  811. ENDDO
  812. ENDDO
  813. DO jj=1,ny_global
  814. DO ji=1,nx_global
  815. pcg(ji,jj)=png2(ji+ji_off,jj+jj_off)
  816. ENDDO
  817. ENDDO
  818. ENDIF
  819. #endif
  820. SELECT CASE ( cd_type )
  821. CASE ( 'T' )
  822. grid_loc=field_loc_center
  823. CASE ( 'F' )
  824. grid_loc=field_loc_NEcorner
  825. END SELECT
  826. SELECT CASE ( NINT(psgn) )
  827. CASE ( -1 )
  828. field_type=field_type_vector
  829. CASE ( 1 )
  830. field_type=field_type_scalar
  831. END SELECT
  832. #if defined key_nemocice_decomp
  833. ! Ensure CICE halos are up to date
  834. CALL ice_HaloUpdate (pc, halo_info, grid_loc, field_type)
  835. #else
  836. ! D. Scatter pcg to CICE blocks (pc) + update halos
  837. CALL scatter_global(pc, pcg, 0, distrb_info, grid_loc, field_type)
  838. #endif
  839. END SUBROUTINE nemo2cice
  840. SUBROUTINE cice2nemo ( pc, pn, cd_type, psgn )
  841. !!---------------------------------------------------------------------
  842. !! *** ROUTINE cice2nemo ***
  843. !! ** Purpose : Transfer field in CICE array to field in NEMO array.
  844. #if defined key_nemocice_decomp
  845. !!
  846. !! NEMO and CICE PE sub domains are identical, hence
  847. !! there is no need to gather or scatter data from
  848. !! one PE configuration to another.
  849. #else
  850. !! Automatically deal with scatter/gather between
  851. !! different processors and blocks
  852. !! ** Method : A. Gather CICE blocks (pc) into global array (pcg)
  853. !! B. Map pcg into NEMO global array (png)
  854. !! C. Scatter png into NEMO field (pn) for each processor
  855. !! D. Ensure all haloes are filled in pn
  856. #endif
  857. !!---------------------------------------------------------------------
  858. CHARACTER(len=1), INTENT( in ) :: &
  859. cd_type ! nature of pn grid-point
  860. ! ! = T or F gridpoints
  861. REAL(wp), INTENT( in ) :: &
  862. psgn ! control of the sign change
  863. ! ! =-1 , the sign is modified following the type of b.c. used
  864. ! ! = 1 , no sign change
  865. REAL(wp), DIMENSION(jpi,jpj) :: pn
  866. #if defined key_nemocice_decomp
  867. INTEGER (int_kind) :: &
  868. field_type, & ! id for type of field (scalar, vector, angle)
  869. grid_loc ! id for location on horizontal grid
  870. ! (center, NEcorner, Nface, Eface)
  871. #else
  872. REAL (kind=dbl_kind), dimension(nx_global,ny_global) :: pcg
  873. #endif
  874. REAL (kind=dbl_kind), dimension(nx_block,ny_block,max_blocks) :: pc
  875. INTEGER :: ji, jj, jn ! dummy loop indices
  876. #if defined key_nemocice_decomp
  877. SELECT CASE ( cd_type )
  878. CASE ( 'T' )
  879. grid_loc=field_loc_center
  880. CASE ( 'F' )
  881. grid_loc=field_loc_NEcorner
  882. END SELECT
  883. SELECT CASE ( NINT(psgn) )
  884. CASE ( -1 )
  885. field_type=field_type_vector
  886. CASE ( 1 )
  887. field_type=field_type_scalar
  888. END SELECT
  889. CALL ice_HaloUpdate (pc, halo_info, grid_loc, field_type)
  890. pn(:,:)=0.0
  891. DO jj=1,jpjm1
  892. DO ji=1,jpim1
  893. pn(ji,jj)=pc(ji+1-ji_off,jj+1-jj_off,1)
  894. ENDDO
  895. ENDDO
  896. #else
  897. ! A. Gather CICE blocks (pc) into global array (pcg)
  898. CALL gather_global(pcg, pc, 0, distrb_info)
  899. ! B. Map pcg into NEMO global array (png)
  900. ! Need to make sure this is robust to changes in NEMO halo rows....
  901. ! (may be OK but not spent much time thinking about it)
  902. ! Note that non-existent pcg elements may be used below, but
  903. ! the lbclnk call on pn will replace these with sensible values
  904. IF (nproc==0) THEN
  905. png(:,:,:)=0.0
  906. DO jn=1,jpnij
  907. DO jj=nldjt(jn),nlejt(jn)
  908. DO ji=nldit(jn),nleit(jn)
  909. png(ji,jj,jn)=pcg(ji+nimppt(jn)-1-ji_off,jj+njmppt(jn)-1-jj_off)
  910. ENDDO
  911. ENDDO
  912. ENDDO
  913. ENDIF
  914. ! C. Scatter png into NEMO field (pn) for each processor
  915. IF ( jpnij > 1) THEN
  916. CALL mppsync
  917. CALL mppscatter (png,0,pn)
  918. CALL mppsync
  919. ELSE
  920. pn(:,:)=png(:,:,1)
  921. ENDIF
  922. #endif
  923. ! D. Ensure all haloes are filled in pn
  924. CALL lbc_lnk( pn , cd_type, psgn )
  925. END SUBROUTINE cice2nemo
  926. #else
  927. !!----------------------------------------------------------------------
  928. !! Default option Dummy module NO CICE sea-ice model
  929. !!----------------------------------------------------------------------
  930. !! $Id: sbcice_cice.F90 2544 2015-08-24 09:00:45Z ufla $
  931. CONTAINS
  932. SUBROUTINE sbc_ice_cice ( kt, ksbc ) ! Dummy routine
  933. WRITE(*,*) 'sbc_ice_cice: You should not have seen this print! error?', kt
  934. END SUBROUTINE sbc_ice_cice
  935. SUBROUTINE cice_sbc_init (ksbc) ! Dummy routine
  936. WRITE(*,*) 'cice_sbc_init: You should not have seen this print! error?'
  937. END SUBROUTINE cice_sbc_init
  938. SUBROUTINE cice_sbc_final ! Dummy routine
  939. WRITE(*,*) 'cice_sbc_final: You should not have seen this print! error?'
  940. END SUBROUTINE cice_sbc_final
  941. #endif
  942. !!======================================================================
  943. END MODULE sbcice_cice