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.
bulk.F90 in tags/nemo_v1_03/NEMO/OPA_SRC/SBC – NEMO

source: tags/nemo_v1_03/NEMO/OPA_SRC/SBC/bulk.F90 @ 5784

Last change on this file since 5784 was 258, checked in by opalod, 19 years ago

nemo_v1_update_004 : CT : Integration of the control print option for debugging work

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.1 KB
Line 
1MODULE bulk
2   !!======================================================================
3   !!                           ***  bulk  ***
4   !!======================================================================
5#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily
6   !!----------------------------------------------------------------------
7   !!   'key_flx_bulk_monthly'                        monthly bulk formulea
8   !!   'key_flx_bulk_daily'                          daily bulk formulea
9   !!----------------------------------------------------------------------
10   !!   bulk          : computation of fluxes using bulk formulation
11   !!----------------------------------------------------------------------
12   !! * Modules used   
13   USE oce             ! ocean dynamics and tracers
14   USE dom_oce         ! ocean space and time domain
15   USE ice_oce         ! bulk variable 
16   USE ocfzpt          ! ocean freezing point
17   USE flxblk          ! bulk formulae
18   USE blk_oce         ! bulk variable
19   USE flx_oce
20   USE taumod
21   USE phycst          ! physical constants
22   USE in_out_manager  ! I/O manager
23   USE prtctl          ! Print control
24
25   IMPLICIT NONE
26   PRIVATE
27
28   !! * Routine accessibility
29   PUBLIC blk        ! called by flx.F90   
30   !!----------------------------------------------------------------------
31   !!   OPA 9.0 , LOCEAN-IPSL (2005)
32   !! $Header$
33   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE blk( kt )
38      !!---------------------------------------------------------------------
39      !!                    ***  ROUTINE blk  ***
40      !!       
41      !! ** Purpose :   provide the heat fluxes on ice and ocean
42      !!                using bulk formulation
43      !!
44      !! History :
45      !!   9.0  !  03-11  (C. Ethe and G. Madec)  F90: Free form and MODULE
46      !!----------------------------------------------------------------------
47      !! * arguments
48      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
49
50      !! * Local declarations   
51      REAL(wp), DIMENSION(jpi,jpj) ::   &
52         zsst , zsss
53# if ! defined key_ice_lim
54      INTEGER  ::   ji, jj         ! dummy loop indices 
55      REAL(wp) ::   ztgel, zicopa
56# endif
57      !!---------------------------------------------------------------------
58
59     ! Initialisation
60     IF( kt == nit000) THEN
61      ! computation of rdtbs2
62        IF( nacc == 1 ) THEN
63           rdtbs2 = nfbulk * rdtmin * 0.5
64        ELSE
65           rdtbs2 = nfbulk * rdt * 0.5
66        ENDIF
67        IF ( .NOT.ln_rstart ) THEN
68           gsst(:,:) =  ( nfbulk - 1 ) * ( tn(:,:,1) + rt0 )
69           gsss(:,:) =  ( nfbulk - 1 ) *   sn(:,:,1)
70        ENDIF
71     ENDIF
72
73# if ! defined key_ice_lim
74      ! opa model ice freeze()     
75      DO jj = 1, jpj
76         DO ji = 1, jpi
77            ztgel  = fzptn(ji,jj)
78            zicopa = tmask(ji,jj,1)
79            IF( tn(ji,jj,1) >= ztgel ) zicopa = 0.
80            freeze(ji,jj) = zicopa
81         END DO
82      END DO
83# endif
84
85      gsst(:,:) = gsst(:,:) + tn(:,:,1) + rt0 
86      gsss(:,:) = gsss(:,:) + sn(:,:,1)
87
88      !  Computation of the fluxes       
89      IF( MOD( kt - 1 , nfbulk ) == 0 ) THEN
90
91!i       zsst(:,:) = gsst(:,:) / REAL( nfbulk )
92         zsst(:,:) = gsst(:,:) / REAL( nfbulk ) * tmask(:,:,1)
93         zsss(:,:) = gsss(:,:) / REAL( nfbulk )
94         CALL flx_blk( zsst )   
95     
96         gsst(:,:) = 0.   
97         gsss(:,:) = 0. 
98
99# if ! defined key_ice_lim
100         IF(ln_ctl) THEN         ! print mean trends (used for debugging)
101            CALL prt_ctl_info(' Forcings ')
102            CALL prt_ctl(tab2d_1=qsr_oce , clinfo1=' qsr_oce   : ', mask1=tmask, ovlap=1)
103            CALL prt_ctl(tab2d_1=qsr_ice , clinfo1=' qsr_ice   : ', mask1=tmask, ovlap=1)
104            CALL prt_ctl(tab2d_1=qnsr_oce, clinfo1=' qnsr_oce  : ', mask1=tmask, ovlap=1)
105            CALL prt_ctl(tab2d_1=qnsr_ice, clinfo1=' qnsr_ice  : ', mask1=tmask, ovlap=1)
106            CALL prt_ctl(tab2d_1=evap    , clinfo1=' evap      : ', mask1=tmask, ovlap=1)
107            CALL prt_ctl(tab2d_1=tprecip , clinfo1=' precip    : ', mask1=tmask, ovlap=1)
108            CALL prt_ctl(tab2d_1=sprecip , clinfo1=' Snow      : ', mask1=tmask, ovlap=1)
109            CALL prt_ctl(tab2d_1=taux    , clinfo1=' u-stress  : ', mask1=tmask, ovlap=1)
110            CALL prt_ctl(tab2d_1=tauy    , clinfo1=' v-stress  : ', mask1=tmask, ovlap=1)
111            CALL prt_ctl(tab2d_1=zsst    , clinfo1=' sst       : ', mask1=tmask, ovlap=1)
112            CALL prt_ctl(tab2d_1=zsss    , clinfo1=' sss       : ', mask1=tmask, ovlap=1)
113         ENDIF
114# endif   
115      ENDIF
116 
117   END SUBROUTINE blk
118
119#else
120   !!----------------------------------------------------------------------
121   !!   Dummy module :                                     NO bulk formulea
122   !!----------------------------------------------------------------------
123CONTAINS
124   SUBROUTINE blk( kt )          ! Dummy routine
125      WRITE(*,*) 'blk: You should not see this print! error? ', kt
126   END SUBROUTINE blk
127#endif
128 
129   !!======================================================================
130END MODULE bulk
Note: See TracBrowser for help on using the repository browser.