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

source: branches/dev_002_LIM/NEMO/OPA_SRC/SBC/albedo.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: 12.2 KB
RevLine 
[152]1MODULE albedo
2   !!======================================================================
3   !!                       ***  MODULE  albedo  ***
4   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice)
5   !!=====================================================================
6   !!----------------------------------------------------------------------
[719]7   !!   flx_blk_albedo : albedo for ocean and ice (clear and overcast skies)
[152]8   !!----------------------------------------------------------------------
[719]9   !! * Modules used
[152]10   USE oce             ! ocean dynamics and tracers
[719]11   USE dom_oce         ! ocean space and time domain
12   USE cpl_oce         ! ???
[152]13   USE phycst          ! physical constants
[719]14   USE daymod
15   USE blk_oce         ! bulk variables
16   USE flx_oce         ! forcings variables
17   USE ocfzpt          ! ???
[152]18   USE in_out_manager
[719]19   USE lbclnk
[152]20
21   IMPLICIT NONE
22   PRIVATE
23
[719]24   !! * Accessibility
25   PUBLIC flx_blk_albedo ! routine called by limflx.F90 in coupled
26                         ! and in flxblk.F90 in forced
27   !! * Module variables
28   INTEGER  ::             &  !: nameos : ocean physical parameters
29      albd_init = 0           !: control flag for initialization
[165]30
[719]31   REAL(wp)  ::            &  ! constant values
32      zzero   = 0.e0    ,  &
33      zone    = 1.0
[152]34
[719]35   !! * constants for albedo computation (flx_blk_albedo)
[152]36   REAL(wp) ::   &
[719]37      c1     = 0.05  ,     &   ! constants values
38      c2     = 0.10  ,     &
39      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
[703]40      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account
[719]41                               !  effects of cloudiness (Grenfell & Perovich, 1984)
[152]42      alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute
43      alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972)
[719]44      alphc  = 0.65  ,     &
45      zmue   = 0.40            !  cosine of local solar altitude
[152]46
47   !!----------------------------------------------------------------------
[719]48   !!   OPA 9.0 , LOCEAN-IPSL (2005)
49   !! $Header$
50   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
[152]51   !!----------------------------------------------------------------------
52
53CONTAINS
54
[826]55#if defined key_lim3
[152]56   !!----------------------------------------------------------------------
[826]57   !!   'key_lim3'                                         LIM ice model
[152]58   !!----------------------------------------------------------------------
59
[719]60   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
[152]61      !!----------------------------------------------------------------------
[719]62      !!               ***  ROUTINE flx_blk_albedo  ***
[152]63      !!         
64      !! ** Purpose :   Computation of the albedo of the snow/ice system
[719]65      !!      as well as the ocean one
[152]66      !!       
67      !! ** Method  : - Computation of the albedo of snow or ice (choose the
[719]68      !!      rignt one by a large number of tests
[152]69      !!              - Computation of the albedo of the ocean
70      !!
[719]71      !! References :
72      !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
73      !!
74      !! History :
75      !!  8.0   !  01-04  (LIM 1.0)
76      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
[703]77      !!----------------------------------------------------------------------
[719]78      !! * Modules used
79      USE ice                   ! ???
80
81      !! * Arguments
82      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
83         palb         ,     &    !  albedo of ice under overcast sky
84         palcn        ,     &    !  albedo of ocean under overcast sky
85         palbp        ,     &    !  albedo of ice under clear sky
86         palcnp                  !  albedo of ocean under clear sky
87
88      !! * Local variables
89      INTEGER ::    &
90         ji, jj                   ! dummy loop indices
91      REAL(wp) ::   & 
92         zmue14         ,     &   !  zmue**1.4
[152]93         zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting
94         zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing
95         zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow
96         zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow
97         zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
98         zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow)
99         zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1
100         zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2
[719]101      REAL(wp), DIMENSION(jpi,jpj) ::  &
102         zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice )
103         zficeth                  !  function of ice thickness
104      LOGICAL , DIMENSION(jpi,jpj) ::  &
105         llmask
[152]106      !!---------------------------------------------------------------------
107     
[719]108      ! initialization
109      IF( albd_init == 0 )   CALL albedo_init
[165]110
[719]111      !-------------------------                                                             
[152]112      !  Computation of  zficeth
[719]113      !--------------------------
[152]114     
115      llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice )
116      WHERE ( llmask )   !  ice free of snow and melts
117         zalbfz = albice
118      ELSEWHERE                   
119         zalbfz = alphdi
120      END WHERE
121     
122      DO jj = 1, jpj
123         DO ji = 1, jpi
124            IF( hicif(ji,jj) > 1.5 ) THEN
125               zficeth(ji,jj) = zalbfz(ji,jj)
126            ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN
127               zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 )
128            ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN
129               zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                &
130                  &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 &
131                  &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj)
132            ELSE
133               zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj) 
134            ENDIF
135         END DO
136      END DO
137     
138      !-----------------------------------------------
139      !    Computation of the snow/ice albedo system
140      !-------------------------- ---------------------
141     
142      !    Albedo of snow-ice for clear sky.
143      !-----------------------------------------------   
144      DO jj = 1, jpj
145         DO ji = 1, jpi
146            !  Case of ice covered by snow.             
147           
148            !  melting snow       
149            zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) )
150            zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) &
151               &                 + zihsc1   * alphd 
152            !  freezing snow               
153            zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) )
154            zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 &
155               &                 + zihsc2   * alphc 
156           
157            zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )   
158            zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm 
159           
160            !  Case of ice free of snow.
161            zalbpic      = zficeth(ji,jj) 
162           
163            ! albedo of the system   
164            zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) )
165            palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
166         END DO
167      END DO
168     
169      !    Albedo of snow-ice for overcast sky.
170      !---------------------------------------------- 
171      palb(:,:)   = palbp(:,:) + cgren                                           
172     
173      !--------------------------------------------
174      !    Computation of the albedo of the ocean
175      !-------------------------- -----------------                                                         
176     
[719]177      !  Parameterization of Briegled and Ramanathan, 1982
178      zmue14      = zmue**1.4                                       
179      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )               
180     
181      !  Parameterization of Kondratyev, 1969 and Payne, 1972
182      palcn(:,:)  = 0.06                                                 
183     
184   END SUBROUTINE flx_blk_albedo
[152]185
186# else
187   !!----------------------------------------------------------------------
188   !!   Default option :                                   NO sea-ice model
189   !!----------------------------------------------------------------------
190
[719]191   SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp )
[152]192      !!----------------------------------------------------------------------
[719]193      !!               ***  ROUTINE flx_blk_albedo  ***
[152]194      !!
[719]195      !! ** Purpose :   Computation of the albedo of the snow/ice system
196      !!      as well as the ocean one
[152]197      !!
[719]198      !! ** Method  :   Computation of the albedo of snow or ice (choose the
199      !!      wright one by a large number of tests Computation of the albedo
200      !!      of the ocean
[152]201      !!
[719]202      !! History :
203      !!  8.0   !  01-04  (LIM 1.0)
204      !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
[152]205      !!----------------------------------------------------------------------
[719]206      !! * Arguments
207      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  &
208         palb         ,     &    !  albedo of ice under overcast sky
209         palcn        ,     &    !  albedo of ocean under overcast sky
210         palbp        ,     &    !  albedo of ice under clear sky
211         palcnp                  !  albedo of ocean under clear sky
[152]212
[719]213      REAL(wp) ::   &
214         zmue14                 !  zmue**1.4
215      !!----------------------------------------------------------------------
[152]216
[719]217      !--------------------------------------------
218      !    Computation of the albedo of the ocean
219      !-------------------------- -----------------
[152]220
[719]221      !  Parameterization of Briegled and Ramanathan, 1982
222      zmue14      = zmue**1.4
223      palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )
224
225      !  Parameterization of Kondratyev, 1969 and Payne, 1972
226      palcn(:,:)  = 0.06
227
228      palb (:,:)  = palcn(:,:)
229      palbp(:,:)  = palcnp(:,:)
230
231   END SUBROUTINE flx_blk_albedo
232
[152]233#endif
[165]234
235   SUBROUTINE albedo_init
236      !!----------------------------------------------------------------------
237      !!                 ***  ROUTINE albedo_init  ***
238      !!
239      !! ** Purpose :   initializations for the albedo parameters
240      !!
241      !! ** Method  :   Read the namelist namalb
[719]242      !!
243      !! ** Action  : 
244      !!
245      !!
246      !! History :
247      !!   9.0  !  04-11  (C. Talandier)  Original code
[165]248      !!----------------------------------------------------------------------
[719]249      NAMELIST/namalb/ cgren, albice, alphd, alphdi, alphc
250      !!----------------------------------------------------------------------
251      !!  OPA 9.0, LODYC-IPSL (2004)
252      !!----------------------------------------------------------------------
[165]253
[719]254      ! set the initialization flag to 1
255      albd_init = 1           ! indicate that the initialization has been done
256
257      ! Read Namelist namalb : albedo parameters
258      REWIND( numnam )
[165]259      READ  ( numnam, namalb )
260
[719]261      ! Control print
262      IF(lwp) THEN
[165]263         WRITE(numout,*)
[719]264         WRITE(numout,*) 'albedo_init : albedo '
[165]265         WRITE(numout,*) '~~~~~~~~~~~'
[719]266         WRITE(numout,*) '          Namelist namalb : set albedo parameters'
267         WRITE(numout,*)
268         WRITE(numout,*) '             correction of the snow or ice albedo to take into account cgren = ', cgren
269         WRITE(numout,*) '             albedo of melting ice in the arctic and antarctic        albice = ', albice
270         WRITE(numout,*) '             coefficients for linear                                   alphd = ', alphd
271         WRITE(numout,*) '             interpolation used to compute albedo                     alphdi = ', alphdi
272         WRITE(numout,*) '             between two extremes values (Pyane, 1972)                 alphc = ', alphc
273         WRITE(numout,*)
[165]274      ENDIF
[719]275
[703]276   END SUBROUTINE albedo_init
[152]277   !!======================================================================
278END MODULE albedo
Note: See TracBrowser for help on using the repository browser.