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 152 for trunk/NEMO – NEMO

Changeset 152 for trunk/NEMO


Ignore:
Timestamp:
2004-10-19T15:35:09+02:00 (20 years ago)
Author:
opalod
Message:

CL + CT: UPDATE097: Move the computation step of the albedo in a module albedo.F90 and add the corresponding "USE albedo" module in both flxblk.F90 and limflx.F90 modules

Location:
trunk/NEMO
Files:
1 added
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC/limflx.F90

    r106 r152  
    2020   USE lbclnk 
    2121   USE in_out_manager 
     22   USE albedo 
    2223 
    2324   IMPLICIT NONE 
  • trunk/NEMO/OPA_SRC/SBC/flxblk.F90

    r84 r152  
    1010   !!---------------------------------------------------------------------- 
    1111   !!   flx_blk        : thermohaline fluxes from bulk 
    12    !!   flx_blk_albedo : albedo for ocean and ice (clear and overcast skies) 
    1312   !!   flx_blk_declin : solar declinaison 
    1413   !!---------------------------------------------------------------------- 
     
    2423   USE in_out_manager 
    2524   USE lbclnk 
     25   USE albedo 
    2626 
    2727   IMPLICIT NONE 
     
    3030   !! * Accessibility 
    3131   PUBLIC flx_blk        ! routine called by flx.F90  
    32    PUBLIC flx_blk_albedo ! routine called by limflx.F90  
    3332 
    3433   !! * Module variables 
     
    6059      zzero   = 0.e0    ,  & 
    6160      zone    = 1.0 
    62  
    63    !! * constants for albedo computation (flx_blk_albedo) 
    64    REAL(wp) ::   & 
    65       c1     = 0.05  ,     &   ! constants values 
    66       c2     = 0.10  ,     & 
    67       albice = 0.50  ,     &   !  albedo of melting ice in the arctic and antarctic (Shine & Hendersson-Sellers) 
    68       cgren  = 0.06  ,     &   !  correction of the snow or ice albedo to take into account 
    69                                !  effects of cloudiness (Grenfell & Perovich, 1984) 
    70       alphd  = 0.80  ,     &   !  coefficients for linear interpolation used to compute 
    71       alphdi = 0.72  ,     &   !  albedo between two extremes values (Pyane, 1972) 
    72       alphc  = 0.65  ,     & 
    73       zmue   = 0.40            !  cosine of local solar altitude 
    7461 
    7562   !! * constants for solar declinaison computation (flx_blk_declin) 
     
    693680 
    694681 
    695 #if defined key_ice_lim 
    696    !!---------------------------------------------------------------------- 
    697    !!   'key_ice_lim'                                         LIM ice model 
    698    !!---------------------------------------------------------------------- 
    699  
    700    SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp ) 
    701       !!---------------------------------------------------------------------- 
    702       !!               ***  ROUTINE flx_blk_albedo  *** 
    703       !!           
    704       !! ** Purpose :   Computation of the albedo of the snow/ice system  
    705       !!      as well as the ocean one 
    706       !!        
    707       !! ** Method  : - Computation of the albedo of snow or ice (choose the  
    708       !!      rignt one by a large number of tests 
    709       !!              - Computation of the albedo of the ocean 
    710       !! 
    711       !! References : 
    712       !!      Shine and Hendersson-Sellers 1985, JGR, 90(D1), 2243-2250. 
    713       !! 
    714       !! History : 
    715       !!  8.0   !  01-04  (LIM 1.0) 
    716       !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine) 
    717       !!---------------------------------------------------------------------- 
    718       !! * Modules used 
    719       USE ice                   ! ??? 
    720  
    721       !! * Arguments 
    722       REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    723          palb         ,     &    !  albedo of ice under overcast sky 
    724          palcn        ,     &    !  albedo of ocean under overcast sky 
    725          palbp        ,     &    !  albedo of ice under clear sky  
    726          palcnp                  !  albedo of ocean under clear sky 
    727  
    728       !! * Local variables 
    729       INTEGER ::    & 
    730          ji, jj                   ! dummy loop indices 
    731       REAL(wp) ::   &  
    732          zmue14         ,     &   !  zmue**1.4 
    733          zalbpsnm       ,     &   !  albedo of ice under clear sky when snow is melting 
    734          zalbpsnf       ,     &   !  albedo of ice under clear sky when snow is freezing 
    735          zalbpsn        ,     &   !  albedo of snow/ice system when ice is coverd by snow 
    736          zalbpic        ,     &   !  albedo of snow/ice system when ice is free of snow 
    737          zithsn         ,     &   !  = 1 for hsn >= 0 ( ice is cov. by snow ) ; = 0 otherwise (ice is free of snow) 
    738          zitmlsn        ,     &   !  = 1 freezinz snow (sist >=rt0_snow) ; = 0 melting snow (sist<rt0_snow) 
    739          zihsc1         ,     &   !  = 1 hsn <= c1 ; = 0 hsn > c1 
    740          zihsc2                   !  = 1 hsn >= c2 ; = 0 hsn < c2 
    741       REAL(wp), DIMENSION(jpi,jpj) ::  & 
    742          zalbfz         ,     &   !  ( = alphdi for freezing ice ; = albice for melting ice ) 
    743          zficeth                  !  function of ice thickness 
    744       LOGICAL , DIMENSION(jpi,jpj) ::  & 
    745          llmask 
    746       !!--------------------------------------------------------------------- 
    747        
    748       !-------------------------                                                              
    749       !  Computation of  zficeth 
    750       !--------------------------  
    751        
    752       llmask = (hsnif == 0.e0) .AND. ( sist >= rt0_ice ) 
    753       WHERE ( llmask )   !  ice free of snow and melts 
    754          zalbfz = albice 
    755       ELSEWHERE                    
    756          zalbfz = alphdi 
    757       END WHERE 
    758        
    759       DO jj = 1, jpj 
    760          DO ji = 1, jpi 
    761             IF( hicif(ji,jj) > 1.5 ) THEN 
    762                zficeth(ji,jj) = zalbfz(ji,jj) 
    763             ELSEIF( hicif(ji,jj) > 1.0  .AND. hicif(ji,jj) <= 1.5 ) THEN 
    764                zficeth(ji,jj) = 0.472 + 2.0 * ( zalbfz(ji,jj) - 0.472 ) * ( hicif(ji,jj) - 1.0 ) 
    765             ELSEIF( hicif(ji,jj) > 0.05 .AND. hicif(ji,jj) <= 1.0 ) THEN 
    766                zficeth(ji,jj) = 0.2467 + 0.7049 * hicif(ji,jj)                                & 
    767                   &                    - 0.8608 * hicif(ji,jj) * hicif(ji,jj)                 & 
    768                   &                    + 0.3812 * hicif(ji,jj) * hicif(ji,jj) * hicif (ji,jj) 
    769             ELSE 
    770                zficeth(ji,jj) = 0.1 + 3.6 * hicif(ji,jj)  
    771             ENDIF 
    772          END DO 
    773       END DO 
    774        
    775       !-----------------------------------------------  
    776       !    Computation of the snow/ice albedo system  
    777       !-------------------------- --------------------- 
    778        
    779       !    Albedo of snow-ice for clear sky. 
    780       !-----------------------------------------------     
    781       DO jj = 1, jpj 
    782          DO ji = 1, jpi 
    783             !  Case of ice covered by snow.              
    784              
    785             !  melting snow         
    786             zihsc1       = 1.0 - MAX ( zzero , SIGN ( zone , - ( hsnif(ji,jj) - c1 ) ) ) 
    787             zalbpsnm     = ( 1.0 - zihsc1 ) * ( zficeth(ji,jj) + hsnif(ji,jj) * ( alphd - zficeth(ji,jj) ) / c1 ) & 
    788                &                 + zihsc1   * alphd   
    789             !  freezing snow                 
    790             zihsc2       = MAX ( zzero , SIGN ( zone , hsnif(ji,jj) - c2 ) ) 
    791             zalbpsnf     = ( 1.0 - zihsc2 ) * ( albice + hsnif(ji,jj) * ( alphc - albice ) / c2 )                 & 
    792                &                 + zihsc2   * alphc  
    793              
    794             zitmlsn      =  MAX ( zzero , SIGN ( zone , sist(ji,jj) - rt0_snow ) )    
    795             zalbpsn      =  zitmlsn * zalbpsnf + ( 1.0 - zitmlsn ) * zalbpsnm  
    796              
    797             !  Case of ice free of snow. 
    798             zalbpic      = zficeth(ji,jj)  
    799              
    800             ! albedo of the system    
    801             zithsn       = 1.0 - MAX ( zzero , SIGN ( zone , - hsnif(ji,jj) ) ) 
    802             palbp(ji,jj) =  zithsn * zalbpsn + ( 1.0 - zithsn ) *  zalbpic 
    803          END DO 
    804       END DO 
    805        
    806       !    Albedo of snow-ice for overcast sky. 
    807       !----------------------------------------------   
    808       palb(:,:)   = palbp(:,:) + cgren                                            
    809        
    810       !-------------------------------------------- 
    811       !    Computation of the albedo of the ocean  
    812       !-------------------------- -----------------                                                           
    813        
    814       !  Parameterization of Briegled and Ramanathan, 1982  
    815       zmue14      = zmue**1.4                                        
    816       palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 )                 
    817        
    818       !  Parameterization of Kondratyev, 1969 and Payne, 1972 
    819       palcn(:,:)  = 0.06                                                  
    820        
    821    END SUBROUTINE flx_blk_albedo 
    822  
    823 # else 
    824    !!---------------------------------------------------------------------- 
    825    !!   Default option :                                   NO sea-ice model 
    826    !!---------------------------------------------------------------------- 
    827  
    828    SUBROUTINE flx_blk_albedo( palb , palcn , palbp , palcnp ) 
    829       !!---------------------------------------------------------------------- 
    830       !!               ***  ROUTINE flx_blk_albedo  *** 
    831       !!  
    832       !! ** Purpose :   Computation of the albedo of the snow/ice system 
    833       !!      as well as the ocean one 
    834       !! 
    835       !! ** Method  :   Computation of the albedo of snow or ice (choose the 
    836       !!      wright one by a large number of tests Computation of the albedo 
    837       !!      of the ocean 
    838       !! 
    839       !! History : 
    840       !!  8.0   !  01-04  (LIM 1.0) 
    841       !!  8.5   !  03-07  (C. Ethe, G. Madec)  Optimization (old name:shine) 
    842       !!---------------------------------------------------------------------- 
    843       !! * Arguments 
    844       REAL(wp), DIMENSION(jpi,jpj), INTENT(out) ::  & 
    845          palb         ,     &    !  albedo of ice under overcast sky 
    846          palcn        ,     &    !  albedo of ocean under overcast sky 
    847          palbp        ,     &    !  albedo of ice under clear sky 
    848          palcnp                  !  albedo of ocean under clear sky 
    849  
    850       REAL(wp) ::   & 
    851          zmue14                 !  zmue**1.4 
    852       !!---------------------------------------------------------------------- 
    853  
    854       !-------------------------------------------- 
    855       !    Computation of the albedo of the ocean 
    856       !-------------------------- ----------------- 
    857  
    858       !  Parameterization of Briegled and Ramanathan, 1982 
    859       zmue14      = zmue**1.4 
    860       palcnp(:,:) = 0.05 / ( 1.1 * zmue14 + 0.15 ) 
    861  
    862       !  Parameterization of Kondratyev, 1969 and Payne, 1972 
    863       palcn(:,:)  = 0.06 
    864  
    865       palb (:,:)  = palcn(:,:) 
    866       palbp(:,:)  = palcnp(:,:) 
    867  
    868    END SUBROUTINE flx_blk_albedo 
    869  
    870 #endif 
    871  
    872682   SUBROUTINE flx_blk_declin( ky, kday, pdecl ) 
    873683      !!--------------------------------------------------------------------------- 
Note: See TracChangeset for help on using the changeset viewer.