source: branches/GRISLIv3/SOURCES/lineartemp-0.2.f90 @ 414

Last change on this file since 414 was 414, checked in by dumas, 14 months ago

use only in subroutine lineartemp

File size: 1.3 KB
Line 
1!> \file lineartemp-0.2.f90
2!!  Linear temperature in ice
3!<
4
5!> SUBROUTINE: LINEARTEMP
6!! Calculate the linear temperature in ice
7
8subroutine lineartemp
9
10  !     *********************************************************
11  !     (********** LINEAR TEMPERATURE IN ICE *******************)
12  !     *********************************************************
13
14  use geography, only:nx,ny,nz,nzm
15  use module3D_phy, only:H1,H,B1,B,TG,bmelt,T,TS,tpmp,ghf
16  use icetemp_declar, only:Dzm,Cm
17 
18  implicit none
19
20  integer :: i,j,k
21
22  do I=1,NX
23     do J=1,NY 
24        H1(I,J)=H(I,J) 
25        B1(I,J)=B(I,J) 
26        TG(I,J)=0.
27        BMELT(I,J)=0.
28        T(I,J,1)=min(0.,TS(I,J))
29        !     TPMP(I,J,1)=0.
30        !     TPMP(I,J,NZ)=-0.00087*H(I,J)
31        !     T(I,J,NZ)=TPMP(I,J,NZ)
32        !     pour partir d'une tempéature plus froide
33        !     T(I,J,NZ)=TPMP(I,J,NZ)-10.
34
35        if (H(i,j).gt.0.)  T(I,J,NZ)=TPMP(I,J,NZ)-20.
36
37
38
39        do K=2,NZ-1
40           !     TPMP(I,J,K)=-0.00087*(K-1)/(NZ-1)*H(I,J)
41           !     T(I,J,K)=T(I,J,1)-(T(I,J,1)-TPMP(I,J,NZ))*(K-1)/(NZ-1)
42           T(I,J,K)=T(I,J,1)-(T(I,J,1)-T(I,J,NZ))*(K-1)/(NZ-1)
43           !     write(num_templin,*) T(I,J,K)
44        end do
45        do K=NZ+1,NZ+NZM
46           T(I,J,K)=(T(I,J,K-1)-GHF(i,j)*DZM/cm)
47        end do
48     end do
49  end do
50
51
52end subroutine lineartemp
Note: See TracBrowser for help on using the repository browser.