MODULE domain !!============================================================================== !! *** MODULE domain *** !! Ocean initialization : domain initialization !!============================================================================== !!---------------------------------------------------------------------- !! dom_init : initialize the space and time domain !! dom_nam : read and contral domain namelists !! dom_ctl : control print for the ocean domain !!---------------------------------------------------------------------- !! * Modules used USE oce ! USE dom_oce ! ocean space and time domain USE phycst ! physical constants USE in_out_manager ! I/O manager USE ice_oce ! ice variables USE blk_oce ! bulk variables USE flxrnf ! runoffs USE daymod ! calendar USE lib_mpp ! distributed memory computing library USE domhgr ! domain: set the horizontal mesh USE domzgr ! domain: set the vertical mesh USE domstp ! domain: set the time-step USE dommsk ! domain: set the mask system USE domwri ! domain: write the meshmask file USE closea ! closed sea or lake (dom_clo routine) USE domvvl ! variable volume IMPLICIT NONE PRIVATE !! * Routine accessibility PUBLIC dom_init ! called by opa.F90 !! * Substitutions # include "domzgr_substitute.h90" !!---------------------------------------------------------------------- !! OPA 9.0 , LOCEAN-IPSL (2005) !! $Header$ !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt !!---------------------------------------------------------------------- CONTAINS SUBROUTINE dom_init !!---------------------------------------------------------------------- !! *** ROUTINE dom_init *** !! !! ** Purpose : Domain initialization. Call the routines that are !! required to create the arrays which define the space and time !! domain of the ocean model. !! !! ** Method : !! - dom_msk: compute the masks from the bathymetry file !! - dom_hgr: compute or read the horizontal grid-point position and !! scale factors, and the coriolis factor !! - dom_zgr: define the vertical coordinate system and the bathymetry !! - dom_stp: defined the model time step !! - dom_wri: create the meshmask file if nmsh=1 !! !! History : !! ! 90-10 (C. Levy - G. Madec) Original code !! ! 91-11 (G. Madec) !! ! 92-01 (M. Imbard) insert time step initialization !! ! 96-06 (G. Madec) generalized vertical coordinate !! ! 97-02 (G. Madec) creation of domwri.F !! ! 01-05 (E.Durand - G. Madec) insert closed sea !! 8.5 ! 02-08 (G. Madec) F90: Free form and module !! 9.0 ! 05-11 (V. Garnier) Surface pressure gradient organization !!---------------------------------------------------------------------- !! * Local declarations INTEGER :: jk ! dummy loop argument INTEGER :: iconf = 0 ! temporary integers !!---------------------------------------------------------------------- IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'dom_init : domain initialization' WRITE(numout,*) '~~~~~~~~' ENDIF CALL dom_nam ! read namelist ( namrun, namdom, namcla ) CALL dom_clo ! Closed seas and lake CALL dom_hgr ! Horizontal mesh CALL dom_zgr ! Vertical mesh and bathymetry CALL dom_msk ! Masks IF( lk_vvl ) CALL dom_vvl_ini ! Vertical variable mesh ! Local depth or Inverse of the local depth of the water column at u- and v-points ! ------------------------------ ! Ocean depth at U- and V-points hu(:,:) = 0. hv(:,:) = 0. DO jk = 1, jpk hu(:,:) = hu(:,:) + fse3u(:,:,jk) * umask(:,:,jk) hv(:,:) = hv(:,:) + fse3v(:,:,jk) * vmask(:,:,jk) END DO ! Inverse of the local depth hur(:,:) = fse3u(:,:,1) ! Lower bound : thickness of the first model level hvr(:,:) = fse3v(:,:,1) DO jk = 2, jpk ! Sum of the vertical scale factors hur(:,:) = hur(:,:) + fse3u(:,:,jk) * umask(:,:,jk) hvr(:,:) = hvr(:,:) + fse3v(:,:,jk) * vmask(:,:,jk) END DO ! Compute and mask the inverse of the local depth hur(:,:) = 1. / hur(:,:) * umask(:,:,1) hvr(:,:) = 1. / hvr(:,:) * vmask(:,:,1) CALL dom_stp ! Time step IF( nmsh /= 0 ) CALL dom_wri ! Create a domain file IF( .NOT.ln_rstart ) CALL dom_ctl ! Domain control END SUBROUTINE dom_init SUBROUTINE dom_nam !!---------------------------------------------------------------------- !! *** ROUTINE dom_nam *** !! !! ** Purpose : read domaine namelists and print the variables. !! !! ** input : - namrun namelist !! - namdom namelist !! - namcla namelist !! !! History : !! 9.0 ! 03-08 (G. Madec) Original code !!---------------------------------------------------------------------- !! * Modules used USE ioipsl NAMELIST/namrun/ no , cexper , ln_rstart , nrstdt , nit000, & & nitend, ndate0 , nleapy , ninist , nstock, & & nwrite, nrunoff , ln_dimgnnn NAMELIST/namdom/ ntopo , e3zps_min, e3zps_rat, ngrid , nmsh , & & nacc , atfp , rdt , rdtmin , rdtmax, & & rdth , rdtbt , nfice , nfbulk , nclosea NAMELIST/namcla/ n_cla !!---------------------------------------------------------------------- IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) 'dom_nam : domain initialization through namelist read' WRITE(numout,*) '~~~~~~~ ' ENDIF ! Namelist namrun : parameters of the run REWIND( numnam ) READ ( numnam, namrun ) IF(lwp) THEN WRITE(numout,*) ' Namelist namrun' WRITE(numout,*) ' job number no = ', no WRITE(numout,*) ' experiment name for output cexper = ', cexper WRITE(numout,*) ' restart logical ln_rstart = ', ln_rstart WRITE(numout,*) ' control of time step nrstdt = ', nrstdt WRITE(numout,*) ' number of the first time step nit000 = ', nit000 WRITE(numout,*) ' number of the last time step nitend = ', nitend WRITE(numout,*) ' initial calendar date aammjj ndate0 = ', ndate0 WRITE(numout,*) ' leap year calendar (0/1) nleapy = ', nleapy WRITE(numout,*) ' initial state output ninist = ', ninist WRITE(numout,*) ' frequency of restart file nstock = ', nstock WRITE(numout,*) ' frequency of output file nwrite = ', nwrite WRITE(numout,*) ' runoff option nrunoff = ', nrunoff WRITE(numout,*) ' multi file dimgout ln_dimgnnn = ', ln_dimgnnn ENDIF ndastp = ndate0 ! Assign initial date to current date ! ... Control of output frequency IF ( nstock == 0 .OR. nstock > nitend - nit000 + 1 ) THEN WRITE(ctmp1,*) ' nstock = ', nstock, ' it is forced to ', nitend - nit000 + 1 CALL ctl_warn( ctmp1 ) nstock = nitend - nit000 + 1 ENDIF IF ( nwrite == 0 ) THEN WRITE(ctmp1,*) ' nwrite = ', nwrite, ' it is forced to ', nitend CALL ctl_warn( ctmp1 ) nwrite = nitend ENDIF #if defined key_agrif if ( Agrif_Root() ) then #endif SELECT CASE ( nleapy ) ! Choose calendar for IOIPSL CASE ( 1 ) CALL ioconf_calendar('gregorian') IF(lwp) WRITE(numout,*) ' The IOIPSL calendar is "gregorian", i.e. leap year' CASE ( 0 ) CALL ioconf_calendar('noleap') IF(lwp) WRITE(numout,*) ' The IOIPSL calendar is "noleap", i.e. no leap year' CASE ( 30 ) CALL ioconf_calendar('360d') IF(lwp) WRITE(numout,*) ' The IOIPSL calendar is "360d", i.e. 360 days in a year' END SELECT #if defined key_agrif endif #endif SELECT CASE ( nleapy ) ! year=raajj*days day=rjjhh*hours hour=rhhmm*minutes etc ... CASE ( 1 ) raajj = 365.25 raass = raajj * rjjss rmoss = raass/raamo CASE ( 0 ) raajj = 365. raass = raajj * rjjss rmoss = raass/raamo CASE DEFAULT raajj = FLOAT( nleapy ) * raamo raass = raajj * rjjss rmoss = FLOAT( nleapy ) * rjjss END SELECT IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) ' nb of days per year raajj = ', raajj,' days' WRITE(numout,*) ' nb of seconds per year raass = ', raass, ' s' WRITE(numout,*) ' nb of seconds per month rmoss = ', rmoss, ' s' ENDIF ! Namelist namdom : space/time domain (bathymetry, mesh, timestep) REWIND( numnam ) READ ( numnam, namdom ) IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) ' Namelist namdom' WRITE(numout,*) ' flag read/compute bathymetry ntopo = ', ntopo WRITE(numout,*) ' minimum thickness of partial e3zps_min = ', e3zps_min, ' (m)' WRITE(numout,*) ' step level e3zps_rat = ', e3zps_rat WRITE(numout,*) ' flag read/compute coordinates ngrid = ', ngrid WRITE(numout,*) ' flag write mesh/mask file(s) nmsh = ', nmsh WRITE(numout,*) ' = 0 no file created ' WRITE(numout,*) ' = 1 mesh_mask ' WRITE(numout,*) ' = 2 mesh and mask ' WRITE(numout,*) ' = 3 mesh_hgr, msh_zgr and mask ' WRITE(numout,*) ' acceleration of converge nacc = ', nacc WRITE(numout,*) ' asselin time filter parameter atfp = ', atfp WRITE(numout,*) ' time step rdt = ', rdt WRITE(numout,*) ' minimum time step on tracers rdtmin = ', rdtmin WRITE(numout,*) ' maximum time step on tracers rdtmax = ', rdtmax WRITE(numout,*) ' depth variation tracer step rdth = ', rdth WRITE(numout,*) ' barotropic time step rdtbt = ', rdtbt ENDIF IF( lk_ice_lim ) THEN IF(lwp) WRITE(numout,*) ' ice model coupling frequency nfice = ', nfice IF( MOD( nitend - nit000 + 1, nfice) /= 0 ) THEN WRITE(ctmp1,*) 'experiment length (', nitend - nit000 + 1, ') is NOT a multiple of nfice (', nfice, ')' CALL ctl_stop( ctmp1, 'Impossible to do proper restart files' ) ENDIF IF( MOD( nstock , nfice) /= 0 ) THEN WRITE(ctmp1,*) 'nstock (' , nstock , ') is NOT a multiple of nfice (', nfice, ')' CALL ctl_stop( ctmp1, 'Impossible to do proper restart files' ) ENDIF nfbulk = nfice IF( MOD( rday, nfice*rdt ) /= 0 ) CALL ctl_warn( 'nfice is NOT a multiple of the number of time steps in a day' ) IF(lwp) WRITE(numout,*) ' bulk computation frequency nfbulk = ', nfbulk, ' = nfice if ice model used' IF(lwp) WRITE(numout,*) ' flag closed sea or not nclosea = ', nclosea ENDIF ! Default values n_cla = 0 ! Namelist cross land advection REWIND( numnam ) READ ( numnam, namcla ) IF(lwp) THEN WRITE(numout,*) WRITE(numout,*) ' Namelist namcla' WRITE(numout,*) ' cross land advection n_cla = ',n_cla ENDIF IF( nbit_cmp == 1 .AND. n_cla /= 0 ) THEN CALL ctl_stop( ' Reproductibility tests (nbit_cmp=1) require n_cla = 0' ) END IF END SUBROUTINE dom_nam SUBROUTINE dom_ctl !!---------------------------------------------------------------------- !! *** ROUTINE dom_ctl *** !! !! ** Purpose : Domain control. !! !! ** Method : compute and print extrema of masked scale factors !! !! History : !! 8.5 ! 02-08 (G. Madec) Original code !!---------------------------------------------------------------------- !! * Local declarations INTEGER :: iimi1, ijmi1, iimi2, ijmi2, iima1, ijma1, iima2, ijma2 INTEGER, DIMENSION(2) :: iloc ! REAL(wp) :: ze1min, ze1max, ze2min, ze2max !!---------------------------------------------------------------------- ! Extrema of the scale factors IF(lwp)WRITE(numout,*) IF(lwp)WRITE(numout,*) 'dom_ctl : extrema of the masked scale factors' IF(lwp)WRITE(numout,*) '~~~~~~~' IF (lk_mpp) THEN CALL mpp_minloc( e1t(:,:), tmask(:,:,1), ze1min, iimi1,ijmi1 ) CALL mpp_minloc( e2t(:,:), tmask(:,:,1), ze2min, iimi2,ijmi2 ) CALL mpp_maxloc( e1t(:,:), tmask(:,:,1), ze1max, iima1,ijma1 ) CALL mpp_maxloc( e2t(:,:), tmask(:,:,1), ze2max, iima2,ijma2 ) ELSE ze1min = MINVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) ze2min = MINVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) ze1max = MAXVAL( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) ze2max = MAXVAL( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) iloc = MINLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) iimi1 = iloc(1) + nimpp - 1 ijmi1 = iloc(2) + njmpp - 1 iloc = MINLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) iimi2 = iloc(1) + nimpp - 1 ijmi2 = iloc(2) + njmpp - 1 iloc = MAXLOC( e1t(:,:), mask = tmask(:,:,1) == 1.e0 ) iima1 = iloc(1) + nimpp - 1 ijma1 = iloc(2) + njmpp - 1 iloc = MAXLOC( e2t(:,:), mask = tmask(:,:,1) == 1.e0 ) iima2 = iloc(1) + nimpp - 1 ijma2 = iloc(2) + njmpp - 1 ENDIF IF(lwp) THEN WRITE(numout,"(14x,'e1t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1max, iima1, ijma1 WRITE(numout,"(14x,'e1t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze1min, iimi1, ijmi1 WRITE(numout,"(14x,'e2t maxi: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2max, iima2, ijma2 WRITE(numout,"(14x,'e2t mini: ',1f10.2,' at i = ',i5,' j= ',i5)") ze2min, iimi2, ijmi2 ENDIF END SUBROUTINE dom_ctl !!====================================================================== END MODULE domain