source: trunk/SOURCES/Old-sources/lect-Ant_clim_Acc-T_gen_dat.f90 @ 334

Last change on this file since 334 was 236, checked in by aquiquet, 5 years ago

Deprecated modules moved to Old-sources

File size: 2.7 KB
Line 
1module lect_clim_acc_T_ant_gen
2
3  use module3D_phy
4  use ablation_ann                       ! le module pdd base sur Tann et Tjuly
5  use interface_input
6  character(len=100) :: precip_file        ! precipitations
7  character(len=100) :: temp_annual_file   ! temperature annuelles
8  real               :: coef_dens          ! pour corriger si donnees en eq. eau
9  logical            :: temp_param         ! si utilisation de temperature parametree
10
11contains
12
13  subroutine input_climat_ref()
14
15    namelist/climat_acc_T_gen/precip_file,coef_dens,temp_annual_file
16
17428 format(A)
18    rewind(num_param)                     ! pour revenir au debut du fichier param_list.dat
19    read(num_param,climat_acc_T_gen)
20
21    write(num_rep_42,428)'!___________________________________________________________' 
22    write(num_rep_42,428)'!  module  lect_clim_acc_T_ant_gen                          '
23    write(num_rep_42,climat_acc_T_gen)
24    write(num_rep_42,428)'!___________________________________________________________' 
25
26
27    ! precipitation
28    precip_file  = trim(dirnameinp)//trim(precip_file)
29
30    call lect_input(3,'precip',1,precip,precip_file,trim(dirnameinp)//trim(runname)//'.nc')
31    !call lect_datfile(nx,ny,precip,1,precip_file)                 
32
33    precip(:,:)=precip(:,:)*coef_dens
34    acc(:,:)=precip(:,:)
35
36    if ((trim(temp_annual_file).eq.'no').or.(trim(temp_annual_file).eq.'NO')) then
37       temp_param=.true.
38    else
39       temp_param=.false.
40    end if
41
42    !    temperature en surface
43
44    test_param: if (.not.temp_param) then
45       temp_annual_file = trim(dirnameinp)//trim(temp_annual_file)
46
47
48       call lect_input(3,'Tann',1,Tann,temp_annual_file,trim(dirnameinp)//trim(runname)//'.nc')
49       !call lect_datfile(nx,ny,Tann,1,temp_annual_file)               ! temperature annuelle
50
51    else                        !    parametrisation de Fortuin pour la temperature annuelle.
52
53       do j=1,ny
54          do i=1,nx
55
567            if (s0(i,j).le.200.) then                                    ! shelfs
57                tann(i,j)=49.642-0.943*abs(ylat(i,j))
58             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then      ! pente
59                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j))
60             else if (s0(i,j).ge.1500.) then                              ! plateau
61                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j))
62             endif
63          end do
64       end do
65    end if test_param
66
67    ta0(:,:)=tann(:,:)
68
69
70    !           pour la temperature d'ete, idem parametrisation huybrechts
71    do j=1,ny
72       do i=1,nx
73
74          tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)&
75               +0.40802*abs(ylat(i,j))
76       end do
77    end do
78
79  end subroutine input_climat_ref
80
81end module  lect_clim_acc_T_ant_gen
Note: See TracBrowser for help on using the repository browser.