MODULE crs_dom !!====================================================================== !! *** MODULE crs_dom *** !! Declare the coarse grid domain and other public variables !! then allocate them if needed. !!====================================================================== !! History 2012-06 Editing (J. Simeon, G. Madec, C. Ethe) Original code !!---------------------------------------------------------------------- USE dom_oce, ONLY: jpk ! For parameters in par_oce (jperio, lk_vvl) USE par_kind, ONLY: wp USE par_oce, ONLY: jpts IMPLICIT NONE PUBLIC PUBLIC crs_dom_alloc ! Called from crsini.F90 ! Domain variables INTEGER :: jpiglo_crs , & !: 1st dimension of global coarse grid domain jpjglo_crs !: 2nd dimension of global coarse grid domain INTEGER :: jpi_crs , & !: 1st dimension of local coarse grid domain jpj_crs !: 2nd dimension of local coarse grid domain INTEGER :: jpi_full , & !: 1st dimension of local parent grid domain jpj_full !: 2nd dimension of local parent grid domain INTEGER :: jpi_crsm1, jpj_crsm1 !: loop indices INTEGER :: jpiglo_crsm1, jpjglo_crsm1 !: loop indices INTEGER :: nperio_full, nperio_crs !: jperio of parent and coarse grids INTEGER :: npolj_full, npolj_crs !: north fold mark INTEGER :: npiglo_full, npiglo_crs, npiglo !: jpiglo INTEGER :: npjglo_full, npjglo_crs, npjglo !: jpjglo INTEGER :: nlci_full, nlcj_full !: i-, j-dimension of local or sub domain on parent grid INTEGER :: nldi_full, nldj_full !: starting indices of internal sub-domain on parent grid INTEGER :: nlei_full, nlej_full !: ending indices of internal sub-domain on parent grid INTEGER :: nlci_crs, nlcj_crs !: i-, j-dimension of local or sub domain on coarse grid INTEGER :: nldi_crs, nldj_crs !: starting indices of internal sub-domain on coarse grid INTEGER :: nlei_crs, nlej_crs !: ending indices of internal sub-domain on coarse grid INTEGER :: narea_full, narea_crs !: node INTEGER :: jpnij_full, jpnij_crs !: =jpni*jpnj, the pe decomposition INTEGER :: jpim1_full, jpjm1_full !: INTEGER :: nimpp_full, njmpp_full !: global position of point (1,1) of subdomain on parent grid INTEGER :: nimpp_crs, njmpp_crs !: set to 1,1 for now . Valid only for monoproc INTEGER, DIMENSION(:), ALLOCATABLE :: mis_crs, mie_crs, mjs_crs, mje_crs ! starting and ending indices of parent subset INTEGER :: mxbinctr, mybinctr ! central point in grid box ! Masks REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: tmask_crs, umask_crs, vmask_crs, fmask_crs REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: tmask_i_crs, rnfmsk_crs ! Scale factors REAL(wp), DIMENSION(:,:), ALLOCATABLE :: e1t_crs, e2t_crs, e1e2t_crs ! horizontal scale factors grid type T REAL(wp), DIMENSION(:,:), ALLOCATABLE :: e1u_crs, e2u_crs ! horizontal scale factors grid type U REAL(wp), DIMENSION(:,:), ALLOCATABLE :: e1v_crs, e2v_crs ! horizontal scale factors grid type V REAL(wp), DIMENSION(:,:), ALLOCATABLE :: e1f_crs, e2f_crs ! horizontal scale factors grid type F REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: e3t_crs, e3u_crs, e3v_crs, e3w_crs REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: fse3t_crs, fse3u_crs, fse3v_crs, fse3w_crs REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: fse3t_n_crs, fse3t_b_crs, fse3t_a_crs ! vertical scale factors ! Coordinates REAL(wp), DIMENSION(:,:), ALLOCATABLE :: gphit_crs, glamt_crs, gphif_crs, glamf_crs REAL(wp), DIMENSION(:,:), ALLOCATABLE :: gphiu_crs, glamu_crs, gphiv_crs, glamv_crs REAL(wp), DIMENSION(:,:), ALLOCATABLE :: ff_crs INTEGER, DIMENSION(:,:), ALLOCATABLE :: mbathy_crs, mbkt_crs, mbku_crs, mbkv_crs REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: gdept_crs, gdepu_crs, gdepv_crs, gdepw_crs ! Weights REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: facsurfv, facsurfu, facvol_t, facvol_w REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: ocean_volume_crs_t, ocean_volume_crs_w REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: crs_surfu_wgt, crs_surfv_wgt, crs_surfw_wgt, crs_volt_wgt ! CRS Namelist INTEGER :: nn_factx = 3 !: reduction factor of x-dimension of the parent grid INTEGER :: nn_facty = 3 !: reduction factor of y-dimension of the parent grid CHARACTER(len=5) :: cn_binref = 'NORTH' !: NORTH = binning starts north fold (equator could be asymmetric) !: EQUAT = binning centers at equator (north fold my have artifacts) !: for even reduction factors, equator placed in bin biased south INTEGER :: nn_fcrs = 3 !: frequence of coarsening INTEGER :: nn_msh_crs = 1 !: Organization of mesh mask output !: 0 = no mesh mask output !: 1 = unified mesh mask output !: 2 = 2 separate mesh mask output !: 3 = 3 separate mesh mask output CHARACTER(len=11) :: cn_ocerstcrs !: root name of restart files for coarsened variables ! Grid reduction factors REAL(wp) :: rfactx_r !: inverse of x-dim reduction factor REAL(wp) :: rfacty_r !: inverse of y-dim reduction factor REAL(wp) :: rfactxy !! Horizontal grid parameters for domhgr !! ===================================== INTEGER :: nphgr_msh_crs = 0 !: type of horizontal mesh ! ! = 0 curvilinear coordinate on the sphere read in coordinate.nc ! ! = 1 geographical mesh on the sphere with regular grid-spacing ! ! = 2 f-plane with regular grid-spacing ! ! = 3 beta-plane with regular grid-spacing ! ! = 4 Mercator grid with T/U point at the equator ! Physical and dynamical ocean fields for output or passing to TOP, time-mean fields ! REAL(wp), DIMENSION(:,:,:,:), ALLOCATABLE :: tsn_crs, tsb_crs, tsa_crs ! REAL(wp), DIMENSION(:,:,:) , ALLOCATABLE :: un_crs, vn_crs, wn_crs ! REAL(wp), DIMENSION(:,:,:) , ALLOCATABLE :: ut_crs, vt_crs, wt_crs, us_crs, vs_crs, ws_crs ! REAL(wp), DIMENSION(:,:,:) , ALLOCATABLE :: rhd_crs, rhop_crs, hdivn_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: sshb_crs, sshn_crs, ssha_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: sshun_crs, sshvn_crs, sshfn_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: sshub_crs, sshvb_crs, sshua_crs, sshva_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: hu_crs, hv_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: hdivbt_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: ssh_b_crs, ssh_a_crs, ssh_un_crs, ssh_vn_crs ! instantaneous fields ! ! Surface fluxes to pass to TOP ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: utau_crs, vtau_crs, wndm_crs, qsr_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: del_emp_crs, sum_emp_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: emp_crs, emp_b_crs, emps_crs ! REAL(wp), DIMENSION(:,:) , ALLOCATABLE :: rnf_crs, fr_i_crs, h_rnf_crs ! ! Lateral diffusivity (tracers) to pass to TOP ! REAL(wp) :: rldf_crs, rn_aht_0_crs, aht0_crs, ahtb0_crs !#if defined key_traldf_c3d ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) :: ahtt_crs, ahtu_crs, ahtv_crs, ahtw_crs !: 3D coefficients at T-,U-,V-,W-points ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) :: aeiu_crs, aeiv_crs, aeiw_crs !#elif defined key_traldf_c2d ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) :: ahtt_crs, ahtu_crs, ahtv_crs, ahtw_crs !: 2D coefficients at T-,U-,V-,W-points ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) :: aeiu_crs, aeiv_crs, aeiw_crs !#elif defined key_traldf_c1d ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) :: ahtt_crs, ahtu_crs, ahtv_crs, ahtw_crs !: 1D coefficients at T-,U-,V-,W-points ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:) :: aeiu_crs, aeiv_crs, aeiw_crs !#else ! REAL(wp), PUBLIC :: ahtt_crs, ahtu_crs, ahtv_crs, ahtw_crs !: scalar coefficients at T-,U-,V-,W-points !#endif ! Vertical diffusion ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) :: avt_crs !: vert. diffusivity coef. [m2/s] at w-point for temp !# if defined key_zdfddm ! REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:,:) :: avs_crs !: salinity vertical diffusivity coeff. [m2/s] at w-point !# endif ! Mixing and Mixed Layer Depth ! INTEGER, PUBLIC, ALLOCATABLE, DIMENSION(:,:) :: nmln_crs, hmld_crs, hmlp_crs, hmlpt_crs ! Direction of lateral diffusion CONTAINS INTEGER FUNCTION crs_dom_alloc() !!------------------------------------------------------------------- !! *** FUNCTION crs_dom_alloc *** !! ** Purpose : Allocate public crs arrays !!------------------------------------------------------------------- !! Local variables INTEGER, DIMENSION(10) :: ierr ierr(:) = 0 ! Set up bins for coarse grid, horizontal only. ALLOCATE( mis_crs(jpiglo_crs) , mie_crs(jpiglo_crs) , mjs_crs(jpjglo_crs) , mje_crs(jpjglo_crs), STAT=ierr(1) ) ! Set up Mask and Mesh ALLOCATE( tmask_crs(jpi_crs,jpj_crs,jpk) , fmask_crs(jpi_crs,jpj_crs,jpk) , & & umask_crs(jpi_crs,jpj_crs,jpk) , vmask_crs(jpi_crs,jpj_crs,jpk) , STAT=ierr(2)) ALLOCATE( tmask_i_crs(jpi_crs,jpj_crs), rnfmsk_crs(jpi_crs,jpj_crs), STAT=ierr(3) ) ALLOCATE( gphit_crs(jpi_crs,jpj_crs) , glamt_crs(jpi_crs,jpj_crs) , & & gphiu_crs(jpi_crs,jpj_crs) , glamu_crs(jpi_crs,jpj_crs) , & & gphiv_crs(jpi_crs,jpj_crs) , glamv_crs(jpi_crs,jpj_crs) , & & gphif_crs(jpi_crs,jpj_crs) , glamf_crs(jpi_crs,jpj_crs) , & & ff_crs(jpi_crs,jpj_crs) , STAT=ierr(4)) ALLOCATE( e1t_crs(jpi_crs,jpj_crs) , e2t_crs(jpi_crs,jpj_crs) , & & e1u_crs(jpi_crs,jpj_crs) , e2u_crs(jpi_crs,jpj_crs) , & & e1v_crs(jpi_crs,jpj_crs) , e2v_crs(jpi_crs,jpj_crs) , & & e1f_crs(jpi_crs,jpj_crs) , e2f_crs(jpi_crs,jpj_crs) , & & e1e2t_crs(jpi_crs,jpj_crs), STAT=ierr(5)) ALLOCATE( fse3t_crs(jpi_crs,jpj_crs,jpk) , fse3w_crs(jpi_crs,jpj_crs,jpk) , & & fse3u_crs(jpi_crs,jpj_crs,jpk) , fse3v_crs(jpi_crs,jpj_crs,jpk) , & & e3t_crs(jpi_crs,jpj_crs,jpk) , e3w_crs(jpi_crs,jpj_crs,jpk) , & & e3u_crs(jpi_crs,jpj_crs,jpk) , e3v_crs(jpi_crs,jpj_crs,jpk) , & & fse3t_b_crs(jpi_crs,jpj_crs,jpk), fse3t_n_crs(jpi_crs,jpj_crs,jpk),& & fse3t_a_crs(jpi_crs,jpj_crs,jpk), STAT=ierr(6)) ALLOCATE( facsurfv(jpi_crs,jpj_crs,jpk) , facsurfu(jpi_crs,jpj_crs,jpk) , & & facvol_t(jpi_crs,jpj_crs,jpk) , facvol_w(jpi_crs,jpj_crs,jpk) , & & ocean_volume_crs_t(jpi_crs,jpj_crs,jpk) , ocean_volume_crs_w(jpi_crs,jpj_crs,jpk) , STAT=ierr(7)) ALLOCATE( crs_surfu_wgt(jpi_crs,jpj_crs,jpk) , crs_surfv_wgt(jpi_crs,jpj_crs,jpk) , & & crs_surfw_wgt(jpi_crs,jpj_crs,jpk) , crs_volt_wgt(jpi_crs,jpj_crs,jpk) , STAT=ierr(8)) ALLOCATE( mbathy_crs(jpi_crs,jpj_crs) , mbkt_crs(jpi_crs,jpj_crs) , & & mbku_crs(jpi_crs,jpj_crs) , mbkv_crs(jpi_crs,jpj_crs) , STAT=ierr(9)) ALLOCATE( gdept_crs(jpi_crs,jpj_crs,jpk) , gdepu_crs(jpi_crs,jpj_crs,jpk) , & & gdepv_crs(jpi_crs,jpj_crs,jpk) , gdepw_crs(jpi_crs,jpj_crs,jpk) , STAT=ierr(10) ) ! ALLOCATE( un_crs(jpi_crs,jpj_crs,jpk) , vn_crs(jpi_crs,jpj_crs,jpk) , & ! & wn_crs(jpi_crs,jpj_crs,jpk) , & ! & ut_crs(jpi_crs,jpj_crs,jpk) , vt_crs(jpi_crs,jpj_crs,jpk) , & ! & us_crs(jpi_crs,jpj_crs,jpk) , vs_crs(jpi_crs,jpj_crs,jpk) , & ! & wt_crs(jpi_crs,jpj_crs,jpk) , ws_crs(jpi_crs,jpj_crs,jpk) , & ! & rhd_crs(jpi_crs,jpj_crs,jpk) , rhop_crs(jpi_crs,jpj_crs,jpk) , & ! & STAT=ierr(11)) ! ALLOCATE( sshb_crs(jpi_crs,jpj_crs) , sshn_crs(jpi_crs,jpj_crs) , & ! & sshun_crs(jpi_crs,jpj_crs) , sshvn_crs(jpi_crs,jpj_crs) , & ! & sshfn_crs(jpi_crs,jpj_crs) , emp_crs(jpi_crs,jpj_crs) , & ! & del_emp_crs(jpi_crs,jpj_crs), sum_emp_crs(jpi_crs,jpj_crs), & ! & emp_b_crs(jpi_crs,jpj_crs) , emps_crs(jpi_crs,jpj_crs) , & ! & ssh_b_crs(jpi_crs,jpj_crs) , ssh_a_crs(jpi_crs,jpj_crs) , & ! & STAT=ierr(12) ) ! ALLOCATE( tsn_crs(jpi_crs,jpj_crs,jpk,jpts) , tsb_crs(jpi_crs,jpj_crs,jpk,jpts) , & ! & tsa_crs(jpi_crs,jpj_crs,jpk,jpts) , STAT=ierr(13) ) crs_dom_alloc = MAXVAL(ierr) END FUNCTION crs_dom_alloc !!====================================================================== END MODULE crs_dom