Ignore:
Timestamp:
07/05/16 11:20:52 (8 years ago)
Author:
dumas
Message:

Merge branche iLOVECLIM sur rev 76

Location:
branches/iLoveclim
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • branches/iLoveclim

  • branches/iLoveclim/SOURCES/Temperature-routines/advec_icetemp.f90

    r24 r77  
    1414!> 
    1515 
    16 Subroutine  Advec_icetemp(Ii,Jj,Prodq_m,Cro_m,Advecx_m,Advecy_m,Advec_m,Ct_m) 
     16Subroutine  Advec_icetemp(Nz,Nzm,Nn,Prodq_m,Cro_m,Advecx_m,Advecy_m,Advec_m,Ct_m,Iadvec_w,Iadvec_e,Iadvec_s,Iadvec_n, & 
     17        Uxij,Uxi_plus_un,Uyij,Uyj_plus_un,Tij,Ti_moins_un,Ti_plus_un,Tj_moins_un,Tj_plus_un,Hij,Tsij,Aa,Bb,Cc,Rr, & 
     18        Dx11,Dou,DTT,Dee,Uzrij,Dttdx) 
    1719 
    18   use icetemp_declar  
     20!  use icetemp_declar  
    1921 
    2022  Implicit None 
    2123    !< Arguments 
    22   Integer,                     Intent(In)  ::  Ii,Jj          !< Indice Selon X Et Y 
    23   Real, Dimension(Nz),         Intent(In)   :: Prodq_m        !< Tableau 1d Vert. heat production 
    24   Real, Dimension(Nz),         Intent(In)   :: Cro_m          !< Tableau 1d Vert. heat capcity 
    25   Real, Dimension(Nz),         Intent(Inout):: Advecx_m       !< Advection selon x 
    26   Real, Dimension(Nz),         Intent(Inout):: Advecy_m       !< Advection selon y 
    27   Real, Dimension(Nz),         Intent(Inout):: Advec_m        !< Advection total 
    28   Real, Dimension(Nz),         Intent(In)   :: Ct_m           !< Tableau 1d Vert.  thermal cond. 
     24  Integer,                     intent(in)  ::  Nz,Nzm,Nn      !< Taille des tableaux 
     25  Real, Dimension(Nz),         intent(in)   :: Prodq_m        !< Tableau 1d Vert. heat production 
     26  Real, Dimension(Nz),         intent(in)   :: Cro_m          !< Tableau 1d Vert. heat capcity 
     27  Real, Dimension(Nz),         intent(inout):: Advecx_m       !< Advection selon x 
     28  Real, Dimension(Nz),         intent(inout):: Advecy_m       !< Advection selon y 
     29  Real, Dimension(Nz),         intent(inout):: Advec_m        !< Advection total 
     30  Real, Dimension(Nz),         intent(in)   :: Ct_m           !< Tableau 1d Vert.  thermal cond. 
     31   
     32  Integer, intent(in) :: Iadvec_w,Iadvec_e,Iadvec_s,Iadvec_n 
     33  real, dimension(Nz), Intent(in) :: Uxij, Uxi_plus_un 
     34  real, dimension(Nz), Intent(in) :: Uyij, Uyj_plus_un 
     35  real, dimension(Nz+Nzm), Intent(inout) :: Tij 
     36  real, dimension(Nz+Nzm), Intent(in) :: Ti_moins_un,Ti_plus_un,Tj_moins_un,Tj_plus_un 
     37  real, intent(in) :: Hij 
     38  real,intent(in) :: Tsij 
     39  Real,Dimension(Nn),intent(inout) :: Aa    !< Work Arrays For Tridiag  !Dim Nn 
     40  Real,Dimension(Nn),intent(inout) :: Bb    !< Work Arrays For Tridiag  !Dim Nn 
     41  Real,Dimension(Nn),intent(inout) :: Cc    !< Work Arrays For Tridiag  !Dim Nn 
     42  Real,Dimension(Nn),intent(inout) :: Rr    !< Work Arrays For Tridiag  !Dim Nn 
     43  Real, intent(in) :: Dx11 
     44  Real, intent(inout) :: Dou 
     45  real, intent(in) :: DTT 
     46  real, intent(in) :: Dee 
     47  real, dimension(Nz) :: Uzrij 
     48  real :: Dttdx 
     49   
     50 
     51   
     52  ! variables locales 
     53  Integer :: K 
     54  Real :: Dzz,Dah,Ct_haut,Ct_bas 
    2955 
    3056  
     
    3561     !         Avection Selon X  (advecx_m en general > 0) 
    3662     !         ---------------- 
    37      Advecx_m(K) = Iadvec_w(Ii,Jj) * Ux(Ii,Jj,K) *          & ! ux west if upwind 
    38           (T(Ii,Jj,K) - T(Ii-1,Jj,K))  & ! west T gradient 
     63     Advecx_m(K) = Iadvec_w * Uxij(K) *          & ! ux west if upwind 
     64          (Tij(K) - Ti_moins_un(K))  & ! west T gradient 
    3965             
    40           + Iadvec_e(Ii+1,Jj)* Ux(Ii+1,Jj,K)*      & ! ux east if upwind 
    41           (T(Ii+1,Jj,K)-T(Ii,Jj,K))     ! east T gradient 
     66          + Iadvec_e * Uxi_plus_un(K)*      & ! ux east if upwind 
     67          (Ti_plus_un(K)-Tij(K))     ! east T gradient 
    4268 
    4369     Advecx_m(K) =  Advecx_m(K) * Dx11                                        !Dx11=1/Dx 
     
    4672     !         Avection Selon Y 
    4773     !         ---------------- 
    48      Advecy_m(K) =   Iadvec_s(Ii,Jj) * Uy(Ii,Jj,K) *        & ! uy sud if upwind 
    49           (T(Ii,Jj,K) - T(Ii,Jj-1,K))& ! south T gradient 
     74     Advecy_m(K) =   Iadvec_s * Uyij(K) *        & ! uy sud if upwind 
     75          (Tij(K) - Tj_moins_un(K))& ! south T gradient 
    5076           
    51           + Iadvec_n(Ii,Jj+1) * Uy(Ii,Jj+1,K) *   & ! uy nord is upwind 
    52           (T(Ii,Jj+1,K)-T(Ii,Jj,K))    ! north T gradient 
     77          + Iadvec_n * Uyj_plus_un(K) *   & ! uy nord is upwind 
     78          (Tj_plus_un(K)-Tij(K))    ! north T gradient 
    5379 
    5480     Advecy_m(K) =  Advecy_m(K) * Dx11 
     
    6288 
    6389  !      -----------------------------Cas General (H>10m) 
    64   thick_ice:  If (H(Ii,Jj).Gt.10.) Then 
     90  thick_ice:  If (Hij.Gt.10.) Then 
    6591 
    6692     !        Variables De Calcul Dans La Glace 
    6793     ! dou = dtt/dz^2 
    68      Dou=Dtt/Dee/Dee/ H(Ii,Jj) / H(Ii,Jj)   
     94     Dou=Dtt/Dee/Dee/ Hij / Hij   
    6995 
    7096     ! Dah = dtt/dz 
    71      Dah=Dtt /Dee /H(Ii,Jj) 
     97     Dah=Dtt /Dee /Hij 
    7298 
    7399     ! thermal conductivity at mid point just below the surface                    
     
    75101 
    76102     ! surface temperature : cannot go above 0 celsius 
    77      T(Ii,Jj,1)=Min(0.,Ts(Ii,Jj)) 
     103     Tij(1)=Min(0.,Tsij) 
    78104 
    79105     ! surface boundary condition 
     
    81107     Bb(1)=1. 
    82108     Cc(1)=0. 
    83      Rr(1)=T(Ii,Jj,1) 
     109     Rr(1)=Tij(1) 
    84110 
    85111     Do K=2,Nz-1 
     
    91117 
    92118        ! Advection Verticale Centree 
    93         Aa(K) = -Dzz * Ct_haut - Uzr(Ii,Jj,K) * Dah / 2.  ! lower diag 
    94         Cc(K) = -Dzz * Ct_bas  + Uzr(Ii,Jj,K) * Dah / 2.  ! upper diag 
     119        Aa(K) = -Dzz * Ct_haut - Uzrij(K) * Dah / 2.  ! lower diag 
     120        Cc(K) = -Dzz * Ct_bas  + Uzrij(K) * Dah / 2.  ! upper diag 
    95121        Bb(K) =  1.+ Dzz * (Ct_haut+Ct_bas)                                ! diag 
    96122         
    97         Rr(K) =  T(Ii,Jj,K) + Prodq_m(K) * Dtt   ! vector 
     123        Rr(K) =  Tij(K) + Prodq_m(K) * Dtt   ! vector 
    98124        Rr(K) =  Rr(K)- Dttdx * (Advec_m(K)) 
    99125 
Note: See TracChangeset for help on using the changeset viewer.