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.
sbcdcy.F90 in trunk/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: trunk/NEMOGCM/NEMO/OPA_SRC/SBC/sbcdcy.F90 @ 3294

Last change on this file since 3294 was 3294, checked in by rblod, 12 years ago

Merge of 3.4beta into the trunk

  • Property svn:keywords set to Id
File size: 10.7 KB
RevLine 
[2198]1MODULE sbcdcy
2   !!======================================================================
3   !!                    ***  MODULE  sbcdcy  ***
4   !! Ocean forcing:  compute the diurnal cycle
5   !!======================================================================
6   !! History : OPA  !  2005-02  (D. Bernie)  Original code
7   !!   NEMO    2.0  !  2006-02  (S. Masson, G. Madec)  adaptation to NEMO
8   !!           3.1  !  2009-07  (J.M. Molines)  adaptation to v3.1
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
[2715]12   !!  sbc_dcy : solar flux at kt from daily mean, taking diurnal cycle into account
[2198]13   !!----------------------------------------------------------------------
14   USE oce              ! ocean dynamics and tracers
15   USE phycst           ! ocean physics
16   USE dom_oce          ! ocean space and time domain
[2228]17   USE sbc_oce          ! Surface boundary condition: ocean fields
[2198]18   USE in_out_manager   ! I/O manager
[2715]19   USE lib_mpp          ! MPP library
[3294]20   USE timing           ! Timing
[2198]21
22   IMPLICIT NONE
23   PRIVATE
[2715]24   
25   INTEGER, PUBLIC ::   nday_qsr   !: day when parameters were computed
26   
27   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   raa , rbb  , rcc  , rab     ! diurnal cycle parameters
28   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   rtmd, rdawn, rdusk, rscal   !    -      -       -
[2198]29 
[2715]30   PUBLIC   sbc_dcy        ! routine called by sbc
[2198]31
32   !!----------------------------------------------------------------------
33   !! NEMO/OPA 3.3 , NEMO-consortium (2010)
34   !! $Id$
[2715]35   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[2198]36   !!----------------------------------------------------------------------
37CONTAINS
38
[2715]39      INTEGER FUNCTION sbc_dcy_alloc()
40         !!----------------------------------------------------------------------
41         !!                ***  FUNCTION sbc_dcy_alloc  ***
42         !!----------------------------------------------------------------------
43         ALLOCATE( raa (jpi,jpj) , rbb  (jpi,jpj) , rcc  (jpi,jpj) , rab  (jpi,jpj) ,     &
44            &      rtmd(jpi,jpj) , rdawn(jpi,jpj) , rdusk(jpi,jpj) , rscal(jpi,jpj) , STAT=sbc_dcy_alloc )
45            !
46         IF( lk_mpp             )   CALL mpp_sum ( sbc_dcy_alloc )
47         IF( sbc_dcy_alloc /= 0 )   CALL ctl_warn('sbc_dcy_alloc: failed to allocate arrays')
48      END FUNCTION sbc_dcy_alloc
49
50
51   FUNCTION sbc_dcy( pqsrin ) RESULT( zqsrout )
[2198]52      !!----------------------------------------------------------------------
53      !!                  ***  ROUTINE sbc_dcy  ***
54      !!
55      !! ** Purpose : introduce a diurnal cycle of qsr from daily values
56      !!
57      !! ** Method  : see Appendix A of Bernie et al. 2007.
58      !!
59      !! ** Action  : redistribute daily QSR on each time step following the diurnal cycle
60      !!
61      !! reference  : Bernie, DJ, E Guilyardi, G Madec, JM Slingo, and SJ Woolnough, 2007
62      !!              Impact of resolving the diurnal cycle in an ocean--atmosphere GCM.
63      !!              Part 1: a diurnally forced OGCM. Climate Dynamics 29:6, 575-590.
64      !!----------------------------------------------------------------------
[2228]65      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   pqsrin    ! input daily QSR flux
[2198]66      !!
[2228]67      INTEGER  ::   ji, jj                                       ! dummy loop indices
[2198]68      REAL(wp) ::   ztwopi, zinvtwopi, zconvrad 
69      REAL(wp) ::   zlo, zup, zlousd, zupusd
[2228]70      REAL(wp) ::   zdsws, zdecrad, ztx, zsin, zcos
[2198]71      REAL(wp) ::   ztmp, ztmp1, ztmp2, ztest
[2228]72      REAL(wp), DIMENSION(jpi,jpj) ::   zqsrout                  ! output QSR flux with diurnal cycle
[2198]73      !---------------------------statement functions------------------------
[2228]74      REAL(wp) ::   fintegral, pt1, pt2, paaa, pbbb, pccc        ! dummy statement function arguments
[2198]75      fintegral( pt1, pt2, paaa, pbbb, pccc ) =                         &
76         &   paaa * pt2 + zinvtwopi * pbbb * SIN(pccc + ztwopi * pt2)   &
77         & - paaa * pt1 - zinvtwopi * pbbb * SIN(pccc + ztwopi * pt1)
78      !!---------------------------------------------------------------------
[3294]79      !
80      IF( nn_timing == 1 )  CALL timing_start('sbc_dcy')
81      !
[2198]82      ! Initialization
83      ! --------------
[2715]84      ztwopi    = 2._wp * rpi
85      zinvtwopi = 1._wp / ztwopi
86      zconvrad  = ztwopi / 360._wp
[2198]87
88      ! When are we during the day (from 0 to 1)
[2715]89      zlo = ( REAL(nsec_day, wp) - 0.5_wp * rdttra(1) ) / rday
90      zup = zlo + ( REAL(nn_fsbc, wp)     * rdttra(1) ) / rday
[2198]91      !                                         
[2228]92      IF( nday_qsr == -1 ) THEN       ! first time step only               
[2198]93         IF(lwp) THEN
94            WRITE(numout,*)
95            WRITE(numout,*) 'sbc_dcy : introduce diurnal cycle from daily mean qsr'
96            WRITE(numout,*) '~~~~~~~'
97            WRITE(numout,*)
98         ENDIF
[2715]99         ! allocate sbcdcy arrays
100         IF( sbc_dcy_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'sbc_dcy_alloc : unable to allocate arrays' )
[2198]101         ! Compute rcc needed to compute the time integral of the diurnal cycle
102         rcc(:,:) = zconvrad * glamt(:,:) - rpi
103         ! time of midday
104         rtmd(:,:) = 0.5 - glamt(:,:) / 360.
105         rtmd(:,:) = MOD( (rtmd(:,:) + 1.), 1. )
106      ENDIF
107
108      ! If this is a new day, we have to update the dawn, dusk and scaling function 
109      !----------------------
110   
111      !     2.1 dawn and dusk 
112
113      ! nday is the number of days since the beginning of the current month
114      IF( nday_qsr /= nday ) THEN 
115         ! save the day of the year and the daily mean of qsr
116         nday_qsr = nday 
117         ! number of days since the previous winter solstice (supposed to be always 21 December)         
[2228]118         zdsws = REAL(11 + nday_year, wp)
[2198]119         ! declination of the earths orbit
120         zdecrad = (-23.5 * zconvrad) * COS( zdsws * ztwopi / REAL(nyear_len(1),wp) )
121         ! Compute A and B needed to compute the time integral of the diurnal cycle
122       
[2228]123         zsin = SIN( zdecrad )   ;   zcos = COS( zdecrad )
[2198]124         DO jj = 1, jpj
125            DO ji = 1, jpi
126               ztmp = zconvrad * gphit(ji,jj)
[2228]127               raa(ji,jj) = SIN( ztmp ) * zsin
128               rbb(ji,jj) = COS( ztmp ) * zcos
[2198]129            END DO 
130         END DO 
131
132         ! Compute the time of dawn and dusk
133
134         ! rab to test if the day time is equal to 0, less than 24h of full day       
135         rab(:,:) = -raa(:,:) / rbb(:,:)
136         DO jj = 1, jpj
137            DO ji = 1, jpi
138               IF ( ABS(rab(ji,jj)) < 1 ) THEN         ! day duration is less than 24h
139         ! When is it night?
140                  ztx = zinvtwopi * (ACOS(rab(ji,jj)) - rcc(ji,jj))
141                  ztest = -rbb(ji,jj) * SIN( rcc(ji,jj) + ztwopi * ztx )
142         ! is it dawn or dusk?
143                  IF ( ztest > 0 ) THEN
144                     rdawn(ji,jj) = ztx
145                     rdusk(ji,jj) = rtmd(ji,jj) + ( rtmd(ji,jj) - rdawn(ji,jj) )
146                  ELSE
147                     rdusk(ji,jj) = ztx
148                     rdawn(ji,jj) = rtmd(ji,jj) - ( rdusk(ji,jj) - rtmd(ji,jj) )
149                  ENDIF
150               ELSE
151                  rdawn(ji,jj) = rtmd(ji,jj) + 0.5
152                  rdusk(ji,jj) = rdawn(ji,jj)
153               ENDIF
154             END DO 
155         END DO 
[2715]156         rdawn(:,:) = MOD( (rdawn(:,:) + 1._wp), 1._wp )
157         rdusk(:,:) = MOD( (rdusk(:,:) + 1._wp), 1._wp )
[2198]158
159         !     2.2 Compute the scalling function:
160         !         S* = the inverse of the time integral of the diurnal cycle from dawm to dusk
161         DO jj = 1, jpj
162            DO ji = 1, jpi
163               IF ( ABS(rab(ji,jj)) < 1 ) THEN         ! day duration is less than 24h
164                  IF ( rdawn(ji,jj) < rdusk(ji,jj) ) THEN      ! day time in one part
165                     rscal(ji,jj) = fintegral(rdawn(ji,jj), rdusk(ji,jj), raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
166                     rscal(ji,jj) = 1. / rscal(ji,jj)
167                  ELSE                                         ! day time in two parts
168                     rscal(ji,jj) = fintegral(0., rdusk(ji,jj), raa(ji,jj), rbb(ji,jj), rcc(ji,jj))   &
169                        &         + fintegral(rdawn(ji,jj), 1., raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
170                     rscal(ji,jj) = 1. / rscal(ji,jj)
171                  ENDIF
172               ELSE
173                  IF ( raa(ji,jj) > rbb(ji,jj) ) THEN         ! 24h day
174                     rscal(ji,jj) = fintegral(0., 1., raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
175                     rscal(ji,jj) = 1. / rscal(ji,jj)
176                  ELSE                                          ! No day
177                     rscal(ji,jj) = 0.e0
178                  ENDIF
179               ENDIF
180            END DO 
181         END DO 
182         !
[2228]183         ztmp = rday / ( rdttra(1) * REAL(nn_fsbc, wp) )
[2198]184         rscal(:,:) = rscal(:,:) * ztmp
[2715]185         !
[2198]186      ENDIF 
187
188         !     3. update qsr with the diurnal cycle
189         !     ------------------------------------
190
191      DO jj = 1, jpj
192         DO ji = 1, jpi
193            IF( ABS(rab(ji,jj)) < 1 ) THEN         ! day duration is less than 24h
194               !
195               IF( rdawn(ji,jj) < rdusk(ji,jj) ) THEN       ! day time in one part
196                  zlousd = MAX(zlo, rdawn(ji,jj))
197                  zlousd = MIN(zlousd, zup)
198                  zupusd = MIN(zup, rdusk(ji,jj))
199                  zupusd = MAX(zupusd, zlo)
200                  ztmp = fintegral(zlousd, zupusd, raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
[2228]201                  zqsrout(ji,jj) = pqsrin(ji,jj) * ztmp * rscal(ji,jj)
[2198]202                  !
203               ELSE                                         ! day time in two parts
204                  zlousd = MIN(zlo, rdusk(ji,jj))
205                  zupusd = MIN(zup, rdusk(ji,jj))
206                  ztmp1 = fintegral(zlousd, zupusd, raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
207                  zlousd = MAX(zlo, rdawn(ji,jj))
208                  zupusd = MAX(zup, rdawn(ji,jj))
209                  ztmp2 = fintegral(zlousd, zupusd, raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
210                  ztmp = ztmp1 + ztmp2
[2228]211                  zqsrout(ji,jj) = pqsrin(ji,jj) * ztmp * rscal(ji,jj)
[2198]212               ENDIF
213            ELSE                                   ! 24h light or 24h night
214               !
[2228]215               IF( raa(ji,jj) > rbb(ji,jj) ) THEN           ! 24h day
[2198]216                  ztmp = fintegral(zlo, zup, raa(ji,jj), rbb(ji,jj), rcc(ji,jj)) 
[2228]217                  zqsrout(ji,jj) = pqsrin(ji,jj) * ztmp * rscal(ji,jj)
[2198]218                  !
219               ELSE                                         ! No day
[2228]220                  zqsrout(ji,jj) = 0.e0
[2198]221               ENDIF
222            ENDIF
223         END DO 
224      END DO 
225      !
[3294]226      IF( nn_timing == 1 )  CALL timing_stop('sbc_dcy')
227      !
[2228]228   END FUNCTION sbc_dcy
[2198]229
230   !!======================================================================
231END MODULE sbcdcy
Note: See TracBrowser for help on using the repository browser.