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.
sbcwave_ecmwf.F90 in branches/2013/dev_ECMWF_waves/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2013/dev_ECMWF_waves/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave_ecmwf.F90 @ 4353

Last change on this file since 4353 was 4353, checked in by acc, 10 years ago

Branch 2013/dev_ECMWF_waves ticket #1216. Update namelist handling to v3.6 standard

File size: 11.8 KB
Line 
1MODULE sbcwave_ecmwf
2   !!======================================================================
3   !!                       ***  MODULE  sbcwave  ***
4   !! Wave module
5   !!======================================================================
6   !! History :  3.3.1  !   2011-09  (Adani M)  Original code
7   !!----------------------------------------------------------------------
8   USE iom             ! I/O manager library
9   USE in_out_manager  ! I/O manager
10   USE lib_mpp         ! distribued memory computing library
11   USE fldread         ! read input fields
12   USE sbc_oce         ! Surface boundary condition: ocean fields
13   USE phycst          ! physical constants
14   USE sbcblk_core, ONLY: Cd_n10
15   
16   !!----------------------------------------------------------------------
17   !!   sbc_wave_ecmwf : read drag coefficient from wave model in netcdf files
18   !!----------------------------------------------------------------------
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   sbc_wavepar       !
24   PUBLIC   sbc_wave_ecmwf    ! routine called in sbc_blk_core or sbc_blk_mfs
25   
26   INTEGER , PARAMETER ::   jpfld_wavepar = 7    ! maximum number of fields to be read
27   INTEGER , PARAMETER ::   jp_ust = 1           ! index of Stokes velocity (east component) (m/s)  at T-point
28   INTEGER , PARAMETER ::   jp_vst = 2           ! index of Stokes velocity (north component) (m/s) at T-point
29   INTEGER , PARAMETER ::   jp_swh = 3           ! index of significant wave height (m)
30   INTEGER , PARAMETER ::   jp_mwp = 4           ! index of mean wave period (s)
31   INTEGER , PARAMETER ::   jp_phioc = 5         ! index of normalized energy flux into the ocean (non-dim)
32   INTEGER , PARAMETER ::   jp_tauoc = 6         ! index of normalized wave stress into the ocean (non-dim)
33   INTEGER , PARAMETER ::   jp_wspd = 7          ! index of 10 m neutral wind speed (m/s)
34
35   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wave    ! structure of input fields (file informations, fields read)
36   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wavepar ! structure of input fields (file informations, fields read)
37   REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: ust_wavepar, vst_wavepar, swh_wavepar, mwp_wavepar
38   REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: phioc_wavepar
39
40   !! * Substitutions
41#  include "domzgr_substitute.h90"
42#  include "vectopt_loop_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
45   !! $Id: $
46   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48CONTAINS
49
50   SUBROUTINE sbc_wave_ecmwf( kt )
51      !!---------------------------------------------------------------------
52      !!                     ***  ROUTINE sbc_apr  ***
53      !!
54      !! ** Purpose :   read drag coefficient from wave model  in netcdf files.
55      !!
56      !! ** Method  : - Read namelist namsbc_wave
57      !!              - Read Cd_n10 fields in netcdf files
58      !! ** action  :   
59      !!               
60      !!---------------------------------------------------------------------
61      INTEGER, INTENT( in  ) ::  kt       ! ocean time step
62      INTEGER                ::  ierror   ! return error code
63      INTEGER                ::  ios      ! io return code
64      CHARACTER(len=100)     ::  cn_dir_cdg                      ! Root directory for location of drag coefficient files
65      TYPE(FLD_N)            ::  sn_cdg                          ! informations about the fields to be read
66      !!---------------------------------------------------------------------
67      NAMELIST/namsbc_wave_ecmwf/  sn_cdg, cn_dir_cdg
68      !!---------------------------------------------------------------------
69
70      !!----------------------------------------------------------------------
71      !
72      !
73      !                                         ! -------------------- !
74      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
75         !                                      ! -------------------- !
76         !                                            !* set file information (default values)
77         ! ... default values (NB: frequency positive => hours, negative => months)
78         !              !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
79         !              !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
80         sn_cdg = FLD_N( 'cdg_wave'  ,    1.    ,'drag_coeff',  .true.    , .false. ,   'daily'   , ''       , ''      , '' )
81         cn_dir_cdg = './'          ! directory in which the Patm data are
82         
83
84         REWIND( numnam_ref )              !  Namelist namsbc_wavepar in reference namelist
85         READ  ( numnam_ref, namsbc_wave_ecmwf, IOSTAT = ios, ERR = 901)
86901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave_ecmwf in reference namelist', lwp )
87
88         REWIND( numnam_cfg )              !  Namelist namsbc_wave_ecmwf in configuration namelist
89         READ  ( numnam_cfg, namsbc_wave_ecmwf, IOSTAT = ios, ERR = 902 )
90902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wave_ecmwf in configuration namelist', lwp )
91         WRITE ( numond, namsbc_wave_ecmwf )
92         !
93
94         ALLOCATE( sf_wave(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg
95         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_ecmwf: unable to allocate sf_wave structure' )
96         !
97         CALL fld_fill( sf_wave, (/ sn_cdg /), cn_dir_cdg, 'sbc_wave_ecmwf', 'Wave module ', 'namsbc_wave_ecmwf' )
98                                ALLOCATE( sf_wave(1)%fnow(jpi,jpj,1)   )
99         IF( sn_cdg%ln_tint )   ALLOCATE( sf_wave(1)%fdta(jpi,jpj,1,2) )
100         ! Allocation done by sbc_oce
101         cdn_wave(:,:) = 0.0
102      ENDIF
103         !
104         !
105      CALL fld_read( kt, nn_fsbc, sf_wave )      !* read drag coefficient from external forcing
106      cdn_wave(:,:) = sf_wave(1)%fnow(:,:,1)
107
108   END SUBROUTINE sbc_wave_ecmwf
109
110
111   SUBROUTINE sbc_wavepar( kt )
112      !!---------------------------------------------------------------------
113      !!                     ***  ROUTINE sbc_wavepar  ***
114      !!
115      !! ** Purpose :   Provide at each time step wave model parameters, including the
116      !!                Stokes drift (east and north components), significant wave height and the
117      !!                mean wave period as well as the normalized stress and energy flux into the
118      !!                ocean for TKE.
119      !!
120      !!
121      !! ** Method  : - Read namelist namsbc_wavepar
122      !!              - Read fields in NetCDF files
123      !! ** action  :   
124      !!               
125      !!---------------------------------------------------------------------
126      INTEGER, INTENT( in  ) ::  kt  ! ocean time step
127      !!
128      INTEGER  ::  ierror ! return error code
129      INTEGER  ::   ji      ! dummy loop index
130      INTEGER  ::   jfld    ! dummy loop arguments
131      INTEGER  ::   ios     ! io return code
132      !!
133      CHARACTER(len=100)     ::  cn_dir_wavepar ! Root directory for location of ECWAM wave parameter fields
134      TYPE(FLD_N), DIMENSION(jpfld_wavepar) :: slf_i ! array of namelist informations on the fields to read
135      TYPE(FLD_N)            ::  sn_ust, sn_vst, sn_swh, sn_mwp ! information about the fields to be read
136      TYPE(FLD_N)            ::  sn_phioc, sn_tauoc
137      TYPE(FLD_N)            ::  sn_wspd
138      !TYPE(FLD_N)            ::  sn_cdww
139      !!---------------------------------------------------------------------
140      !NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_phioc, sn_tauoc, cn_dir_wavepar
141      NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_wspd, sn_phioc, sn_tauoc, cn_dir_wavepar
142      !!---------------------------------------------------------------------
143
144      !!----------------------------------------------------------------------
145      !
146      !
147      !                                         ! -------------------- !
148      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
149         !                                      ! -------------------- !
150         ! set file information (default values)
151         ! ... default values (NB: frequency positive => hours, negative => months)
152         !            !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
153         !            !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
154         sn_ust = FLD_N( 'ust'   ,     6     ,  'ust'     ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
155         sn_vst = FLD_N( 'vst'   ,     6     ,  'vst'     ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
156         sn_swh = FLD_N( 'swh'   ,     6     ,  'swh'     ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
157         sn_mwp = FLD_N( 'mwp'   ,     6     ,  'mwp'     ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
158         !sn_cdww = FLD_N( 'cdww'  ,    6     ,  'cdww'    ,  .true.    , .false. ,   'monthly' , ''       , ''      ,  '' )
159         sn_wspd = FLD_N( 'wspd'   ,   6     ,  'wspd'    ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
160         sn_phioc = FLD_N( 'phioc'   , 6     ,  'phioc'   ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
161         sn_tauoc = FLD_N( 'tauoc'   , 6     ,  'tauoc'   ,  .true.    , .false. ,   'monthly' , ''       , ''       ,  '' )
162         cn_dir_wavepar = './'          ! directory in which the wave data are found
163
164         REWIND( numnam_ref )              !  Namelist namsbc_wavepar in reference namelist
165         READ  ( numnam_ref, namsbc_wavepar, IOSTAT = ios, ERR = 901)
166901      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wavepar in reference namelist', lwp )
167
168         REWIND( numnam_cfg )              !  Namelist namsbc_wavepar in configuration namelist
169         READ  ( numnam_cfg, namsbc_wavepar, IOSTAT = ios, ERR = 902 )
170902      IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_wavepar in configuration namelist', lwp )
171         WRITE ( numond, namsbc_wavepar )
172         !
173         slf_i(jp_ust) = sn_ust 
174         slf_i(jp_vst) = sn_vst
175         slf_i(jp_swh) = sn_swh
176         slf_i(jp_mwp) = sn_mwp
177         !slf_i(jp_cdww) = sn_cdww
178         slf_i(jp_wspd) = sn_wspd
179         slf_i(jp_phioc) = sn_phioc
180         slf_i(jp_tauoc) = sn_tauoc
181
182         ALLOCATE( sf_wavepar(jpfld_wavepar), STAT=ierror )          !* set sf_wavepar structure
183         IF ( ierror > 0 ) THEN
184            CALL ctl_stop( 'STOP', 'sbc_wavepar: unable to allocate sf_wavepar structure' ) ; RETURN
185         ENDIF
186         !
187         jfld = jpfld_wavepar
188         DO ji = 1, jpfld_wavepar
189            ALLOCATE( sf_wavepar(ji)%fnow(jpi,jpj,1)   )
190            IF ( slf_i(ji)%ln_tint ) ALLOCATE( sf_wavepar(ji)%fdta(jpi,jpj,1,2) )
191         ENDDO
192         ALLOCATE( ust_wavepar(jpi,jpj) )
193         ALLOCATE( vst_wavepar(jpi,jpj) )
194         ALLOCATE( swh_wavepar(jpi,jpj) )
195         ALLOCATE( mwp_wavepar(jpi,jpj) )
196         !ALLOCATE( wspd_wavepar(jpi,jpj) ) ! allocation done by sbc_oce
197         ALLOCATE( phioc_wavepar(jpi,jpj) )
198         ALLOCATE( tauoc_wavepar(jpi,jpj) )
199
200         !
201         CALL fld_fill( sf_wavepar, slf_i, cn_dir_wavepar, 'sbc_wavepar', 'Wave module ', 'namsbc_wavepar' )
202         !
203      ENDIF
204         !
205      CALL fld_read( kt, nn_fsbc, sf_wavepar )      !* read wave parameters from ECWAM NetCDF file
206      ust_wavepar(:,:) = sf_wavepar(jp_ust)%fnow(:,:,1)
207      vst_wavepar(:,:) = sf_wavepar(jp_vst)%fnow(:,:,1)
208      swh_wavepar(:,:) = sf_wavepar(jp_swh)%fnow(:,:,1)
209      mwp_wavepar(:,:) = sf_wavepar(jp_mwp)%fnow(:,:,1)
210      !cdww_wavepar(:,:) = sf_wavepar(jp_cdww)%fnow(:,:,1)
211      wspd_wavepar(:,:) = sf_wavepar(jp_wspd)%fnow(:,:,1)
212      phioc_wavepar(:,:) = sf_wavepar(jp_phioc)%fnow(:,:,1)
213      tauoc_wavepar(:,:) = sf_wavepar(jp_tauoc)%fnow(:,:,1)
214
215   END SUBROUTINE sbc_wavepar
216
217END MODULE sbcwave_ecmwf
Note: See TracBrowser for help on using the repository browser.