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.
Changeset 2188 for branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcblk_core.F90 – NEMO

Ignore:
Timestamp:
2010-10-08T10:32:36+02:00 (14 years ago)
Author:
smasson
Message:

code review but GM for dev_r2174_DCY

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_r2174_DCY/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r2187 r2188  
    1212   !!            3.0  !  2006-06  (G. Madec) sbc rewritting    
    1313   !!            3.2  !  2009-04  (B. Lemaire)  Introduce iom_put 
     14   !!            3.3  !  2010-10  (S. Masson)  add diurnal cycle 
    1415   !!---------------------------------------------------------------------- 
    1516 
     
    2627   USE fldread         ! read input fields 
    2728   USE sbc_oce         ! Surface boundary condition: ocean fields 
    28    USE sbcdcy          ! surface forcing: diurnal cycle 
     29   USE sbcdcy          ! surface boundary condition: diurnal cycle 
    2930   USE iom             ! I/O manager library 
    3031   USE in_out_manager  ! I/O manager 
     
    3536   USE sbc_ice         ! Surface boundary condition: ice fields 
    3637#endif 
    37  
    3838 
    3939   IMPLICIT NONE 
     
    6363   REAL(wp), PARAMETER ::   Cice =    1.63e-3     ! transfer coefficient over ice 
    6464 
    65    !                                !!* Namelist namsbc_core : CORE bulk parameters 
    66    LOGICAL  ::   ln_2m     = .FALSE.     ! logical flag for height of air temp. and hum 
    67    LOGICAL  ::   ln_taudif = .FALSE.     ! logical flag to use the "mean of stress module - module of mean stress" data 
    68    REAL(wp) ::   rn_pfac   = 1.          ! multiplication factor for precipitation 
     65   !                                  !!* Namelist namsbc_core : CORE bulk parameters 
     66   LOGICAL  ::   ln_2m     = .FALSE.   ! logical flag for height of air temp. and hum 
     67   LOGICAL  ::   ln_taudif = .FALSE.   ! logical flag to use the "mean of stress module - module of mean stress" data 
     68   REAL(wp) ::   rn_pfac   = 1.        ! multiplication factor for precipitation 
    6969 
    7070   !! * Substitutions 
     
    7272#  include "vectopt_loop_substitute.h90" 
    7373   !!---------------------------------------------------------------------- 
    74    !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)  
     74   !! NEMO/OPA 3.3 , NEMO-consortium (2010)  
    7575   !! $Id$ 
    7676   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    7777   !!---------------------------------------------------------------------- 
    78  
    7978CONTAINS 
    8079 
     
    145144         sn_tdif = FLD_N( 'taudif'  ,    24     ,  'taudif'  ,  .true.    , .false. ,   'yearly'  , ''       , ''         ) 
    146145         ! 
    147          REWIND( numnam )                    ! ... read in namlist namsbc_core 
     146         REWIND( numnam )                          ! read in namlist namsbc_core 
    148147         READ  ( numnam, namsbc_core ) 
    149          ! 
    150          ! do we plan to use ln_dm2dc with non-daily forcing? 
    151          IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   & 
     148         !                                         ! check: do we plan to use ln_dm2dc with non-daily forcing? 
     149         IF( ln_dm2dc .AND. sn_qsr%nfreqh /= 24 )   &  
    152150            &   CALL ctl_stop( 'sbc_blk_core: ln_dm2dc can be activated only with daily short-wave forcing' )  
    153151         IF( ln_dm2dc .AND. sn_qsr%ln_tint ) THEN 
     
    156154            sn_qsr%ln_tint = .false. 
    157155         ENDIF 
    158          ! 
    159          ! store namelist information in an array 
     156         !                                         ! store namelist information in an array 
    160157         slf_i(jp_wndi) = sn_wndi   ;   slf_i(jp_wndj) = sn_wndj 
    161158         slf_i(jp_qsr ) = sn_qsr    ;   slf_i(jp_qlw ) = sn_qlw 
     
    163160         slf_i(jp_prec) = sn_prec   ;   slf_i(jp_snow) = sn_snow 
    164161         slf_i(jp_tdif) = sn_tdif 
    165          ! 
    166          ! do we use HF tau information? 
    167          lhftau = ln_taudif 
     162         !                  
     163         lhftau = ln_taudif                        ! do we use HF tau information? 
    168164         jfld = jpfld - COUNT( (/.NOT. lhftau/) ) 
    169165         ! 
    170          ! set sf structure 
    171          ALLOCATE( sf(jfld), STAT=ierror ) 
     166         ALLOCATE( sf(jfld), STAT=ierror )         ! set sf structure 
    172167         IF( ierror > 0 ) THEN 
    173168            CALL ctl_stop( 'sbc_blk_core: unable to allocate sf structure' )   ;   RETURN 
     
    177172            ALLOCATE( sf(ifpr)%fdta(jpi,jpj,2) ) 
    178173         END DO 
    179          ! 
    180          ! fill sf with slf_i and control print 
     174         !                                         ! fill sf with slf_i and control print 
    181175         CALL fld_fill( sf, slf_i, cn_dir, 'sbc_blk_core', 'flux formulation for ocean surface boundary condition', 'namsbc_core' ) 
    182176         ! 
    183177      ENDIF 
    184178 
    185       CALL fld_read( kt, nn_fsbc, sf )                   ! input fields provided at the current time-step 
    186  
    187       IF( ln_dm2dc )   CALL sbc_dcy( kt , sf(jp_qsr)%fnow )   ! modify sf(jp_qsr)%fnow for diurnal cycle 
     179                       CALL fld_read( kt, nn_fsbc, sf )        ! input fields provided at the current time-step 
     180 
     181      IF( ln_dm2dc )   CALL sbc_dcy ( kt , sf(jp_qsr)%fnow )   ! modify now Qsr to include the diurnal cycle 
    188182 
    189183#if defined key_lim3 
    190       tatm_ice(:,:) = sf(jp_tair)%fnow(:,:) 
     184      tatm_ice(:,:) = sf(jp_tair)%fnow(:,:)                    ! LIM3: make Tair available in sea-ice 
    191185#endif 
    192  
    193       IF( MOD( kt - 1, nn_fsbc ) == 0 ) THEN 
    194           CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m )   ! compute the surface ocean fluxes using CLIO bulk formulea 
    195       ENDIF 
    196       !                                                  ! using CORE bulk formulea 
     186      !                                                        ! surface ocean fluxes computed with CLIO bulk formulea 
     187      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce_core( sf, sst_m, ssu_m, ssv_m ) 
     188      ! 
    197189   END SUBROUTINE sbc_blk_core 
    198190    
Note: See TracChangeset for help on using the changeset viewer.