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 7646 for trunk/NEMOGCM/NEMO/OPA_SRC/DIU/cool_skin.F90 – NEMO

Ignore:
Timestamp:
2017-02-06T10:25:03+01:00 (7 years ago)
Author:
timgraham
Message:

Merge of dev_merge_2016 into trunk. UPDATE TO ARCHFILES NEEDED for XIOS2.
LIM_SRC_s/limrhg.F90 to follow in next commit due to change of kind (I'm unable to do it in this commit).
Merged using the following steps:

1) svn merge --reintegrate svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk .
2) Resolve minor conflicts in sette.sh and namelist_cfg for ORCA2LIM3 (due to a change in trunk after branch was created)
3) svn commit
4) svn switch svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/trunk
5) svn merge svn+ssh://forge.ipsl.jussieu.fr/ipsl/forge/projets/nemo/svn/branches/2016/dev_merge_2016 .
6) At this stage I checked out a clean copy of the branch to compare against what is about to be committed to the trunk.
6) svn commit #Commit code to the trunk

In this commit I have also reverted a change to Fcheck_archfile.sh which was causing problems on the Paris machine.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/DIU/cool_skin.F90

    r6493 r7646  
    1010 
    1111   !!---------------------------------------------------------------------- 
    12    !!   diurnal_sst_coolskin_step  : time-step the cool skin corrections 
     12   !!   diurnal_sst_coolskin_init : initialisation of the cool skin 
     13   !!   diurnal_sst_coolskin_step : time-stepping  of the cool skin corrections 
    1314   !!---------------------------------------------------------------------- 
    1415   USE par_kind 
     
    2122    
    2223   IMPLICIT NONE 
    23     
     24   PRIVATE 
     25 
    2426   ! Namelist parameters 
    2527 
     
    3739   REAL(wp), PUBLIC, ALLOCATABLE, DIMENSION(:,:) :: x_csthick   ! Cool skin thickness 
    3840 
    39    PRIVATE 
    4041   PUBLIC diurnal_sst_coolskin_step, diurnal_sst_coolskin_init 
    4142 
    4243      !! * Substitutions 
    4344#  include "vectopt_loop_substitute.h90" 
    44     
     45   !!---------------------------------------------------------------------- 
     46   !! NEMO/OPA 4.0 , NEMO-consortium (2016)  
     47   !! $Id:  $ 
     48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     49   !!----------------------------------------------------------------------    
    4550   CONTAINS  
    4651    
     
    5661      !!  
    5762      !!---------------------------------------------------------------------- 
    58        
    59       IMPLICIT NONE 
    60        
    6163      ALLOCATE( x_csdsst(jpi,jpj), x_csthick(jpi,jpj) ) 
    6264      x_csdsst = 0. 
    6365      x_csthick = 0. 
    64        
     66      ! 
    6567   END SUBROUTINE diurnal_sst_coolskin_init 
    66   
     68 
     69 
    6770   SUBROUTINE diurnal_sst_coolskin_step(psqflux, pstauflux, psrho, rdt) 
    6871      !!---------------------------------------------------------------------- 
     
    7578      !! ** Reference :  
    7679      !!---------------------------------------------------------------------- 
    77       
    78       IMPLICIT NONE 
    79       
    8080      ! Dummy variables 
    8181      REAL(wp), INTENT(IN), DIMENSION(jpi,jpj) :: psqflux     ! Heat (non-solar)(Watts) 
     
    9494      
    9595      INTEGER :: ji,jj 
    96       
    97       IF ( .NOT. ln_blk_core ) THEN 
    98          CALL ctl_stop("cool_skin.f90: diurnal flux processing only implemented"//& 
    99          &             " for core bulk forcing") 
    100       ENDIF 
    101   
     96      !!---------------------------------------------------------------------- 
     97      ! 
     98      IF( .NOT. ln_blk )   CALL ctl_stop("cool_skin.f90: diurnal flux processing only implemented for bulk forcing") 
     99      ! 
    102100      DO jj = 1,jpj 
    103101         DO ji = 1,jpi 
    104              
     102            ! 
    105103            ! Calcualte wind speed from wind stress and friction velocity 
    106104            IF( tmask(ji,jj,1) == 1. .AND. pstauflux(ji,jj) /= 0 .AND. psrho(ji,jj) /=0 ) THEN 
     
    111109               z_wspd(ji,jj) = 0.      
    112110            ENDIF 
    113  
    114   
     111            ! 
    115112            ! Calculate gamma function which is dependent upon wind speed 
    116113            IF( tmask(ji,jj,1) == 1. ) THEN 
     
    119116               IF( ( z_wspd(ji,jj) >= 10. ) ) z_gamma(ji,jj) = 6. 
    120117            ENDIF 
    121  
    122  
     118            ! 
    123119            ! Calculate lamda function 
    124120            IF( tmask(ji,jj,1) == 1. .AND. z_fv(ji,jj) /= 0 ) THEN 
     
    127123               z_lamda(ji,jj) = 0. 
    128124            ENDIF 
    129  
    130  
    131  
     125            ! 
    132126            ! Calculate the cool skin thickness - only when heat flux is out of the ocean 
    133127            IF( tmask(ji,jj,1) == 1. .AND. z_fv(ji,jj) /= 0 .AND. psqflux(ji,jj) < 0 ) THEN 
    134                 x_csthick(ji,jj) = ( z_lamda(ji,jj) * pp_v ) / z_fv(ji,jj) 
     128               x_csthick(ji,jj) = ( z_lamda(ji,jj) * pp_v ) / z_fv(ji,jj) 
    135129            ELSE 
    136                 x_csthick(ji,jj) = 0. 
     130               x_csthick(ji,jj) = 0. 
    137131            ENDIF 
    138  
    139  
    140  
     132            ! 
    141133            ! Calculate the cool skin correction - only when the heat flux is out of the ocean 
    142134            IF( tmask(ji,jj,1) == 1. .AND. x_csthick(ji,jj) /= 0. .AND. psqflux(ji,jj) < 0. ) THEN 
     
    145137               x_csdsst(ji,jj) = 0. 
    146138            ENDIF 
    147  
    148          ENDDO 
    149       ENDDO 
    150  
     139            ! 
     140         END DO 
     141      END DO 
     142      ! 
    151143   END SUBROUTINE diurnal_sst_coolskin_step 
    152144 
    153  
     145   !!====================================================================== 
    154146END MODULE cool_skin 
Note: See TracChangeset for help on using the changeset viewer.