New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
sbc_arcmsk.F90 in branches/UKMO/dev_r5518_fa_am_dt_deltadelta_toa/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_fa_am_dt_deltadelta_toa/NEMOGCM/NEMO/OPA_SRC/SBC/sbc_arcmsk.F90 @ 9991

Last change on this file since 9991 was 6913, checked in by kuniko, 8 years ago

Made identical twin to dev_r5518_haney_arctic_mask and commited

File size: 8.2 KB
Line 
1MODULE sbc_arcmsk
2   !!======================================================================
3   !!                       ***  MODULE  sbc_arcmsk  ***
4   !! Ocean forcing:  masking Arctic (based on river runoff)
5   !!=====================================================================
6   !! History :       !
7   !!   NEMO     3.6  ! 2016-03  (K. Yamazaki)
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   sbc_rnf_init_arcmsk : runoffs initialisation
12   !!   rnf_mouth_arcmsk    : set river mouth mask
13   !!----------------------------------------------------------------------
14   USE dom_oce         ! ocean space and time domain
15   USE phycst          ! physical constants
16   USE sbc_oce         ! surface boundary condition variables
17   USE sbcisf          ! PM we could remove it I think
18   USE sbcrnf          ! surface boundary condition : runoffs
19   USE closea          ! closed seas
20   USE fldread         ! read input field at current time step
21   USE in_out_manager  ! I/O manager
22   USE iom             ! I/O module
23   USE lib_mpp         ! MPP library
24   USE eosbn2
25   USE wrk_nemo        ! Memory allocation
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   sbc_rnf_alloc_arcmsk ! routine call in sbcmod module
31   PUBLIC   sbc_rnf_init_arcmsk  ! (PUBLIC for TAM)
32   !                                                     !!* namsbc_rnf namelist *
33   CHARACTER(len=100)         ::   cn_dir          !: Root directory for location of rnf files
34   TYPE(FLD_N)                ::   sn_cnf_arcmsk          !: information about the runoff mouth file to be read
35
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rnfmsk_arcmsk            !: river mouth & Arctic mask (hori.)
37   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   only_arcmsk              !: only Arctic mask (hori.)
38
39   !! * Substitutions 
40#  include "domzgr_substitute.h90" 
41   !!----------------------------------------------------------------------
42   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
43   !! $Id$
44   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
45   !!----------------------------------------------------------------------
46CONTAINS
47
48   INTEGER FUNCTION sbc_rnf_alloc_arcmsk()
49      !!----------------------------------------------------------------------
50      !!                ***  ROUTINE sbc_rnf_alloc_arcmsk  ***
51      !!----------------------------------------------------------------------
52      ALLOCATE( rnfmsk_arcmsk(jpi,jpj)         , STAT=sbc_rnf_alloc_arcmsk )
53      ALLOCATE( only_arcmsk(jpi,jpj)         , STAT=sbc_rnf_alloc_arcmsk )
54         !
55      IF( lk_mpp            )   CALL mpp_sum ( sbc_rnf_alloc_arcmsk )
56      IF( sbc_rnf_alloc_arcmsk > 0 )   CALL ctl_warn('sbc_rnf_alloc_arcmsk: allocation of arrays failed')
57   END FUNCTION sbc_rnf_alloc_arcmsk
58
59
60   SUBROUTINE sbc_rnf_init_arcmsk
61      !!----------------------------------------------------------------------
62      !!                  ***  ROUTINE sbc_rnf_init_arcmsk  ***
63      !!
64      !! ** Purpose :   Initialisation of the runoffs if (ln_rnf_arcmsk=T)
65      !!
66      !! ** Method  : - read the runoff namsbc_rnf_arcmsk namelist
67      !!
68      !! ** Action  : - read parameters
69      !!----------------------------------------------------------------------
70      INTEGER           ::   ios           ! Local integer output status for namelist read
71      NAMELIST/namsbc_rnf_arcmsk/ cn_dir            , sn_cnf_arcmsk
72      !!----------------------------------------------------------------------
73      !
74      !                                         !==  allocate runoff arrays
75      IF( sbc_rnf_alloc_arcmsk() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_rnf_alloc_arcmsk : unable to allocate arrays' )
76      !
77      IF( .NOT. ln_rnf ) THEN                      ! no specific treatment in vicinity of river mouths
78         ln_rnf_mouth  = .FALSE.                   ! default definition needed for example by sbc_ssr or by tra_adv_muscl
79         rnfmsk_arcmsk  (:,:) = 0.0_wp
80         RETURN
81      ENDIF
82      !
83      !                                   ! ============
84      !                                   !   Namelist for arcmsk
85      !                                   ! ============
86      !
87      REWIND( numnam_ref )              ! Namelist namsbc_rnf_arcmsk in reference namelist : Runoffs & Arctic mask
88      READ  ( numnam_ref, namsbc_rnf_arcmsk, IOSTAT = ios, ERR = 901)
89901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf_arcmsk in reference namelist', lwp )
90
91      REWIND( numnam_cfg )              ! Namelist namsbc_rnf_arcmsk in configuration namelist : Runoffs & Arctic mask
92      READ  ( numnam_cfg, namsbc_rnf_arcmsk, IOSTAT = ios, ERR = 902 )
93902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_rnf_arcmsk in configuration namelist', lwp )
94      IF(lwm) WRITE ( numond, namsbc_rnf_arcmsk )
95      !
96      !                                         ! Control print
97      IF(lwp) THEN
98         WRITE(numout,*)
99         WRITE(numout,*) 'sbc_rnf_init_arcmsk : runoff & arctic mask'
100         WRITE(numout,*) '~~~~~~~ '
101         WRITE(numout,*) '   Namelist namsbc_rnf_arcmsk'
102         WRITE(numout,*) '      river mouth & Arctic file name    sn_cnf_arcmsk = ', sn_cnf_arcmsk
103      ENDIF
104      !                                   ! ========================
105      !                                   !   River mouth vicinity
106      !                                   ! ========================
107      !
108      !                                     No need to worry about it because would have been taken care of in rnfmsk already
109      !
110      !                                   ! ========================
111      !                                   !   River mouth vicinity
112      !                                   ! ========================
113      CALL rnf_mouth_arcmsk                             ! set river mouth mask & Arctic mask
114      !
115   END SUBROUTINE sbc_rnf_init_arcmsk
116
117
118   SUBROUTINE rnf_mouth_arcmsk
119      !!----------------------------------------------------------------------
120      !!                  ***  ROUTINE rnf_mouth  ***
121      !!
122      !! ** Purpose :   define the river mouths mask and mask out Arctic for use with
123      !!                SST & SSS restoring and flux adjustment
124      !!
125      !! ** Method  :   read the river mouth mask (=0/1) in the river runoff
126      !!                climatological file.
127      !!                This fields can be used to:
128      !!                 - set to zero SST & SSS restoring flux at river mouth grid points and over the Arctic
129      !!
130      !! ** Action  :   rnfmsk_arcmsk   set to 1 at river runoff input and Arctic, 0 elsewhere
131      !!----------------------------------------------------------------------
132      INTEGER            ::   inum        ! temporary integers
133      CHARACTER(len=140) ::   cl_rnfile   ! runoff file name
134      !!----------------------------------------------------------------------
135      !
136      IF(lwp) WRITE(numout,*)
137      IF(lwp) WRITE(numout,*) 'rnf_mouth_arcmsk: river mouth and Arctic mask'
138      IF(lwp) WRITE(numout,*) '~~~~~~~~~ '
139      !
140      cl_rnfile = TRIM( cn_dir )//TRIM( sn_cnf_arcmsk%clname )
141      IF( .NOT. sn_cnf_arcmsk%ln_clim ) THEN   ;   WRITE(cl_rnfile, '(a,"_y",i4)' ) TRIM( cl_rnfile ), nyear    ! add year
142         IF( sn_cnf_arcmsk%cltype == 'monthly' )   WRITE(cl_rnfile, '(a,"m",i2)'  ) TRIM( cl_rnfile ), nmonth   ! add month
143      ENDIF
144      !
145      ! horizontal mask (read in NetCDF file)
146      CALL iom_open ( cl_rnfile, inum )                           ! open file
147      CALL iom_get  ( inum, jpdom_data, sn_cnf_arcmsk%clvar, only_arcmsk )    ! read the river mouth array
148      CALL iom_close( inum )                                      ! close file
149      !
150      !IF( nn_closea == 1 )   CALL clo_rnf( rnfmsk_arcmsk )               ! closed sea inflow set as ruver mouth
151      !
152      ! combine arctic only mask and river mouth mask
153      rnfmsk_arcmsk(:,:) = only_arcmsk(:,:) + rnfmsk(:,:)
154      !
155      ! however in grids where the arctic mask and river mouth masks overlap, just use river mouth mask value
156      where ( rnfmsk(:,:).gt.0.495 .and. rnfmsk(:,:).lt.0.505 ) rnfmsk_arcmsk(:,:) = rnfmsk(:,:)
157      !
158   END SUBROUTINE rnf_mouth_arcmsk
159
160
161   !!======================================================================
162END MODULE sbc_arcmsk
Note: See TracBrowser for help on using the repository browser.