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_2.F90 in branches/dev_002_LIM/NEMO/LIM_SRC – NEMO

source: branches/dev_002_LIM/NEMO/LIM_SRC/albedo_2.F90 @ 822

Last change on this file since 822 was 821, checked in by rblod, 16 years ago

Change name of modules and subroutines for LIM2 with suffix _2, add albedo_2 and flxblk_2, see ticket #71

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