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.
cpl_rnf_1d.F90 in NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC – NEMO

source: NEMO/branches/UKMO/NEMO_4.0.1_icesheet_and_river_coupling/src/OCE/SBC/cpl_rnf_1d.F90 @ 13388

Last change on this file since 13388 was 13388, checked in by dancopsey, 4 years ago

Fix conflicts with penetrating solar branch

File size: 8.5 KB
Line 
1MODULE cpl_rnf_1d
2   !!======================================================================
3   !!                       ***  MODULE  cpl_rnf_1d  ***
4   !! Ocean forcing:  River runoff passed from the atmosphere using
5   !!                 1D array. One value per river.
6   !!=====================================================================
7   !! History : ?.?  ! 2018-01 (D. Copsey) Initial setup
8   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   cpl_rnf_1d_init : runoffs initialisation
12   !!----------------------------------------------------------------------
13
14#if defined key_oasis3
15   USE mod_oasis                    ! OASIS3-MCT module
16#endif
17   USE timing          ! Timing
18   USE in_out_manager  ! I/O units
19   USE lib_mpp         ! MPP library
20   USE iom
21   USE dom_oce         ! Domain sizes (for grid box area e1e2t)
22   USE sbc_oce         ! Surface boundary condition: ocean fields
23   USE lib_fortran,    ONLY: DDPDD
24   
25   IMPLICIT NONE
26   PRIVATE
27   
28   PUBLIC   cpl_rnf_1d_init     ! routine called in nemo_init
29   PUBLIC   cpl_rnf_1d_to_2d      ! routine called in sbccpl.F90
30   
31   TYPE, PUBLIC ::   RIVERS_DATA     !: Storage for river outflow data
32      INTEGER, ALLOCATABLE, DIMENSION(:,:)    ::   river_number       !: River outflow number
33      REAL(wp), ALLOCATABLE, DIMENSION(:)     ::   river_area         ! 1D array listing areas of each river outflow (m2)
34      COMPLEX(wp), ALLOCATABLE, DIMENSION(:)  ::   river_area_c       ! Comlex version of river_area for use in bit reproducible sums (m2)
35   END TYPE RIVERS_DATA
36   
37   TYPE(RIVERS_DATA), PUBLIC, TARGET :: rivers  !: River data
38   
39   INTEGER, PUBLIC            :: nn_cpl_river   ! Maximum number of rivers being passed through the coupler
40   INTEGER, PUBLIC            :: runoff_id      ! OASIS coupling id used in oasis_get command
41   LOGICAL                    :: ln_print_river_info  ! Diagnostic prints of river coupling information
42   
43CONTAINS
44
45   SUBROUTINE cpl_rnf_1d_init
46      !!----------------------------------------------------------------------
47      !!                    ***  SUBROUTINE cpl_rnf_1d_init  ***
48      !!                     
49      !! ** Purpose : - Read in file for river outflow numbers.
50      !!                Calculate 2D area of river outflow points.
51      !!                Called from nemo_init (nemogcm.F90).
52      !!
53      !!----------------------------------------------------------------------
54      !! namelist variables
55      !!-------------------
56      CHARACTER(len=200)                        ::   file_riv_number             !: Filename for river numbers
57      INTEGER                                   ::   ios                 ! Local integer output status for namelist read
58      INTEGER                                   ::   inum
59      INTEGER                                   ::   ii, jj              !: Loop indices
60      INTEGER                                   ::   max_river
61      REAL(wp), DIMENSION(jpi,jpj)              ::   river_number        ! 2D array containing the river outflow numbers
62     
63      NAMELIST/nam_cpl_rnf_1d/file_riv_number, nn_cpl_river, ln_print_river_info
64      !!----------------------------------------------------------------------
65
66      IF( ln_timing ) CALL timing_start('cpl_rnf_1d_init')
67     
68      IF(lwp) WRITE(numout,*)
69      IF(lwp) WRITE(numout,*) 'cpl_rnf_1d_init : initialization of river runoff coupling'
70      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
71      IF(lwp) CALL flush(numout)
72     
73      REWIND(numnam_cfg)
74     
75      ! Read the namelist
76      READ  ( numnam_ref, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 901)
77901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in reference namelist' )
78      READ  ( numnam_cfg, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 902 )
79902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in configuration namelist' )
80      IF(lwm .AND. nprint > 2) WRITE ( numond, nam_cpl_rnf_1d )
81
82      !                                               ! Parameter control and print
83      IF(lwp) WRITE(numout,*) '  '
84      IF(lwp) WRITE(numout,*) '          Namelist nam_cpl_rnf_1d : Coupled runoff using 1D array'
85      IF(lwp) WRITE(numout,*) '             Input file that contains river numbers = ',file_riv_number
86      IF(lwp) WRITE(numout,*) '             Maximum number of rivers to couple = ',nn_cpl_river
87      IF(lwp) WRITE(numout,*) '             Print river information = ',ln_print_river_info
88      IF(lwp) WRITE(numout,*) ' '
89      IF(lwp) CALL flush(numout)
90
91      ! Assign space for river numbers
92      ALLOCATE( rivers%river_number( jpi, jpj ) )
93     
94      ! Read the river numbers from netcdf file
95      CALL iom_open (file_riv_number , inum )
96      CALL iom_get  ( inum, jpdom_data, 'river_number', river_number )
97      CALL iom_close( inum )
98     
99      ! Convert from a real array to an integer array
100      max_river=0
101      DO ii = 1, jpi
102        DO jj = 1, jpj
103          rivers%river_number(ii,jj) = INT(river_number(ii,jj))
104          IF ( rivers%river_number(ii,jj) > max_river ) THEN
105            max_river = rivers%river_number(ii,jj)
106          END IF
107        END DO
108      END DO
109     
110      ! Print out the largest river number
111      IF ( ln_print_river_info .AND. lwp) THEN
112         WRITE(numout,*) 'Maximum river number in input file = ',max_river
113         CALL flush(numout)
114      END IF
115     
116      ! Get the area of each river outflow
117      ALLOCATE( rivers%river_area( nn_cpl_river ) )
118      ALLOCATE( rivers%river_area_c( nn_cpl_river ) )
119      rivers%river_area_c(:) = CMPLX( 0.e0, 0.e0, wp )
120      DO ii = nldi, nlei     
121        DO jj = nldj, nlej
122          IF ( tmask_i(ii,jj) > 0.5 ) THEN  ! This makes sure we are not at a duplicated point (at north fold or east-west cyclic point)
123            IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= nn_cpl_river ) THEN
124              ! Add the area of each grid box (e1e2t) into river_area_c using DDPDD which should maintain bit reproducibility (needs to be checked)
125              CALL DDPDD( CMPLX( e1e2t(ii,jj), 0.e0, wp ), rivers%river_area_c(rivers%river_number(ii,jj) ) )
126            END IF
127          END IF
128        END DO
129      END DO
130     
131      ! Use mpp_sum to add together river areas on other processors
132      CALL mpp_sum( 'cpl_rnf_1d', rivers%river_area_c )
133     
134      ! Convert from complex number to real
135      rivers%river_area(:) = REAL(rivers%river_area_c(:),wp)
136     
137      IF ( ln_print_river_info .AND. lwp) THEN
138        WRITE(numout,*) 'Area of rivers 1 to 10 are ',rivers%river_area(1:10)
139        WRITE(numout,*) 'Maximum river area = ',MAXVAL(rivers%river_area)
140        WRITE(numout,*) 'Minimum river area = ',MINVAL(rivers%river_area)
141        CALL flush(numout)
142      END IF
143
144      IF ( MINVAL(rivers%river_area) <= 0 ) THEN
145         WRITE(numout,*) 'ERROR: There is at least one river with a river outflow area of zero. Please check your file_riv_number file'
146         WRITE(numout,*) 'that all the allocated river numbers are at ocean points as defined by the bathymetry file with no river'
147         WRITE(numout,*) 'numbers within the north fold or wraparound points.'
148         CALL ctl_stop ( 'STOP', 'ERROR: There is at least one river with a river outflow area of zero. See stdout.')
149      END IF
150     
151   END SUBROUTINE cpl_rnf_1d_init
152   
153   SUBROUTINE cpl_rnf_1d_to_2d( runoff_1d )
154   
155      !!----------------------------------------------------------------------
156      !!                    ***  SUBROUTINE cpl_rnf_1d_to_2d  ***
157      !!                     
158      !! ** Purpose : - Convert river outflow from 1D array (passed from the
159      !!                atmosphere) to the 2D NEMO runoff field.
160      !!                Called from sbc_cpl_ice_flx (sbccpl.F90).
161      !!
162      !!----------------------------------------------------------------------
163     
164      REAL                   , INTENT(in   ) ::   runoff_1d(nn_cpl_river)    ! River runoff. One value per river.
165     
166      INTEGER  ::   ii, jj                 ! Loop indices
167           
168      ! Convert the 1D total runoff per river to 2D runoff flux by
169      ! dividing by the area of each runoff zone.
170      DO ii = 1, jpi
171        DO jj = 1, jpj
172          IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= nn_cpl_river ) THEN
173            rnf(ii,jj) = runoff_1d(rivers%river_number(ii,jj)) / rivers%river_area(rivers%river_number(ii,jj))
174          ELSE
175            rnf(ii,jj) = 0.0
176          END IF
177           
178        END DO
179      END DO
180
181   END SUBROUTINE cpl_rnf_1d_to_2d
182
183END MODULE cpl_rnf_1d
Note: See TracBrowser for help on using the repository browser.