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 branches/dev_002_LIM/NEMO/OPA_SRC/SBC – NEMO

source: branches/dev_002_LIM/NEMO/OPA_SRC/SBC/bulk.F90 @ 826

Last change on this file since 826 was 826, checked in by ctlod, 16 years ago

dev_002_LIM: change remaining cpp key key_ice_lim into key_lim3, see ticket:#71

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 5.0 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 flxblk_2        ! bulk formulae
19   USE blk_oce         ! bulk variable
20   USE flx_oce
21   USE taumod
22   USE phycst          ! physical constants
23   USE in_out_manager  ! I/O manager
24   USE prtctl          ! Print control
25
26   IMPLICIT NONE
27   PRIVATE
28
29   !! * Routine accessibility
30   PUBLIC blk        ! called by flx.F90   
31   !!----------------------------------------------------------------------
32   !!   OPA 9.0 , LOCEAN-IPSL (2005)
33   !! $Header$
34   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE blk( kt )
39      !!---------------------------------------------------------------------
40      !!                    ***  ROUTINE blk  ***
41      !!       
42      !! ** Purpose :   provide the heat fluxes on ice and ocean
43      !!                using bulk formulation
44      !!
45      !! History :
46      !!   9.0  !  03-11  (C. Ethe and G. Madec)  F90: Free form and MODULE
47      !!----------------------------------------------------------------------
48      !! * arguments
49      INTEGER, INTENT( in  ) ::   kt   ! ocean time step
50
51      !! * Local declarations   
52      REAL(wp), DIMENSION(jpi,jpj) ::   zsst 
53# if ( ! defined key_lim3 && !defined key_lim2 )
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        ENDIF
70     ENDIF
71
72# if ( ! defined key_lim3 && ! defined key_lim2 )
73      ! opa model ice freeze()     
74      DO jj = 1, jpj
75         DO ji = 1, jpi
76            ztgel  = fzptn(ji,jj)
77            zicopa = tmask(ji,jj,1)
78            IF( tn(ji,jj,1) >= ztgel ) zicopa = 0.
79            freeze(ji,jj) = zicopa
80         END DO
81      END DO
82# endif
83
84      gsst(:,:) = gsst(:,:) + tn(:,:,1) + rt0 
85
86      !  Computation of the fluxes       
87      IF( MOD( kt - 1 , nfbulk ) == 0 ) THEN
88
89         zsst(:,:) = gsst(:,:) / REAL( nfbulk ) * tmask(:,:,1)
90         IF ( .NOT. lk_lim2 )  CALL flx_blk( zsst )   
91
92#if defined key_lim2
93         CALL flx_blk_2( zsst )   
94#endif
95     
96         gsst(:,:) = 0.   
97
98# if ( ! defined key_lim3 && ! defined key_lim2 )
99         IF(ln_ctl) THEN         ! print mean trends (used for debugging)
100            CALL prt_ctl_info(' Forcings ')
101            CALL prt_ctl(tab2d_1=qsr_oce , clinfo1=' qsr_oce   : ', mask1=tmask, ovlap=1)
102            CALL prt_ctl(tab2d_1=qsr_ice , clinfo1=' qsr_ice   : ', mask1=tmask, ovlap=1)
103            CALL prt_ctl(tab2d_1=qnsr_oce, clinfo1=' qnsr_oce  : ', mask1=tmask, ovlap=1)
104            CALL prt_ctl(tab2d_1=qnsr_ice, clinfo1=' qnsr_ice  : ', mask1=tmask, ovlap=1)
105            CALL prt_ctl(tab2d_1=evap    , clinfo1=' evap      : ', mask1=tmask, ovlap=1)
106            CALL prt_ctl(tab2d_1=tprecip , clinfo1=' precip    : ', mask1=tmask, ovlap=1)
107            CALL prt_ctl(tab2d_1=sprecip , clinfo1=' Snow      : ', mask1=tmask, ovlap=1)
108            CALL prt_ctl(tab2d_1=taux    , clinfo1=' u-stress  : ', mask1=tmask, ovlap=1)
109            CALL prt_ctl(tab2d_1=tauy    , clinfo1=' v-stress  : ', mask1=tmask, ovlap=1)
110            CALL prt_ctl(tab2d_1=zsst    , clinfo1=' sst       : ', mask1=tmask, ovlap=1)
111         ENDIF
112# endif   
113      ENDIF
114 
115   END SUBROUTINE blk
116
117#else
118   !!----------------------------------------------------------------------
119   !!   Dummy module :                                     NO bulk formulea
120   !!----------------------------------------------------------------------
121CONTAINS
122   SUBROUTINE blk( kt )          ! Dummy routine
123      WRITE(*,*) 'blk: You should not see this print! error? ', kt
124   END SUBROUTINE blk
125#endif
126 
127   !!======================================================================
128END MODULE bulk
Note: See TracBrowser for help on using the repository browser.