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

Ignore:
Timestamp:
2008-04-11T19:05:03+02:00 (16 years ago)
Author:
ctlod
Message:

merge dev_001_SBC branche with the trunk to include the New Surface Module package, see ticket: #113

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/SBC/albedo.F90

    r833 r888  
    44   !! Ocean forcing:  bulk thermohaline forcing of the ocean (or ice) 
    55   !!===================================================================== 
    6    !!---------------------------------------------------------------------- 
    7    !!   flx_blk_albedo : albedo for ocean and ice (clear and overcast skies) 
    8    !!---------------------------------------------------------------------- 
    9    !! * Modules used 
    10    USE oce             ! ocean dynamics and tracers 
    11    USE dom_oce         ! ocean space and time domain 
    12    USE cpl_oce         ! ??? 
     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   !!             -   !  01-06  (M. Vancoppenolle) LIM 3.0 
     10   !!             -   !  06-08  (G. Madec)  cleaning for surface module 
     11   !!---------------------------------------------------------------------- 
     12   !!   albedo_ice  : albedo for   ice (clear and overcast skies) 
     13   !!   albedo_oce  : albedo for ocean (clear and overcast skies) 
     14   !!   albedo_init : initialisation of albedo computation 
     15   !!---------------------------------------------------------------------- 
    1316   USE phycst          ! physical constants 
    14    USE daymod 
    15    USE blk_oce         ! bulk variables 
    16    USE flx_oce         ! forcings variables 
    17    USE ocfzpt          ! ??? 
    18    USE in_out_manager 
    19    USE lbclnk 
     17   USE in_out_manager  ! I/O manager 
    2018 
    2119   IMPLICIT NONE 
    2220   PRIVATE 
    2321 
    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 
    30  
    31    REAL(wp)  ::            &  ! constant values 
    32       zzero   = 0.e0    ,  & 
    33       zone    = 1.0 
    34  
    35    !! * constants for albedo computation (flx_blk_albedo) 
     22   PUBLIC albedo_ice   ! routine called sbcice_lim.F90 
     23   PUBLIC albedo_oce   ! routine called by ??? 
     24 
     25   INTEGER  ::   albd_init = 0      !: control flag for initialization 
     26   REAL(wp) ::   zzero     = 0.e0   ! constant values 
     27   REAL(wp) ::   zone      = 1.e0   !    "       " 
     28 
     29   REAL(wp) ::   c1     = 0.05    ! constants values 
     30   REAL(wp) ::   c2     = 0.10    !    "        " 
     31   REAL(wp) ::   rmue   = 0.40    !  cosine of local solar altitude 
     32 
     33   !!* namelist namalb 
    3634   REAL(wp) ::   & 
    37       c1     = 0.05  ,     &   ! constants values 
    38       c2     = 0.10  ,     & 
     35      cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account 
     36      !                        !  effects of cloudiness (Grenfell & Perovich, 1984) 
    3937#if defined key_lim3 
    4038      albice = 0.53  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers) 
     
    4240      albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers) 
    4341#endif 
    44       cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account 
    45                                !  effects of cloudiness (Grenfell & Perovich, 1984) 
    4642      alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute 
    4743      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  
     44      alphc  = 0.65  
     45 
     46   !!---------------------------------------------------------------------- 
     47   !!   OPA 9.0 , LOCEAN-IPSL (2006)  
     48   !! $Id$ 
     49   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    5550   !!---------------------------------------------------------------------- 
    5651 
    5752CONTAINS 
    5853 
    59 #if defined key_lim3 || defined key_lim2 
    60    !!---------------------------------------------------------------------- 
    61    !!   'key_lim3' OR 'key_lim2'               LIM 2.0 or LIM 3.0 ice model 
    62    !!---------------------------------------------------------------------- 
    63  
    64    SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp ) 
    65       !!---------------------------------------------------------------------- 
    66       !!               ***  ROUTINE flx_blk_albedo  *** 
     54   SUBROUTINE albedo_ice( pt_ice, ph_ice, ph_snw, pa_ice_cs, pa_ice_os ) 
     55      !!---------------------------------------------------------------------- 
     56      !!               ***  ROUTINE albedo_ice  *** 
    6757      !!           
    6858      !! ** Purpose :   Computation of the albedo of the snow/ice system  
    69       !!      as well as the ocean one 
     59      !!                as well as the ocean one 
    7060      !!        
    7161      !! ** Method  : - Computation of the albedo of snow or ice (choose the  
    72       !!      rignt one by a large number of tests 
     62      !!                rignt one by a large number of tests 
    7363      !!              - Computation of the albedo of the ocean 
    7464      !! 
    75       !! References : 
    76       !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250. 
    77       !! 
    78       !! History : 
    79       !!  8.0   !  01-04  (LIM 1.0) 
    80       !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine) 
    81       !!  9.0   !  01-06  (M. Vancoppenolle) LIM 3.0 
    82       !!---------------------------------------------------------------------- 
    83       !! * Modules used 
    84 #if defined key_lim3 
    85       USE par_ice 
    86       USE ice                   ! ??? 
    87 #elif defined key_lim2 
    88       USE ice_2                 ! ??? 
    89 #endif 
    90  
    91       !! * Arguments 
    92 #if defined key_lim3 
    93       REAL(wp), DIMENSION(jpi,jpj,jpl), INTENT(out) ::  & 
    94 #elif defined key_lim2 
    95       REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    96 #endif 
    97          palb         ,     &    !  albedo of ice under overcast sky 
    98          palbp                   !  albedo of ice under clear sky  
    99       REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    100          palcn        ,     &    !  albedo of ocean under overcast sky 
    101          palcnp                  !  albedo of ocean under clear sky 
    102  
    103       !! * Local variables 
    104       INTEGER ::    & 
    105          ji, jj, jl               ! dummy loop indices 
    106       REAL(wp) ::   &  
    107          zmue14         ,     &   !  zmue**1.4 
    108          zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting 
    109          zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing 
    110          zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow 
    111          zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow 
    112          zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow) 
    113          zitmlsn        ,     &   !  = 1 freezinz snow (t_su >=rt0_snow) ; = 0 melting snow (t_su<rt0_snow) 
    114          zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1 
    115          zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2 
    116 #if defined key_lim3 
    117       REAL(wp), DIMENSION(jpi,jpj,jpl) ::  & 
    118 #elif defined key_lim2 
    119       REAL(wp), DIMENSION(jpi,jpj) ::  & 
    120 #endif 
    121          zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice ) 
    122          zficeth                  !  function of ice thickness 
    123 #if defined key_lim3 
    124       LOGICAL , DIMENSION(jpi,jpj,jpl) ::  & 
    125 #elif defined key_lim2 
    126       LOGICAL , DIMENSION(jpi,jpj) ::  & 
    127 #endif 
    128          llmask 
     65      !! References :   Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250. 
     66      !!---------------------------------------------------------------------- 
     67      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   pt_ice      !  ice surface temperature 
     68      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_ice      !  sea-ice thickness 
     69      REAL(wp), INTENT(in   ), DIMENSION(:,:,:) ::   ph_snw      !  snow thickness 
     70      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pa_ice_cs   !  albedo of ice under clear    sky 
     71      REAL(wp), INTENT(  out), DIMENSION(:,:,:) ::   pa_ice_os   !  albedo of ice under overcast sky 
     72      !! 
     73      INTEGER  ::   ji, jj, jl    ! dummy loop indices 
     74      INTEGER  ::   ijpl          ! number of ice categories (3rd dim of ice input arrays) 
     75      REAL(wp) ::   zalbpsnm      ! albedo of ice under clear sky when snow is melting 
     76      REAL(wp) ::   zalbpsnf      ! albedo of ice under clear sky when snow is freezing 
     77      REAL(wp) ::   zalbpsn       ! albedo of snow/ice system when ice is coverd by snow 
     78      REAL(wp) ::   zalbpic       ! albedo of snow/ice system when ice is free of snow 
     79      REAL(wp) ::   zithsn        ! = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow) 
     80      REAL(wp) ::   zitmlsn       ! = 1 freezinz snow (pt_ice >=rt0_snow) ; = 0 melting snow (pt_ice<rt0_snow) 
     81      REAL(wp) ::   zihsc1        ! = 1 hsn <= c1 ; = 0 hsn > c1 
     82      REAL(wp) ::   zihsc2        ! = 1 hsn >= c2 ; = 0 hsn < c2 
     83      !! 
     84      LOGICAL , DIMENSION(jpi,jpj,SIZE(pt_ice,3)) ::   llmask 
     85      REAL(wp), DIMENSION(jpi,jpj,SIZE(pt_ice,3)) ::   zalbfz    ! = alphdi for freezing ice ; = albice for melting ice 
     86      REAL(wp), DIMENSION(jpi,jpj,SIZE(pt_ice,3)) ::   zficeth   !  function of ice thickness 
    12987      !!--------------------------------------------------------------------- 
    13088       
    131       ! initialization  
    132       IF( albd_init == 0 )   CALL albedo_init 
    133  
    134       !-------------------------                                                              
     89      ijpl = SIZE( pt_ice, 3 )                     ! number of ice categories 
     90 
     91      IF( albd_init == 0 )   CALL albedo_init      ! initialization  
     92 
     93      !--------------------------- 
    13594      !  Computation of  zficeth 
    136       !--------------------------  
    137 #if defined key_lim3 
    138       llmask = (ht_s(:,:,:) == 0.e0) .AND. ( t_su(:,:,:) >= rt0_ice ) 
    139 #elif defined key_lim2       
    140       llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice ) 
    141 #endif 
    142       WHERE ( llmask )   !  ice free of snow and melts 
    143          zalbfz = albice 
    144       ELSEWHERE                    
    145          zalbfz = alphdi 
     95      !--------------------------- 
     96      llmask = ( ph_snw == 0.e0 ) .AND. ( pt_ice >= rt0_ice ) 
     97      ! ice free of snow and melts 
     98      WHERE( llmask )   ;   zalbfz = albice 
     99      ELSEWHERE         ;   zalbfz = alphdi 
    146100      END WHERE 
    147        
    148 #if defined key_lim3 
    149       DO jl = 1, jpl 
     101 
     102      DO jl = 1, ijpl 
    150103         DO jj = 1, jpj 
    151104            DO ji = 1, jpi 
    152                IF( ht_i(ji,jj,jl) > 1.5 ) THEN 
     105               IF( ph_ice(ji,jj,jl) > 1.5 ) THEN 
    153106                  zficeth(ji,jj,jl) = zalbfz(ji,jj,jl) 
    154                ELSEIF( ht_i(ji,jj,jl) > 1.0  .AND. ht_i(ji,jj,jl) <= 1.5 ) THEN 
    155                   zficeth(ji,jj,jl) = 0.472 + 2.0 * ( zalbfz(ji,jj,jl) - 0.472 ) * ( ht_i(ji,jj,jl) - 1.0 ) 
    156                ELSEIF( ht_i(ji,jj,jl) > 0.05 .AND. ht_i(ji,jj,jl) <= 1.0 ) THEN 
    157                   zficeth(ji,jj,jl) = 0.2467 + 0.7049 * ht_i(ji,jj,jl)                               & 
    158                      &                    - 0.8608 * ht_i(ji,jj,jl) * ht_i(ji,jj,jl)                 & 
    159                      &                    + 0.3812 * ht_i(ji,jj,jl) * ht_i(ji,jj,jl) * ht_i (ji,jj,jl) 
     107               ELSEIF( ph_ice(ji,jj,jl) > 1.0  .AND. ph_ice(ji,jj,jl) <= 1.5 ) THEN 
     108                  zficeth(ji,jj,jl) = 0.472 + 2.0 * ( zalbfz(ji,jj,jl) - 0.472 ) * ( ph_ice(ji,jj,jl) - 1.0 ) 
     109               ELSEIF( ph_ice(ji,jj,jl) > 0.05 .AND. ph_ice(ji,jj,jl) <= 1.0 ) THEN 
     110                  zficeth(ji,jj,jl) = 0.2467 + 0.7049 * ph_ice(ji,jj,jl)                               & 
     111                     &                    - 0.8608 * ph_ice(ji,jj,jl) * ph_ice(ji,jj,jl)                 & 
     112                     &                    + 0.3812 * ph_ice(ji,jj,jl) * ph_ice(ji,jj,jl) * ph_ice (ji,jj,jl) 
    160113               ELSE 
    161                   zficeth(ji,jj,jl) = 0.1 + 3.6 * ht_i(ji,jj,jl)  
     114                  zficeth(ji,jj,jl) = 0.1 + 3.6 * ph_ice(ji,jj,jl)  
    162115               ENDIF 
    163116            END DO 
    164117         END DO 
    165118      END DO 
    166 #elif defined key_lim2       
    167       DO jj = 1, jpj 
    168          DO ji = 1, jpi 
    169             IF( hicif(ji,jj) > 1.5 ) THEN 
    170                zficeth(ji,jj) = zalbfz(ji,jj) 
    171             ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN 
    172                zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 ) 
    173             ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN 
    174                zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                & 
    175                   &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 & 
    176                   &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj) 
    177             ELSE 
    178                zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj)  
    179             ENDIF 
    180          END DO 
    181       END DO 
    182 #endif 
    183119       
    184120      !-----------------------------------------------  
     
    188124      !    Albedo of snow-ice for clear sky. 
    189125      !-----------------------------------------------     
    190 #if defined key_lim3 
    191       DO jl = 1, jpl 
     126      DO jl = 1, ijpl 
    192127         DO jj = 1, jpj 
    193128            DO ji = 1, jpi 
    194129               !  Case of ice covered by snow.              
    195              
    196                !  freezing snow         
    197                zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( ht_s(ji,jj,jl) - c1 ) ) ) 
    198                zalbpsnf     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj,jl) + ht_s(ji,jj,jl) * ( alphd - zficeth(ji,jj,jl) ) / c1 ) & 
    199                   &                 + zihsc1   * alphd   
    200  
    201                !  melting snow                 
    202                zihsc2       = MAX ( zzero , SIGN ( zone , ht_s(ji,jj,jl) - c2 ) ) 
    203                zalbpsnm     = ( 1.0 - zihsc2 ) * ( albice + ht_s(ji,jj,jl) * ( alphc - albice ) / c2 )                 & 
    204                   &                 + zihsc2   * alphc  
    205  
    206  
    207                zitmlsn      =  MAX ( zzero , SIGN ( zone , t_su(ji,jj,jl) - rt0_snow ) )    
    208                zalbpsn      =  zitmlsn * zalbpsnm + ( 1.0 - zitmlsn ) * zalbpsnf 
     130               !                                        !  freezing snow         
     131               zihsc1   = 1.0 - MAX( zzero , SIGN( zone , - ( ph_snw(ji,jj,jl) - c1 ) ) ) 
     132               zalbpsnf = ( 1.0 - zihsc1 ) * (  zficeth(ji,jj,jl)                                        & 
     133                  &                           + ph_snw(ji,jj,jl) * ( alphd - zficeth(ji,jj,jl) ) / c1  )   & 
     134                  &     +         zihsc1   * alphd   
     135               !                                        !  melting snow                 
     136               zihsc2   = MAX( zzero , SIGN( zone , ph_snw(ji,jj,jl) - c2 ) ) 
     137               zalbpsnm = ( 1.0 - zihsc2 ) * ( albice + ph_snw(ji,jj,jl) * ( alphc - albice ) / c2 )       & 
     138                  &     +         zihsc2   * alphc  
     139               ! 
     140               zitmlsn  =  MAX( zzero , SIGN( zone , pt_ice(ji,jj,jl) - rt0_snow ) )    
     141               zalbpsn  =  zitmlsn * zalbpsnm + ( 1.0 - zitmlsn ) * zalbpsnf 
    209142             
    210143               !  Case of ice free of snow. 
    211                zalbpic      = zficeth(ji,jj,jl)  
     144               zalbpic  = zficeth(ji,jj,jl)  
    212145             
    213146               ! albedo of the system    
    214                zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - ht_s(ji,jj,jl) ) ) 
    215                palbp(ji,jj,jl) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic 
     147               zithsn   = 1.0 - MAX( zzero , SIGN( zone , - ph_snw(ji,jj,jl) ) ) 
     148               pa_ice_cs(ji,jj,jl) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic 
    216149            END DO 
    217150         END DO 
     
    220153      !    Albedo of snow-ice for overcast sky. 
    221154      !----------------------------------------------   
    222       palb(:,:,:)   = palbp(:,:,:) + cgren       ! Oberhuber correction 
    223  
    224 #elif defined key_lim2       
    225  
    226       DO jj = 1, jpj 
    227          DO ji = 1, jpi 
    228             !  Case of ice covered by snow.              
    229              
    230             !  melting snow         
    231             zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) ) 
    232             zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) & 
    233                &                 + zihsc1   * alphd   
    234             !  freezing snow                 
    235             zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) ) 
    236             zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 & 
    237                &                 + zihsc2   * alphc  
    238              
    239             zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )    
    240             zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm  
    241              
    242             !  Case of ice free of snow. 
    243             zalbpic      = zficeth(ji,jj)  
    244              
    245             ! albedo of the system    
    246             zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) ) 
    247             palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic 
    248          END DO 
    249       END DO 
    250        
    251       !    Albedo of snow-ice for overcast sky. 
    252       !----------------------------------------------   
    253       palb(:,:)   = palbp(:,:) + cgren                                            
    254 #endif 
    255        
    256       !-------------------------------------------- 
    257       !    Computation of the albedo of the ocean  
    258       !-------------------------- -----------------                                                           
    259        
    260       !  Parameterization of Briegled and Ramanathan, 1982  
    261       zmue14      = zmue**1.4                                        
    262       palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )                 
    263        
    264       !  Parameterization of Kondratyev, 1969 and Payne, 1972 
    265       palcn(:,:)  = 0.06                                                  
    266        
    267    END SUBROUTINE flx_blk_albedo 
    268  
    269 # else 
    270    !!---------------------------------------------------------------------- 
    271    !!   Default option :                                   NO sea-ice model 
    272    !!---------------------------------------------------------------------- 
    273  
    274    SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp ) 
    275       !!---------------------------------------------------------------------- 
    276       !!               ***  ROUTINE flx_blk_albedo  *** 
     155      pa_ice_os(:,:,:) = pa_ice_cs(:,:,:) + cgren       ! Oberhuber correction 
     156      ! 
     157   END SUBROUTINE albedo_ice 
     158 
     159 
     160   SUBROUTINE albedo_oce( pa_oce_os , pa_oce_cs ) 
     161      !!---------------------------------------------------------------------- 
     162      !!               ***  ROUTINE albedo_oce  *** 
    277163      !!  
    278       !! ** Purpose :   Computation of the albedo of the snow/ice system 
    279       !!      as well as the ocean one 
    280       !! 
    281       !! ** Method  :   Computation of the albedo of snow or ice (choose the 
    282       !!      wright one by a large number of tests Computation of the albedo 
    283       !!      of the ocean 
    284       !! 
    285       !! History : 
    286       !!  8.0   !  01-04  (LIM 1.0) 
    287       !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine) 
    288       !!---------------------------------------------------------------------- 
    289       !! * Arguments 
    290       REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    291          palb         ,     &    !  albedo of ice under overcast sky 
    292          palcn        ,     &    !  albedo of ocean under overcast sky 
    293          palbp        ,     &    !  albedo of ice under clear sky 
    294          palcnp                  !  albedo of ocean under clear sky 
    295  
    296       REAL(wp) ::   & 
    297          zmue14                 !  zmue**1.4 
    298       !!---------------------------------------------------------------------- 
    299  
    300       !-------------------------------------------- 
    301       !    Computation of the albedo of the ocean 
    302       !-------------------------- ----------------- 
    303  
    304       !  Parameterization of Briegled and Ramanathan, 1982 
    305       zmue14      = zmue**1.4 
    306       palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 ) 
    307  
    308       !  Parameterization of Kondratyev, 1969 and Payne, 1972 
    309       palcn(:,:)  = 0.06 
    310  
    311       palb (:,:)  = palcn(:,:) 
    312       palbp(:,:)  = palcnp(:,:) 
    313  
    314    END SUBROUTINE flx_blk_albedo 
    315  
    316 #endif 
     164      !! ** Purpose :   Computation of the albedo of the ocean 
     165      !! 
     166      !! ** Method  :   .... 
     167      !!---------------------------------------------------------------------- 
     168      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::   pa_oce_os   !  albedo of ocean under overcast sky 
     169      REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::   pa_oce_cs   !  albedo of ocean under clear sky 
     170      !! 
     171      REAL(wp) ::   zcoef   ! temporary scalar 
     172      !!---------------------------------------------------------------------- 
     173      ! 
     174      zcoef = 0.05 / ( 1.1 * rmue**1.4 + 0.15 )      ! Parameterization of Briegled and Ramanathan, 1982  
     175      pa_oce_cs(:,:) = zcoef                
     176      pa_oce_os(:,:)  = 0.06                         ! Parameterization of Kondratyev, 1969 and Payne, 1972 
     177      ! 
     178   END SUBROUTINE albedo_oce 
     179 
    317180 
    318181   SUBROUTINE albedo_init 
     
    323186      !! 
    324187      !! ** Method  :   Read the namelist namalb 
    325       !! 
    326       !! ** Action  :   
    327       !! 
    328       !! 
    329       !! History : 
    330       !!   9.0  !  04-11  (C. Talandier)  Original code 
    331188      !!---------------------------------------------------------------------- 
    332189      NAMELIST/namalb/ cgren, albice, alphd, alphdi, alphc 
    333       !!---------------------------------------------------------------------- 
    334       !!  OPA 9.0, LODYC-IPSL (2004) 
    335190      !!---------------------------------------------------------------------- 
    336191 
     
    342197      READ  ( numnam, namalb ) 
    343198 
    344       ! Control print 
    345       IF(lwp) THEN 
     199      IF(lwp) THEN               ! Control print 
    346200         WRITE(numout,*) 
    347          WRITE(numout,*) 'albedo_init : albedo ' 
     201         WRITE(numout,*) 'albedo_init : set albedo parameters from namelist namalb' 
    348202         WRITE(numout,*) '~~~~~~~~~~~' 
    349          WRITE(numout,*) '          Namelist namalb : set albedo parameters' 
    350          WRITE(numout,*) 
    351          WRITE(numout,*) '             correction of the snow or ice albedo to take into account cgren = ', cgren 
    352          WRITE(numout,*) '             albedo of melting ice in the arctic and antarctic        albice = ', albice 
    353          WRITE(numout,*) '             coefficients for linear                                   alphd = ', alphd 
    354          WRITE(numout,*) '             interpolation used to compute albedo                     alphdi = ', alphdi 
    355          WRITE(numout,*) '             between two extremes values (Pyane, 1972)                 alphc = ', alphc 
    356          WRITE(numout,*) 
     203         WRITE(numout,*) '             correction for snow and ice albedo                    cgren  = ', cgren 
     204         WRITE(numout,*) '             albedo of melting ice in the arctic and antarctic     albice = ', albice 
     205         WRITE(numout,*) '             coefficients for linear                               alphd  = ', alphd 
     206         WRITE(numout,*) '             interpolation used to compute albedo                  alphdi = ', alphdi 
     207         WRITE(numout,*) '             between two extremes values (Pyane, 1972)             alphc  = ', alphc 
    357208      ENDIF 
    358  
     209      ! 
    359210   END SUBROUTINE albedo_init 
     211 
    360212   !!====================================================================== 
    361213END MODULE albedo 
Note: See TracChangeset for help on using the changeset viewer.