source: branches/iLoveclim/SOURCES/Greeneem_files/lect-greeneem_mod.f90 @ 88

Last change on this file since 88 was 88, checked in by dumas, 8 years ago

Merge branche iLOVECLIM sur rev 87

File size: 5.4 KB
Line 
1module lect_topo_greeneem
2
3use module3D_phy
4use param_phy_mod 
5!cdc
6use interface_input
7use io_netcdf_grisli
8
9implicit none
10
11character(len=100) :: topo_dep       ! Topo de départ
12character(len=100) :: topo_ref       ! Topo de référence
13character(len=100) :: grid_topo      ! fichier grille
14character(len=100) :: ghf_fich       ! fichier grille
15character(len=100) :: filin
16real, dimension(nx,ny,5) :: bidon        ! pour l'appel a courbure
17!real :: ghf0                             ! flux geothermique constant en mW/m2
18
19real, dimension(nx,ny) :: Bsoc_bamber, S_bamber, Bsoc_new
20character(len=100) :: topo_surf      !< surface file name
21character(len=100) :: topo_bed       !< bedrock file name
22character(len=100) :: file_ncdf      !< fichier netcdf issue des fichiers .dat
23
24integer :: n1,n2,ndx
25real :: sealevel0
26real :: archimed
27integer :: ios
28
29contains
30 
31  subroutine input_topo
32
33    namelist/toponeem/topo_ref,topo_dep,grid_topo,ghf_fich
34
35428 format(A)
36
37    rewind(num_param)        ! pour revenir au debut du fichier param_list.dat
38
39    read(num_param,toponeem)
40
41    write(num_rep_42,428)'!___________________________________________________________' 
42    write(num_rep_42,428) '&toponeen                     ! module lect_topo_greeneem'
43    write(num_rep_42,'(A,A)')   'topo_ref  =', topo_ref
44    write(num_rep_42,'(A,A)')   'topo_dep  =', topo_dep
45    write(num_rep_42,'(A,A)')   'grid_topo =', grid_topo
46    write(num_rep_42,*)         'ghf_fich  =', ghf_fich
47    write(num_rep_42,*)'/'                     
48    write(num_rep_42,428) '! topo_ref= topo actuelle'
49    write(num_rep_42,428) '! topo_dep= topo de depart'
50    write(num_rep_42,428) '! grid_topo : fichier i,j,x,y,lon,lat'
51    write(num_rep_42,428) '! ghf_fich  : fichier flux geothermique'
52    write(num_rep_42,*)
53
54
55    topo_ref=trim(dirnameinp)//trim(topo_ref) 
56    topo_dep=trim(dirnameinp)//trim(topo_dep) 
57    grid_topo=trim(dirnameinp)//trim(grid_topo)
58    ghf_fich=trim(dirnameinp)//trim(ghf_fich)!trim(ghf0)
59
60    sealevel0=0.  ! voir a passer dans le fichier parametre
61
62    !     lecture de la topo de référence
63    !     -------------------------------
64    ! Cette topo sert a calculer le socle de reference pour l'isostasie
65    ! voir init_iso et a avoir une surface de reference pour les temperatures
66    ! lecture adaptee aux fichiers ZBL.dat ou netcdf ou grd
67    call lect_input(1,'Bsoc',1,Bsoc0,topo_ref,file_ncdf)    ! socle
68    call lect_input(1,'S',1,S0,topo_ref,file_ncdf)          ! surface
69    call lect_input(1,'H',1,H0,topo_ref,file_ncdf)          ! epaisseur
70
71    S0(:,:)=max(S0(:,:),sealevel0)   ! pour etre au niveau des mers : ATTENTION si SEALEV <0
72    mk0(:,:) = 1                   ! mk0=0 pour les zones interdites
73
74    !     lecture de la topo de depart
75    !     ---------------------------
76    ! lecture adaptee aux fichiers ZBL.dat ou netcdf ou grd
77    call lect_input(1,'Bsoc',1,Bsoc,topo_dep,file_ncdf)    ! socle
78    call lect_input(1,'S',1,S,topo_dep,file_ncdf)          ! surface
79    call lect_input(1,'H',1,H,topo_dep,file_ncdf)          ! epaisseur
80    S(:,:)=max(S(:,:),0.)   ! pour etre au niveau des mers : ATTENTION si SEALEV <0
81    H(:,:)=max(H(:,:),1.)   ! pour avoir au moins 1 m
82
83         
84    ! calcul de flottaison
85    do j=1,ny
86       do i=1,nx
87
88          archimed = Bsoc(i,j)+H(i,j)*ro/row -sealevel
89
90          if ((archimed.LT.0.).and.(H(I,J).gt.1.E-3)) then    ! le point flotte
91             flot(i,j)=.true.
92          else
93             flot(i,j)=.false.
94          end if
95
96       end do
97    end do
98
99    ! lecture des coordonnées geographiques
100
101
102    ! les fichiers EISMINT etaient ranges i,j,lat,lon
103    ! je n'arrive pas a retrouver la projection exacte.
104    ! le x est donc calcule en partant de 0, 0
105
106    open(unit=20,file=grid_topo,iostat=ios)
107    read(20,*) 
108    read(20,*) 
109    read(20,*) n1,n2,ndx
110    read(20,*) 
111
112    if ((n1.eq.nx).and.(n2.eq.ny).and.(ndx.eq.nint(dx/1000.))) then
113       ! le fichier correspond bien a
114       ! la grille definie dans paradim
115
116       do k=1,nx*ny
117          read(20,*) i,j,xcc(i,j),ycc(i,j),xlong(i,j),ylat(i,j)
118       enddo
119       ! pour assurer la continuite des temperatures parametrees :
120       where(xlong(:,:).lt.100.)   
121          xlong(:,:)=xlong(:,:)+360.
122       end where
123
124    else
125       write(6,*) 'le fichier ne correspond pas a la grille definie'
126       STOP
127    end if
128    close(20)
129
130    ! xcc est en m
131    xmin=xcc(1,1)
132    ymin=ycc(1,1)
133    do j=1,ny
134       do i=1,nx
135          xcc(i,j)=xcc(i,j)*1000.
136          ycc(i,j)=ycc(i,j)*1000.
137       end do
138    end do
139    xmax=xcc(nx,ny)/1000
140    ymax=ycc(nx,ny)/1000
141
142    ! lecture de la carte de flux geothermique
143    open (20,file=ghf_fich)
144    read(20,*) n1,n2,ndx
145    if ((n1.eq.nx).and.(n2.eq.ny).and.(ndx.eq.nint(dx/1000.))) then
146       ! le fichier correspond bien a
147       ! la grille definie dans paradim
148       do j=1,ny
149          do i=1,nx
150             read(20,*) ghf(i,j)
151          end do
152       end do
153       close(20)
154    else
155       write(6,*) 'le fichier ne correspond pas a la grille definie'
156       STOP
157    end if
158
159
160    !  flux geothermique  : pour passer les flux des mW/m2 aux J/m2/an     
161    ghf(:,:)=-secyear*ghf(:,:)
162    !ghf(:,:)=-secyear*50.0/1000.   !ghf0 ! pour flux constant
163
164
165
166    ! calcul des courbures du socle
167!    call courbure(nx,ny,dx,Bsoc,bidon(:,:,1),bidon(:,:,2),bidon(:,:,3), &
168!         bidon(:,:,4),socle_cry,bidon(:,:,5))
169!    socle_cry(:,:)=socle_cry(:,:)*dx*dx
170
171    !------------------------------------------------     
172  end subroutine input_topo
173
174
175end module lect_topo_greeneem
Note: See TracBrowser for help on using the repository browser.