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

source: trunk/NEMO/OPA_SRC/SBC/albedo.F90 @ 703

Last change on this file since 703 was 703, checked in by smasson, 17 years ago

code modifications associated with the new routines, see ticket:4

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 11.0 KB
Line 
1MODULE albedo
2   !!======================================================================
3   !!                       ***  MODULE  albedo  ***
4   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice)
5   !!=====================================================================
6   !! History :  8.0  !  01-04  (LIM 1.0)
7   !!            8.5  !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
8   !!            9.0  !  04-11  (C. Talandier)  add albedo_init
9   !!            9.0  !  06-08  (G. Madec)  cleaning for surface module
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   blk_albedo  : albedo for ocean and ice (clear and overcast skies)
14   !!   albedo_init : initialisation
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and tracers
17   USE phycst          ! physical constants
18   USE in_out_manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   blk_albedo   ! routine called by sbcice_lim module
24
25   INTEGER  ::   albd_init = 0    !: control flag for initialization
26
27   REAL(wp) ::   zzero   = 0.e0   ! constant values
28   REAL(wp) ::   zone    = 1.e0   !    "       "
29
30   REAL(wp) ::   c1     = 0.05    ! constants values
31   REAL(wp) ::   c2     = 0.10    !    "        "
32   REAL(wp) ::   cmue   = 0.40    !  cosine of local solar altitude
33
34   !!* namelist namalb
35   REAL(wp) ::   &
36      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account
37      !                        !  effects of cloudiness (Grenfell & Perovich, 1984)
38      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
39      alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute
40      alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972)
41      alphc  = 0.65 
42   NAMELIST/namalb/ cgren, albice, alphd, alphdi, alphc
43
44   !!----------------------------------------------------------------------
45   !!   OPA 9.0 , LOCEAN-IPSL (2006)
46   !! $Id$
47   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49
50CONTAINS
51
52#if defined key_ice_lim
53   !!----------------------------------------------------------------------
54   !!   'key_ice_lim'                                         LIM ice model
55   !!----------------------------------------------------------------------
56
57   SUBROUTINE blk_albedo( palb , palcn , palbp , palcnp )
58      !!----------------------------------------------------------------------
59      !!               ***  ROUTINE blk_albedo  ***
60      !!         
61      !! ** Purpose :   Computation of the albedo of the snow/ice system
62      !!                as well as the ocean one
63      !!       
64      !! ** Method  : - Computation of the albedo of snow or ice (choose the
65      !!                rignt one by a large number of tests
66      !!              - Computation of the albedo of the ocean
67      !!
68      !! References :   Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
69      !!----------------------------------------------------------------------
70      USE ice             ! ???
71      !!
72      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palb     ! albedo of ice under overcast sky
73      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palcn    ! albedo of ocean under overcast sky
74      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palbp    ! albedo of ice under clear sky
75      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palcnp   ! albedo of ocean under clear sky
76      !!
77      INTEGER  ::   ji, jj                   ! dummy loop indices
78      REAL(wp) ::   zcoef,    &   ! temporary scalar
79         zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting
80         zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing
81         zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow
82         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow
83         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
84         zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow)
85         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1
86         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2
87      LOGICAL , DIMENSION(jpi,jpj) ::   llmask    !
88      REAL(wp), DIMENSION(jpi,jpj) ::   zalbfz    ! ( = alphdi for freezing ice ; = albice for melting ice )
89      REAL(wp), DIMENSION(jpi,jpj) ::   zficeth   ! function of ice thickness
90      !!---------------------------------------------------------------------
91     
92      IF( albd_init == 0 )   CALL albedo_init      ! initialization
93
94      !---------------------------
95      !  Computation of  zficeth
96      !---------------------------
97     
98      llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice )
99      WHERE ( llmask )   !  ice free of snow and melts
100         zalbfz = albice
101      ELSEWHERE                   
102         zalbfz = alphdi
103      END WHERE
104     
105      DO jj = 1, jpj
106         DO ji = 1, jpi
107            IF( hicif(ji,jj) > 1.5 ) THEN
108               zficeth(ji,jj) = zalbfz(ji,jj)
109            ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN
110               zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 )
111            ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN
112               zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                &
113                  &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 &
114                  &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj)
115            ELSE
116               zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj) 
117            ENDIF
118         END DO
119      END DO
120     
121      !-----------------------------------------------
122      !    Computation of the snow/ice albedo system
123      !-------------------------- ---------------------
124     
125      !    Albedo of snow-ice for clear sky.
126      !-----------------------------------------------   
127      DO jj = 1, jpj
128         DO ji = 1, jpi
129            !  Case of ice covered by snow.             
130           
131            !  melting snow       
132            zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) )
133            zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) &
134               &                 + zihsc1   * alphd 
135            !  freezing snow               
136            zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) )
137            zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 &
138               &                 + zihsc2   * alphc 
139           
140            zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )   
141            zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm 
142           
143            !  Case of ice free of snow.
144            zalbpic      = zficeth(ji,jj) 
145           
146            ! albedo of the system   
147            zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) )
148            palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
149         END DO
150      END DO
151     
152      !    Albedo of snow-ice for overcast sky.
153      !---------------------------------------------- 
154      palb(:,:)   = palbp(:,:) + cgren                                           
155     
156      !--------------------------------------------
157      !    Computation of the albedo of the ocean
158      !-------------------------- -----------------                                                         
159     
160      zcoef = 0.05 / ( 1.1 * cmue**1.4 + 0.15 )        ! Parameterization of Briegled and Ramanathan, 1982
161      palcnp(:,:) = zcoef
162      palcn(:,:)  = 0.06                               ! Parameterization of Kondratyev, 1969 and Payne, 1972
163      !
164   END SUBROUTINE blk_albedo
165
166# else
167   !!----------------------------------------------------------------------
168   !!   Default option :                                   NO sea-ice model
169   !!----------------------------------------------------------------------
170
171   SUBROUTINE blk_albedo( palb , palcn , palbp , palcnp )
172      !!----------------------------------------------------------------------
173      !!               ***  ROUTINE blk_albedo  ***
174      !!
175      !! ** Purpose :   Computation of the albedo of the ocean
176      !!
177      !! ** Method  :   ....
178      !!----------------------------------------------------------------------
179      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palb     ! albedo of ice under overcast sky
180      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palcn    ! albedo of ocean under overcast sky
181      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palbp    ! albedo of ice under clear sky
182      REAL(wp), INTENT(out), DIMENSION(jpi,jpj) ::   palcnp   ! albedo of ocean under clear sky
183      !!
184      REAL(wp) ::   zcoef    ! temporary scalar
185      !!----------------------------------------------------------------------
186      !
187      zcoef = 0.05 / ( 1.1 * cmue**1.4 + 0.15 )
188
189      palcnp(:,:) = zcoef           ! Parameterization of Briegled and Ramanathan, 1982
190      palcn(:,:)  = 0.06            ! Parameterization of Kondratyev, 1969 and Payne, 1972
191
192      palb (:,:)  = zcoef           ! ice overcast  albedo set to oceanvalue
193      palbp(:,:)  = 0.06            ! ice clear sky albedo set to oceanvalue
194      !
195   END SUBROUTINE blk_albedo
196
197#endif
198
199   SUBROUTINE albedo_init
200      !!----------------------------------------------------------------------
201      !!                 ***  ROUTINE albedo_init  ***
202      !!
203      !! ** Purpose :   initializations for the albedo parameters
204      !!
205      !! ** Method  :   Read the namelist namalb
206      !!----------------------------------------------------------------------
207      !
208      albd_init = 1              ! set the initialization flag to 1 (done)
209
210      REWIND( numnam )           ! Read Namelist namalb : albedo parameters
211      READ  ( numnam, namalb )
212
213      IF(lwp) THEN               ! Control print
214         WRITE(numout,*)
215         WRITE(numout,*) 'albedo_init : set albedo parameters from namelist namalb'
216         WRITE(numout,*) '~~~~~~~~~~~'
217         WRITE(numout,*) '             correction for snow and ice albedo                    cgren  = ', cgren
218         WRITE(numout,*) '             albedo of melting ice in the arctic and antarctic     albice = ', albice
219         WRITE(numout,*) '             coefficients for linear                               alphd  = ', alphd
220         WRITE(numout,*) '             interpolation used to compute albedo                  alphdi = ', alphdi
221         WRITE(numout,*) '             between two extremes values (Pyane, 1972)             alphc  = ', alphc
222      ENDIF
223      !
224   END SUBROUTINE albedo_init
225
226   !!======================================================================
227END MODULE albedo
Note: See TracBrowser for help on using the repository browser.