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.F90 in branches/2011/dev_MERCATOR_INGV_2011_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2011/dev_MERCATOR_INGV_2011_MERGE/NEMOGCM/NEMO/OPA_SRC/SBC/sbcwave.F90 @ 3085

Last change on this file since 3085 was 3085, checked in by cbricaud, 12 years ago

commit changes from dev_INGV_2011

File size: 4.3 KB
Line 
1MODULE sbcwave
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
14   
15   !!----------------------------------------------------------------------
16   !!   sbc_wave       : read drag coefficient from wave model in netcdf files
17   !!----------------------------------------------------------------------
18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   sbc_wave    ! routine called in sbc_blk_core or sbc_blk_ecmwf
23   
24   TYPE(FLD), ALLOCATABLE, DIMENSION(:)  :: sf_wave     ! structure of input fields (file informations, fields read)
25   REAL(wp),PUBLIC,ALLOCATABLE,DIMENSION (:,:)       :: cdn_wave 
26
27   !!----------------------------------------------------------------------
28   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
29   !! $Id: $
30   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34   SUBROUTINE sbc_wave( kt )
35      !!---------------------------------------------------------------------
36      !!                     ***  ROUTINE sbc_apr  ***
37      !!
38      !! ** Purpose :   read drag coefficient from wave model  in netcdf files.
39      !!
40      !! ** Method  : - Read namelist namsbc_wave
41      !!              - Read Cd_n10 fields in netcdf files
42      !! ** action  :   
43      !!               
44      !!---------------------------------------------------------------------
45      INTEGER, INTENT( in  ) ::  kt   ! ocean time step
46      INTEGER                ::  ierror   ! return error code
47      CHARACTER(len=100)     ::  cn_dir_cdg                       ! Root directory for location of drag coefficient files
48      TYPE(FLD_N)            ::  sn_cdg                          ! informations about the fields to be read
49      !!---------------------------------------------------------------------
50      NAMELIST/namsbc_wave/  sn_cdg, cn_dir_cdg
51      !!---------------------------------------------------------------------
52
53      !!----------------------------------------------------------------------
54      !
55      !
56      !                                         ! -------------------- !
57      IF( kt == nit000 ) THEN                   ! First call kt=nit000 !
58         !                                      ! -------------------- !
59         !                                            !* set file information (default values)
60         ! ... default values (NB: frequency positive => hours, negative => months)
61         !              !   file   ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! weights  ! rotation !
62         !              !   name   !  (hours)  !   name     !   (T/F)    !  (T/F)  !  'monthly'  ! filename ! pairs    !
63         sn_cdg = FLD_N('cdg_wave'  ,    1     ,'drag_coeff',  .true.    , .false. ,   'daily'   , ''       , ''       )
64         cn_dir_cdg = './'          ! directory in which the Patm data are
65         
66
67         REWIND( numnam )                             !* read in namlist namsbc_wave
68         READ  ( numnam, namsbc_wave ) 
69         !
70
71         ALLOCATE( sf_wave(1), STAT=ierror )           !* allocate and fill sf_wave with sn_cdg
72         IF( ierror > 0 )   CALL ctl_stop( 'STOP', 'sbc_wave: unable to allocate sf_wave structure' )
73         !
74         CALL fld_fill( sf_wave, (/ sn_cdg /), cn_dir_cdg, 'sbc_wave', 'Wave module ', 'namsbc_wave' )
75                                ALLOCATE( sf_wave(1)%fnow(jpi,jpj,1)   )
76         IF( sn_cdg%ln_tint )   ALLOCATE( sf_wave(1)%fdta(jpi,jpj,1,2) )
77         ALLOCATE( cdn_wave(jpi,jpj) )
78         cdn_wave(:,:) = 0.0
79      ENDIF
80         !
81         !
82      CALL fld_read( kt, nn_fsbc, sf_wave )      !* read drag coefficient from external forcing
83      cdn_wave(:,:) = sf_wave(1)%fnow(:,:,1)
84
85   END SUBROUTINE sbc_wave
86     
87   !!======================================================================
88END MODULE sbcwave
Note: See TracBrowser for help on using the repository browser.