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

Last change on this file since 469 was 469, checked in by aquiquet, 4 months ago

Cleaning branch: old empty ritz files and unused file numbers removed

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:H,B,bmelt,T,TS,tpmp,ghf
16  use icetemp_declar, only:Dzm,Cm
17 
18  implicit none
19
20  integer :: i,j,k
21  real,dimension(nx,ny) :: TG           !< degrees above melting point at the base
22
23  do I=1,NX
24     do J=1,NY 
25        TG(I,J)=0.
26        BMELT(I,J)=0.
27        T(I,J,1)=min(0.,TS(I,J))
28        !     TPMP(I,J,1)=0.
29        !     TPMP(I,J,NZ)=-0.00087*H(I,J)
30        !     T(I,J,NZ)=TPMP(I,J,NZ)
31        !     pour partir d'une tempéature plus froide
32        !     T(I,J,NZ)=TPMP(I,J,NZ)-10.
33
34        if (H(i,j).gt.0.)  T(I,J,NZ)=TPMP(I,J,NZ)-20.
35
36
37
38        do K=2,NZ-1
39           !     TPMP(I,J,K)=-0.00087*(K-1)/(NZ-1)*H(I,J)
40           !     T(I,J,K)=T(I,J,1)-(T(I,J,1)-TPMP(I,J,NZ))*(K-1)/(NZ-1)
41           T(I,J,K)=T(I,J,1)-(T(I,J,1)-T(I,J,NZ))*(K-1)/(NZ-1)
42        end do
43        do K=NZ+1,NZ+NZM
44           T(I,J,K)=(T(I,J,K-1)-GHF(i,j)*DZM/cm)
45        end do
46     end do
47  end do
48
49
50end subroutine lineartemp
Note: See TracBrowser for help on using the repository browser.