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 branches/UKMO/dev_r5518_new_runoff_coupling/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/UKMO/dev_r5518_new_runoff_coupling/NEMOGCM/NEMO/OPA_SRC/SBC/cpl_rnf_1d.F90 @ 9264

Last change on this file since 9264 was 9264, checked in by dancopsey, 6 years ago

Added option to turn off coupling of old river runoff coupling and just use the new one.

File size: 8.4 KB
RevLine 
[9242]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 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 cpl_oasis3      ! Coupling information (for n_rivers and runoff_id)
25   
26   IMPLICIT NONE
27   PRIVATE
28   
29   PUBLIC   cpl_rnf_1d_init     ! routine called in nemo_init
30   PUBLIC   cpl_rnf_1d_rcv      ! 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   END TYPE RIVERS_DATA
36   
37   TYPE(RIVERS_DATA), PUBLIC, TARGET :: rivers  !: River data
38   
39CONTAINS
40
41   SUBROUTINE cpl_rnf_1d_init
42      !!----------------------------------------------------------------------
43      !!                    ***  SUBROUTINE cpl_rnf_1d_init  ***
44      !!                     
45      !! ** Purpose : - Read in file for river outflow numbers.
46      !!                Calculate 2D area of river outflow points.
47      !!                Called from nemo_init (nemogcm.F90).
48      !!
49      !!----------------------------------------------------------------------
50      !! namelist variables
51      !!-------------------
52      CHARACTER(len=80)                         ::   file_riv_number             !: Filename for river numbers
53      INTEGER                                   ::   ios                 ! Local integer output status for namelist read
54      INTEGER                                   ::   inum
55      INTEGER                                   ::   ii, jj              !: Loop indices
56      INTEGER                                   ::   max_river
57      REAL(wp), POINTER, DIMENSION(:,:)         ::   river_number        ! 2D array containing the river outflow numbers
58     
59      NAMELIST/nam_cpl_rnf_1d/file_riv_number
60      !!----------------------------------------------------------------------
61
62      IF( nn_timing == 1 ) CALL timing_start('cpl_rnf_1d_init')
63     
64      IF(lwp) WRITE(numout,*)
65      IF(lwp) WRITE(numout,*) 'cpl_rnf_1d_init : initialization of river runoff coupling'
66      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~'
67     
68      REWIND(numnam_cfg)
69     
70      ! Read the namelist
71      READ  ( numnam_ref, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 901)
72901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in reference namelist', lwp )
73      READ  ( numnam_cfg, nam_cpl_rnf_1d, IOSTAT = ios, ERR = 902 )
74902   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nam_cpl_rnf_1d in configuration namelist', lwp )
75      IF(lwm) WRITE ( numond, nam_cpl_rnf_1d )
76
77      !                                               ! Parameter control and print
78      IF(lwp) WRITE(numout,*) '  '
79      IF(lwp) WRITE(numout,*) '          Namelist nam_cpl_rnf_1d : Coupled runoff using 1D array'
80      IF(lwp) WRITE(numout,*) '             Input file that contains river numbers = ',file_riv_number
81      IF(lwp) WRITE(numout,*) ' '
82     
83      ! Assign space for river numbers
84      ALLOCATE( rivers%river_number( jpi, jpj ) )
85      CALL wrk_alloc( jpi, jpj, river_number )
86     
87      ! Read the river numbers from netcdf file
88      CALL iom_open (file_riv_number , inum )
89      CALL iom_get  ( inum, jpdom_data, 'river_number', river_number )
90      CALL iom_close( inum )
91     
92      ! Convert from a real array to an integer array
93      max_river=0
94      DO ii = 1, jpi
95        DO jj = 1, jpj
96          rivers%river_number(ii,jj) = INT(river_number(ii,jj))
97         
98          IF ( rivers%river_number(ii,jj) > max_river ) THEN
99            max_river = rivers%river_number(ii,jj)
100          END IF
101         
102          IF ( ii == 59 .AND. jj == 29 ) THEN
103            WRITE(numout,*) 'Amazon grid point river number (float) = ',river_number(ii,jj)
104            WRITE(numout,*) 'Amazon grid point river number (int) = ',INT(river_number(ii,jj))
105            WRITE(numout,*) 'Amazon grid point river number (store) = ',rivers%river_number(ii,jj)
106            WRITE(numout,*) 'max_river at this stage = ',max_river
107            WRITE(numout,*) 'Amazon grid box area = ',e1e2t(ii,jj)
108          END IF
109        END DO
110      END DO
111     
112      ! Print out the largest river number
113      WRITE(numout,*) 'Maximum river number = ',max_river
114     
115      ! Get the area of each river outflow
116      ALLOCATE( rivers%river_area( n_rivers ) )
117      rivers%river_area(:) = 0.0
118      DO ii = 1, jpi
119        DO jj = 1, jpj
120          IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= n_rivers ) THEN
121            rivers%river_area(rivers%river_number(ii,jj)) = rivers%river_area(rivers%river_number(ii,jj)) + e1e2t(ii,jj)
122          END IF
123        END DO
124      END DO
125     
126      ! Use mpp_sum to add together river areas on other processors
127      CALL mpp_sum( rivers%river_area, n_rivers )
128      WRITE(numout,*) 'Area of river number 1 is ',rivers%river_area(1)
129      WRITE(numout,*) 'Area of river number 10 is ',rivers%river_area(10)
130     
131     
132   END SUBROUTINE cpl_rnf_1d_init
133   
134   SUBROUTINE cpl_rnf_1d_rcv( kstep)
135   
136      !!----------------------------------------------------------------------
137      !!                    ***  SUBROUTINE cpl_rnf_1d_rcv  ***
138      !!                     
139      !! ** Purpose : - Get river outflow from 1D array (passed from the
140      !!                atmosphere) and transfer it to the 2D NEMO runoff
141      !!                field.
142      !!                Called from sbc_cpl_rcv (sbccpl.F90).
143      !!
144      !!----------------------------------------------------------------------
145     
146      INTEGER                   , INTENT(in   ) ::   kstep     ! ocean time-step in seconds
147     
148      INTEGER  ::   kinfo                  ! OASIS3 info argument   
149      REAL(wp) ::   runoff_1d(n_rivers)    ! River runoff. One value per river.
150      INTEGER  ::   ii, jj                 ! Loop indices
151      LOGICAL  ::   llaction               ! Has the get worked?
152     
153      IF ( ln_ctl ) THEN
154         WRITE(numout,*)' Getting data from 1D river runoff coupling '
155      ENDIF
156   
157      ! Get the river runoff sent by the atmosphere
158      CALL oasis_get ( runoff_id, kstep, runoff_1d, kinfo )
159      llaction =  kinfo == OASIS_Recvd   .OR. kinfo == OASIS_FromRest .OR.   &
160                  &        kinfo == OASIS_RecvOut .OR. kinfo == OASIS_FromRestOut
161                 
162      ! Output coupling info
163      IF ( ln_ctl ) THEN
164         WRITE(numout,*)' narea = ', narea
165         WRITE(numout,*)' kstep = ', kstep
[9264]166         WRITE(numout,*)' River runoff = ', runoff_1d(1:10)
[9242]167         WRITE(numout,*)' kinfo = ', kinfo
168         WRITE(numout,*)' llaction = ', llaction
169         WRITE(numout,*)' OASIS_Recvd = ',OASIS_Recvd
170         WRITE(numout,*)' OASIS_FromRest = ',OASIS_FromRest
171         WRITE(numout,*)' OASIS_RecvOut = ',OASIS_RecvOut
172         WRITE(numout,*)' OASIS_FromRestOut = ',OASIS_FromRestOut
173         WRITE(numout,*)'-------'
174      ENDIF
175     
176      IF ( llaction ) THEN
177     
178        ! Convert the 1D total runoff per river to 2D runoff flux by
179        ! dividing by the area of each runoff zone.
180        DO ii = 1, jpi
181          DO jj = 1, jpj
182            IF ( rivers%river_number(ii,jj) > 0 .AND. rivers%river_number(ii,jj) <= n_rivers ) THEN
183              rnf(ii,jj) = runoff_1d(rivers%river_number(ii,jj)) / rivers%river_area(rivers%river_number(ii,jj))
184            ELSE
185              rnf(ii,jj) = 0.0
186            END IF
187           
188          END DO
189        END DO
190         
191      END IF
192     
193      IF ( ln_ctl ) WRITE(numout,*)' River runoff flux of AMAZON (pe 351) is ', rnf(59,29)         
194   
195   END SUBROUTINE cpl_rnf_1d_rcv
196
197END MODULE cpl_rnf_1d
Note: See TracBrowser for help on using the repository browser.