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 @ 4351

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

Branch 2013/dev_ECMWF_waves ticket #1216. First set of code imports from ECMWF. Untested

File size: 10.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_wave_ecmwf    ! routine called in sbc_blk_core or sbc_blk_mfs
24   PUBLIC   sbc_wavepar       !
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_ecwmf( 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      CHARACTER(len=100)     ::  cn_dir_cdg                      ! Root directory for location of drag coefficient files
64      TYPE(FLD_N)            ::  sn_cdg                          ! informations about the fields to be read
65      !!---------------------------------------------------------------------
66      NAMELIST/namsbc_wave_ecmwf/  sn_cdg, cn_dir_cdg
67      !!---------------------------------------------------------------------
68
69      !!----------------------------------------------------------------------
70      !
71      !
72      !                                         ! -------------------- !
73      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
74         !                                      ! -------------------- !
75         !                                            !* set file information (default values)
76         ! ... default values (NB: frequency positive => hours, negative => months)
77         !              !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
78         !              !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
79         sn_cdg = FLD_N('cdg_wave'  ,    1     ,'drag_coeff',  .true.    , .false. ,   'daily'   , ''       , ''       )
80         cn_dir_cdg = './'          ! directory in which the Patm data are
81         
82
83         REWIND( numnam )                             !* read in namlist namsbc_wave_ecmwf
84         READ  ( numnam, namsbc_wave_ecmwf ) 
85         !
86
87         ALLOCATE( sf_wave(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg
88         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave_ecmwf: unable to allocate sf_wave structure' )
89         !
90         CALL fld_fill( sf_wave, (/ sn_cdg /), cn_dir_cdg, 'sbc_wave_ecmwf', 'Wave module ', 'namsbc_wave_ecmwf' )
91                                ALLOCATE( sf_wave(1)%fnow(jpi,jpj,1)   )
92         IF( sn_cdg%ln_tint )   ALLOCATE( sf_wave(1)%fdta(jpi,jpj,1,2) )
93         ! Allocation done by sbc_oce
94         cdn_wave(:,:) = 0.0
95      ENDIF
96         !
97         !
98      CALL fld_read( kt, nn_fsbc, sf_wave )      !* read drag coefficient from external forcing
99      cdn_wave(:,:) = sf_wave(1)%fnow(:,:,1)
100
101   END SUBROUTINE sbc_wave_ecmwf
102
103
104   SUBROUTINE sbc_wavepar( kt )
105      !!---------------------------------------------------------------------
106      !!                     ***  ROUTINE sbc_wavepar  ***
107      !!
108      !! ** Purpose :   Provide at each time step wave model parameters, including the
109      !!                Stokes drift (east and north components), significant wave height and the
110      !!                mean wave period as well as the normalized stress and energy flux into the
111      !!                ocean for TKE.
112      !!
113      !!
114      !! ** Method  : - Read namelist namsbc_wavepar
115      !!              - Read fields in NetCDF files
116      !! ** action  :   
117      !!               
118      !!---------------------------------------------------------------------
119      INTEGER, INTENT( in  ) ::  kt  ! ocean time step
120      !!
121      INTEGER  ::  ierror ! return error code
122      INTEGER  ::   ji      ! dummy loop index
123      INTEGER  ::   jfld    ! dummy loop arguments
124      !!
125      CHARACTER(len=100)     ::  cn_dir_wavepar ! Root directory for location of ECWAM wave parameter fields
126      TYPE(FLD_N), DIMENSION(jpfld_wavepar) :: slf_i ! array of namelist informations on the fields to read
127      TYPE(FLD_N)            ::  sn_ust, sn_vst, sn_swh, sn_mwp ! information about the fields to be read
128      TYPE(FLD_N)            ::  sn_phioc, sn_tauoc
129      TYPE(FLD_N)            ::  sn_wspd
130      !TYPE(FLD_N)            ::  sn_cdww
131      !!---------------------------------------------------------------------
132      !NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_phioc, sn_tauoc, cn_dir_wavepar
133      NAMELIST/namsbc_wavepar/  sn_ust, sn_vst, sn_swh, sn_mwp, sn_wspd, sn_phioc, sn_tauoc, cn_dir_wavepar
134      !!---------------------------------------------------------------------
135
136      !!----------------------------------------------------------------------
137      !
138      !
139      !                                         ! -------------------- !
140      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
141         !                                      ! -------------------- !
142         ! set file information (default values)
143         ! ... default values (NB: frequency positive => hours, negative => months)
144         !            !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
145         !            !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
146         sn_ust = FLD_N( 'ust'   ,     6     ,  'ust'     ,  .true.    , .false. ,   'monthly' , ''       , ''       )
147         sn_vst = FLD_N( 'vst'   ,     6     ,  'vst'     ,  .true.    , .false. ,   'monthly' , ''       , ''       )
148         sn_swh = FLD_N( 'swh'   ,     6     ,  'swh'     ,  .true.    , .false. ,   'monthly' , ''       , ''       )
149         sn_mwp = FLD_N( 'mwp'   ,     6     ,  'mwp'     ,  .true.    , .false. ,   'monthly' , ''       , ''       )
150         !sn_cdww = FLD_N( 'cdww'  ,    6     ,  'cdww'    ,  .true.    , .false. ,   'monthly' , ''       , ''       )
151         sn_wspd = FLD_N( 'wspd'   ,   6     ,  'wspd'    ,  .true.    , .false. ,   'monthly' , ''       , ''       )
152         sn_phioc = FLD_N( 'phioc'   , 6     ,  'phioc'   ,  .true.    , .false. ,   'monthly' , ''       , ''       )
153         sn_tauoc = FLD_N( 'tauoc'   , 6     ,  'tauoc'   ,  .true.    , .false. ,   'monthly' , ''       , ''       )
154         cn_dir_wavepar = './'          ! directory in which the wave data are found
155
156         REWIND( numnam )                             !* read in namlist namsbc_wavepar
157         READ  ( numnam, namsbc_wavepar ) 
158         !
159         slf_i(jp_ust) = sn_ust 
160         slf_i(jp_vst) = sn_vst
161         slf_i(jp_swh) = sn_swh
162         slf_i(jp_mwp) = sn_mwp
163         !slf_i(jp_cdww) = sn_cdww
164         slf_i(jp_wspd) = sn_wspd
165         slf_i(jp_phioc) = sn_phioc
166         slf_i(jp_tauoc) = sn_tauoc
167
168         ALLOCATE( sf_wavepar(jpfld_wavepar), STAT=ierror )          !* set sf_wavepar structure
169         IF ( ierror > 0 ) THEN
170            CALL ctl_stop( 'STOP', 'sbc_wavepar: unable to allocate sf_wavepar structure' ) ; RETURN
171         ENDIF
172         !
173         jfld = jpfld_wavepar
174         DO ji = 1, jpfld_wavepar
175            ALLOCATE( sf_wavepar(ji)%fnow(jpi,jpj,1)   )
176            IF ( slf_i(ji)%ln_tint ) ALLOCATE( sf_wavepar(ji)%fdta(jpi,jpj,1,2) )
177         ENDDO
178         ALLOCATE( ust_wavepar(jpi,jpj) )
179         ALLOCATE( vst_wavepar(jpi,jpj) )
180         ALLOCATE( swh_wavepar(jpi,jpj) )
181         ALLOCATE( mwp_wavepar(jpi,jpj) )
182         !ALLOCATE( wspd_wavepar(jpi,jpj) ) ! allocation done by sbc_oce
183         ALLOCATE( phioc_wavepar(jpi,jpj) )
184         ALLOCATE( tauoc_wavepar(jpi,jpj) )
185
186         !
187         CALL fld_fill( sf_wavepar, slf_i, cn_dir_wavepar, 'sbc_wavepar', 'Wave module ', 'namsbc_wavepar' )
188         !
189      ENDIF
190         !
191      CALL fld_read( kt, nn_fsbc, sf_wavepar )      !* read wave parameters from ECWAM NetCDF file
192      ust_wavepar(:,:) = sf_wavepar(jp_ust)%fnow(:,:,1)
193      vst_wavepar(:,:) = sf_wavepar(jp_vst)%fnow(:,:,1)
194      swh_wavepar(:,:) = sf_wavepar(jp_swh)%fnow(:,:,1)
195      mwp_wavepar(:,:) = sf_wavepar(jp_mwp)%fnow(:,:,1)
196      !cdww_wavepar(:,:) = sf_wavepar(jp_cdww)%fnow(:,:,1)
197      wspd_wavepar(:,:) = sf_wavepar(jp_wspd)%fnow(:,:,1)
198      phioc_wavepar(:,:) = sf_wavepar(jp_phioc)%fnow(:,:,1)
199      tauoc_wavepar(:,:) = sf_wavepar(jp_tauoc)%fnow(:,:,1)
200
201   END SUBROUTINE sbc_wavepar
202
203END MODULE sbcwave
Note: See TracBrowser for help on using the repository browser.