1 | MODULE 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 wrk_nemo ! Memory allocation |
---|
22 | USE dom_oce ! Domain sizes (for grid box area e1e2t) |
---|
23 | USE sbc_oce ! Surface boundary condition: ocean fields |
---|
24 | USE lib_fortran, ONLY: DDPDD |
---|
25 | |
---|
26 | IMPLICIT NONE |
---|
27 | PRIVATE |
---|
28 | |
---|
29 | PUBLIC cpl_rnf_1d_init ! routine called in nemo_init |
---|
30 | PUBLIC cpl_rnf_1d_to_2d ! routine called in sbccpl.F90 |
---|
31 | |
---|
32 | TYPE, PUBLIC :: RIVERS_DATA !: Storage for river outflow data |
---|
33 | INTEGER, POINTER, DIMENSION(:,:) :: river_number !: River outflow number |
---|
34 | REAL(wp), POINTER, DIMENSION(:) :: river_area ! 1D array listing areas of each river outflow (m2) |
---|
35 | COMPLEX(wp), POINTER, DIMENSION(:) :: river_area_c ! Comlex version of river_area for use in bit reproducible sums (m2) |
---|
36 | END TYPE RIVERS_DATA |
---|
37 | |
---|
38 | TYPE(RIVERS_DATA), PUBLIC, TARGET :: rivers !: River data |
---|
39 | |
---|
40 | INTEGER, PUBLIC :: nn_cpl_river ! Maximum number of rivers being passed through the coupler |
---|
41 | INTEGER, PUBLIC :: runoff_id ! OASIS coupling id used in oasis_get command |
---|
42 | LOGICAL :: ln_print_river_info ! Diagnostic prints of river coupling information |
---|
43 | |
---|
44 | CONTAINS |
---|
45 | |
---|
46 | SUBROUTINE cpl_rnf_1d_init |
---|
47 | !!---------------------------------------------------------------------- |
---|
48 | !! *** SUBROUTINE cpl_rnf_1d_init *** |
---|
49 | !! |
---|
50 | !! ** Purpose : - Read in file for river outflow numbers. |
---|
51 | !! Calculate 2D area of river outflow points. |
---|
52 | !! Called from nemo_init (nemogcm.F90). |
---|
53 | !! |
---|
54 | !!---------------------------------------------------------------------- |
---|
55 | !! namelist variables |
---|
56 | !!------------------- |
---|
57 | CHARACTER(len=80) :: file_riv_number !: Filename for river numbers |
---|
58 | INTEGER :: ios ! Local integer output status for namelist read |
---|
59 | INTEGER :: inum |
---|
60 | INTEGER :: ii, jj, rr !: Loop indices |
---|
61 | INTEGER :: max_river |
---|
62 | REAL(wp), POINTER, DIMENSION(:,:) :: river_number ! 2D array containing the river outflow numbers |
---|
63 | |
---|
64 | NAMELIST/nam_cpl_rnf_1d/file_riv_number, nn_cpl_river, ln_print_river_info |
---|
65 | !!---------------------------------------------------------------------- |
---|
66 | |
---|
67 | IF( nn_timing == 1 ) CALL timing_start('cpl_rnf_1d_init') |
---|
68 | |
---|
69 | IF(lwp) WRITE(numout,*) |
---|
70 | IF(lwp) WRITE(numout,*) 'cpl_rnf_1d_init : initialization of river runoff coupling' |
---|
71 | IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' |
---|
72 | |
---|
73 | REWIND(numnam_cfg) |
---|
74 | |
---|
75 | ! Read the namelist |
---|
76 | READ ( numnam_ref, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 901) |
---|
77 | 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in reference namelist', lwp ) |
---|
78 | READ ( numnam_cfg, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 902 ) |
---|
79 | 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in configuration namelist', lwp ) |
---|
80 | IF(lwm) 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 | |
---|
90 | ! Assign space for river numbers |
---|
91 | ALLOCATE( rivers%river_number( jpi, jpj ) ) |
---|
92 | CALL wrk_alloc( jpi, jpj, river_number ) |
---|
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 ) THEN |
---|
112 | WRITE(numout,*) 'Maximum river number in input file = ',max_river |
---|
113 | END IF |
---|
114 | |
---|
115 | ! Get the area of each river outflow |
---|
116 | ALLOCATE( rivers%river_area( nn_cpl_river ) ) |
---|
117 | ALLOCATE( rivers%river_area_c( nn_cpl_river ) ) |
---|
118 | rivers%river_area_c(:) = CMPLX( 0.e0, 0.e0, wp ) |
---|
119 | DO ii = nldi, nlei |
---|
120 | DO jj = nldj, nlej |
---|
121 | 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) |
---|
122 | IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= nn_cpl_river ) THEN |
---|
123 | ! Add the area of each grid box (e1e2t) into river_area_c using DDPDD which should maintain bit reproducibility (needs to be checked) |
---|
124 | CALL DDPDD( CMPLX( e1e2t(ii,jj), 0.e0, wp ), rivers%river_area_c(rivers%river_number(ii,jj) ) ) |
---|
125 | END IF |
---|
126 | END IF |
---|
127 | END DO |
---|
128 | END DO |
---|
129 | |
---|
130 | ! Use mpp_sum to add together river areas on other processors |
---|
131 | CALL mpp_sum( rivers%river_area_c, nn_cpl_river ) |
---|
132 | |
---|
133 | ! Convert from complex number to real |
---|
134 | ! DO rr = 1, nn_cpl_river |
---|
135 | ! rivers%river_area(rr) = rivers%river_area_c(rr) |
---|
136 | ! END DO |
---|
137 | rivers%river_area(:) = REAL(rivers%river_area_c(:),wp) |
---|
138 | |
---|
139 | IF ( ln_print_river_info ) THEN |
---|
140 | WRITE(numout,*) 'Area of rivers 1 to 10 are ',rivers%river_area(1:10) |
---|
141 | END IF |
---|
142 | |
---|
143 | END SUBROUTINE cpl_rnf_1d_init |
---|
144 | |
---|
145 | SUBROUTINE cpl_rnf_1d_to_2d( runoff_1d ) |
---|
146 | |
---|
147 | !!---------------------------------------------------------------------- |
---|
148 | !! *** SUBROUTINE cpl_rnf_1d_to_2d *** |
---|
149 | !! |
---|
150 | !! ** Purpose : - Convert river outflow from 1D array (passed from the |
---|
151 | !! atmosphere) to the 2D NEMO runoff field. |
---|
152 | !! Called from sbc_cpl_ice_flx (sbccpl.F90). |
---|
153 | !! |
---|
154 | !!---------------------------------------------------------------------- |
---|
155 | |
---|
156 | REAL , INTENT(in ) :: runoff_1d(nn_cpl_river) ! River runoff. One value per river. |
---|
157 | |
---|
158 | INTEGER :: ii, jj ! Loop indices |
---|
159 | |
---|
160 | ! Convert the 1D total runoff per river to 2D runoff flux by |
---|
161 | ! dividing by the area of each runoff zone. |
---|
162 | DO ii = 1, jpi |
---|
163 | DO jj = 1, jpj |
---|
164 | IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= nn_cpl_river ) THEN |
---|
165 | rnf(ii,jj) = runoff_1d(rivers%river_number(ii,jj)) / rivers%river_area(rivers%river_number(ii,jj)) |
---|
166 | ELSE |
---|
167 | rnf(ii,jj) = 0.0 |
---|
168 | END IF |
---|
169 | |
---|
170 | END DO |
---|
171 | END DO |
---|
172 | |
---|
173 | END SUBROUTINE cpl_rnf_1d_to_2d |
---|
174 | |
---|
175 | END MODULE cpl_rnf_1d |
---|