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/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/OPA_SRC/SBC – NEMO

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/OPA_SRC/SBC/albedo.F90 @ 3152

Last change on this file since 3152 was 3152, checked in by smasson, 12 years ago

dev_NEMO_MERGE_2011: new dynamical allocation in IOM and SBC

  • Property svn:keywords set to Id
File size: 11.6 KB
RevLine 
[152]1MODULE albedo
2   !!======================================================================
3   !!                       ***  MODULE  albedo  ***
4   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice)
5   !!=====================================================================
[1601]6   !! History :  8.0  ! 2001-04  (LIM 1.0)
7   !!   NEMO     1.0  ! 2003-07  (C. Ethe, G. Madec)  Optimization (old name:shine)
8   !!             -   ! 2004-11  (C. Talandier)  add albedo_init
9   !!             -   ! 2001-06  (M. Vancoppenolle) LIM 3.0
10   !!             -   ! 2006-08  (G. Madec)  cleaning for surface module
[152]11   !!----------------------------------------------------------------------
[1601]12
13   !!----------------------------------------------------------------------
[888]14   !!   albedo_ice  : albedo for   ice (clear and overcast skies)
15   !!   albedo_oce  : albedo for ocean (clear and overcast skies)
16   !!   albedo_init : initialisation of albedo computation
[152]17   !!----------------------------------------------------------------------
18   USE phycst          ! physical constants
[888]19   USE in_out_manager  ! I/O manager
[2715]20   USE lib_mpp         ! MPP library
[3152]21   USE wrk_nemo_2      ! work arrays
[152]22
23   IMPLICIT NONE
24   PRIVATE
25
[1601]26   PUBLIC   albedo_ice   ! routine called sbcice_lim.F90
27   PUBLIC   albedo_oce   ! routine called by ???
[165]28
[888]29   INTEGER  ::   albd_init = 0      !: control flag for initialization
30   REAL(wp) ::   zzero     = 0.e0   ! constant values
31   REAL(wp) ::   zone      = 1.e0   !    "       "
[152]32
[888]33   REAL(wp) ::   c1     = 0.05    ! constants values
34   REAL(wp) ::   c2     = 0.10    !    "        "
35   REAL(wp) ::   rmue   = 0.40    !  cosine of local solar altitude
36
[1601]37   !                               !!* namelist namsbc_alb
38   REAL(wp) ::   rn_cloud  = 0.06   !  cloudiness effect on snow or ice albedo (Grenfell & Perovich, 1984)
[833]39#if defined key_lim3
[1601]40   REAL(wp) ::   rn_albice = 0.53   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
[833]41#else
[1601]42   REAL(wp) ::   rn_albice = 0.50   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers)
[833]43#endif
[1601]44   REAL(wp) ::   rn_alphd  = 0.80   !  coefficients for linear interpolation used to compute
45   REAL(wp) ::   rn_alphdi = 0.72   !  albedo between two extremes values (Pyane, 1972)
46   REAL(wp) ::   rn_alphc  = 0.65   !
[152]47
48   !!----------------------------------------------------------------------
[2528]49   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
[888]50   !! $Id$
[2715]51   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
[152]52   !!----------------------------------------------------------------------
53CONTAINS
54
[888]55   SUBROUTINE albedo_ice( pt_ice, ph_ice, ph_snw, pa_ice_cs, pa_ice_os )
[152]56      !!----------------------------------------------------------------------
[888]57      !!               ***  ROUTINE albedo_ice  ***
[152]58      !!         
59      !! ** Purpose :   Computation of the albedo of the snow/ice system
[888]60      !!                as well as the ocean one
[152]61      !!       
62      !! ** Method  : - Computation of the albedo of snow or ice (choose the
[888]63      !!                rignt one by a large number of tests
[152]64      !!              - Computation of the albedo of the ocean
65      !!
[888]66      !! References :   Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250.
67      !!----------------------------------------------------------------------
[1463]68      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pt_ice      !  ice surface temperature (Kelvin)
[888]69      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_ice      !  sea-ice thickness
70      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_snw      !  snow thickness
71      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pa_ice_cs   !  albedo of ice under clear    sky
72      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pa_ice_os   !  albedo of ice under overcast sky
[719]73      !!
[888]74      INTEGER  ::   ji, jj, jl    ! dummy loop indices
75      INTEGER  ::   ijpl          ! number of ice categories (3rd dim of ice input arrays)
76      REAL(wp) ::   zalbpsnm      ! albedo of ice under clear sky when snow is melting
77      REAL(wp) ::   zalbpsnf      ! albedo of ice under clear sky when snow is freezing
78      REAL(wp) ::   zalbpsn       ! albedo of snow/ice system when ice is coverd by snow
79      REAL(wp) ::   zalbpic       ! albedo of snow/ice system when ice is free of snow
80      REAL(wp) ::   zithsn        ! = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow)
81      REAL(wp) ::   zitmlsn       ! = 1 freezinz snow (pt_ice >=rt0_snow) ; = 0 melting snow (pt_ice<rt0_snow)
82      REAL(wp) ::   zihsc1        ! = 1 hsn <= c1 ; = 0 hsn > c1
83      REAL(wp) ::   zihsc2        ! = 1 hsn >= c2 ; = 0 hsn < c2
84      !!
[2715]85      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zalbfz    ! = rn_alphdi for freezing ice ; = rn_albice for melting ice
86      REAL(wp), POINTER, DIMENSION(:,:,:) ::   zficeth   !  function of ice thickness
[152]87      !!---------------------------------------------------------------------
88     
[888]89      ijpl = SIZE( pt_ice, 3 )                     ! number of ice categories
[165]90
[3152]91      CALL wrk_alloc( jpi,jpj,ijpl, zalbfz, zficeth )
[2715]92
[888]93      IF( albd_init == 0 )   CALL albedo_init      ! initialization
94
95      !---------------------------
[152]96      !  Computation of  zficeth
[888]97      !---------------------------
98      ! ice free of snow and melts
[2715]99      WHERE     ( ph_snw == 0._wp .AND. pt_ice >= rt0_ice )   ;   zalbfz(:,:,:) = rn_albice
100      ELSE WHERE                                              ;   zalbfz(:,:,:) = rn_alphdi
101      END  WHERE
102
103      WHERE     ( 1.5  < ph_ice                     )  ;  zficeth = zalbfz
104      ELSE WHERE( 1.0  < ph_ice .AND. ph_ice <= 1.5 )  ;  zficeth = 0.472  + 2.0 * ( zalbfz - 0.472 ) * ( ph_ice - 1.0 )
105      ELSE WHERE( 0.05 < ph_ice .AND. ph_ice <= 1.0 )  ;  zficeth = 0.2467 + 0.7049 * ph_ice              &
106         &                                                                 - 0.8608 * ph_ice * ph_ice     &
107         &                                                                 + 0.3812 * ph_ice * ph_ice * ph_ice
108      ELSE WHERE                                       ;  zficeth = 0.1    + 3.6    * ph_ice
[152]109      END WHERE
[888]110
[2715]111!!gm old code
112!      DO jl = 1, ijpl
113!         DO jj = 1, jpj
114!            DO ji = 1, jpi
115!               IF( ph_ice(ji,jj,jl) > 1.5 ) THEN
116!                  zficeth(ji,jj,jl) = zalbfz(ji,jj,jl)
117!               ELSEIF( ph_ice(ji,jj,jl) > 1.0  .AND. ph_ice(ji,jj,jl) <= 1.5 ) THEN
118!                  zficeth(ji,jj,jl) = 0.472 + 2.0 * ( zalbfz(ji,jj,jl) - 0.472 ) * ( ph_ice(ji,jj,jl) - 1.0 )
119!               ELSEIF( ph_ice(ji,jj,jl) > 0.05 .AND. ph_ice(ji,jj,jl) <= 1.0 ) THEN
120!                  zficeth(ji,jj,jl) = 0.2467 + 0.7049 * ph_ice(ji,jj,jl)                               &
121!                     &                    - 0.8608 * ph_ice(ji,jj,jl) * ph_ice(ji,jj,jl)                 &
122!                     &                    + 0.3812 * ph_ice(ji,jj,jl) * ph_ice(ji,jj,jl) * ph_ice (ji,jj,jl)
123!               ELSE
124!                  zficeth(ji,jj,jl) = 0.1 + 3.6 * ph_ice(ji,jj,jl)
125!               ENDIF
126!            END DO
127!         END DO
128!      END DO
129!!gm end old code
[152]130     
131      !-----------------------------------------------
132      !    Computation of the snow/ice albedo system
133      !-------------------------- ---------------------
134     
135      !    Albedo of snow-ice for clear sky.
136      !-----------------------------------------------   
[888]137      DO jl = 1, ijpl
[833]138         DO jj = 1, jpj
139            DO ji = 1, jpi
140               !  Case of ice covered by snow.             
[888]141               !                                        !  freezing snow       
142               zihsc1   = 1.0 - MAX( zzero , SIGN( zone , - ( ph_snw(ji,jj,jl) - c1 ) ) )
[1601]143               zalbpsnf = ( 1.0 - zihsc1 ) * (  zficeth(ji,jj,jl)                                             &
144                  &                           + ph_snw(ji,jj,jl) * ( rn_alphd - zficeth(ji,jj,jl) ) / c1  )   &
145                  &     +         zihsc1   * rn_alphd 
[888]146               !                                        !  melting snow               
147               zihsc2   = MAX( zzero , SIGN( zone , ph_snw(ji,jj,jl) - c2 ) )
[1601]148               zalbpsnm = ( 1.0 - zihsc2 ) * ( rn_albice + ph_snw(ji,jj,jl) * ( rn_alphc - rn_albice ) / c2 )   &
149                  &     +         zihsc2   *   rn_alphc 
[888]150               !
151               zitmlsn  =  MAX( zzero , SIGN( zone , pt_ice(ji,jj,jl) - rt0_snow ) )   
152               zalbpsn  =  zitmlsn * zalbpsnm + ( 1.0 - zitmlsn ) * zalbpsnf
[833]153           
154               !  Case of ice free of snow.
[888]155               zalbpic  = zficeth(ji,jj,jl) 
[833]156           
157               ! albedo of the system   
[888]158               zithsn   = 1.0 - MAX( zzero , SIGN( zone , - ph_snw(ji,jj,jl) ) )
159               pa_ice_cs(ji,jj,jl) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic
[833]160            END DO
161         END DO
162      END DO
163     
164      !    Albedo of snow-ice for overcast sky.
165      !---------------------------------------------- 
[1601]166      pa_ice_os(:,:,:) = pa_ice_cs(:,:,:) + rn_cloud       ! Oberhuber correction
[888]167      !
[3152]168      CALL wrk_dealloc( jpi,jpj,ijpl, zalbfz, zficeth )
[2715]169      !
[888]170   END SUBROUTINE albedo_ice
[833]171
172
[888]173   SUBROUTINE albedo_oce( pa_oce_os , pa_oce_cs )
[152]174      !!----------------------------------------------------------------------
[888]175      !!               ***  ROUTINE albedo_oce  ***
[152]176      !!
[888]177      !! ** Purpose :   Computation of the albedo of the ocean
178      !!----------------------------------------------------------------------
[2715]179      REAL(wp), DIMENSION(:,:), INTENT(out) ::   pa_oce_os   !  albedo of ocean under overcast sky
180      REAL(wp), DIMENSION(:,:), INTENT(out) ::   pa_oce_cs   !  albedo of ocean under clear sky
[152]181      !!
[2715]182      REAL(wp) ::   zcoef   ! local scalar
[152]183      !!----------------------------------------------------------------------
[888]184      !
185      zcoef = 0.05 / ( 1.1 * rmue**1.4 + 0.15 )      ! Parameterization of Briegled and Ramanathan, 1982
186      pa_oce_cs(:,:) = zcoef               
187      pa_oce_os(:,:)  = 0.06                         ! Parameterization of Kondratyev, 1969 and Payne, 1972
188      !
189   END SUBROUTINE albedo_oce
[152]190
191
[165]192   SUBROUTINE albedo_init
193      !!----------------------------------------------------------------------
194      !!                 ***  ROUTINE albedo_init  ***
195      !!
196      !! ** Purpose :   initializations for the albedo parameters
197      !!
[1601]198      !! ** Method  :   Read the namelist namsbc_alb
[165]199      !!----------------------------------------------------------------------
[1601]200      NAMELIST/namsbc_alb/ rn_cloud, rn_albice, rn_alphd, rn_alphdi, rn_alphc
[719]201      !!----------------------------------------------------------------------
[1601]202      !
203      albd_init = 1                     ! indicate that the initialization has been done
204      !
205      REWIND( numnam )                  ! Read Namelist namsbc_alb : albedo parameters
206      READ  ( numnam, namsbc_alb )
207      !
208      IF(lwp) THEN                      ! Control print
[165]209         WRITE(numout,*)
[1601]210         WRITE(numout,*) 'albedo : set albedo parameters'
211         WRITE(numout,*) '~~~~~~~'
212         WRITE(numout,*) '   Namelist namsbc_alb : albedo '
213         WRITE(numout,*) '      correction for snow and ice albedo                  rn_cloud  = ', rn_cloud
214         WRITE(numout,*) '      albedo of melting ice in the arctic and antarctic   rn_albice = ', rn_albice
215         WRITE(numout,*) '      coefficients for linear                             rn_alphd  = ', rn_alphd
216         WRITE(numout,*) '      interpolation used to compute albedo                rn_alphdi = ', rn_alphdi
217         WRITE(numout,*) '      between two extremes values (Pyane, 1972)           rn_alphc  = ', rn_alphc
[165]218      ENDIF
[888]219      !
220   END SUBROUTINE albedo_init
[719]221
[152]222   !!======================================================================
223END MODULE albedo
Note: See TracBrowser for help on using the repository browser.