source: trunk/SOURCES/GrIce2sea_files/lect_GrIce2sea_gen_nc.f90 @ 4

Last change on this file since 4 was 4, checked in by dumas, 10 years ago

initial import GRISLI trunk

File size: 7.6 KB
Line 
1!> \file lect_GrIce2sa_gen_nc.f90
2!!Module pour la lecture de la topographie
3!<
4
5!> \namespace lect_topo_green_gen
6!! Module pour la lecture de la topographie
7!! \author Cat
8!! \date 31 oct 2011
9!! @note Used module
10!! @note   - use module3D_phy
11!! @note   - use param_phy_mod
12!<
13
14module lect_topo_green_gen
15
16  use module3D_phy
17  use param_phy_mod
18  use interface_input
19  use io_netcdf_grisli
20
21  character(len=100) :: topo_surf      !< surface file name
22  character(len=100) :: correc_surf    !< ice-real correction file name
23! character(len=100) :: topo_thick    !< thickness file name
24  character(len=100) :: topo_bed       !< bedrock file name
25  character(len=100) :: mask_grounded  !< mask file name
26  character(len=100) :: longitude      !< longitude file name
27  character(len=100) :: latitude       !< latitude file name
28  character(len=100) :: heatflux       !< geothermal heat flux
29  logical            :: corr_firn      !< eventuellement correction firn (pour l'instant surface dejà corrigee)
30
31
32  real,dimension(nx,ny) :: work_tab 
33
34  character(len=100) :: file_ncdf      !< fichier netcdf issue des fichiers .dat
35
36contains
37
38  subroutine input_topo
39
40    namelist/topo_groen_gen/topo_surf,correc_surf,topo_bed,mask_grounded,longitude,latitude,heatflux
41
42
43    if (itracebug.eq.1)  call tracebug(' Entree dans routine input_topo')
44
45428 format(A)
46
47    rewind(num_param)                     ! pour revenir au debut du fichier param_list.dat
48    read(num_param,topo_groen_gen)
49
50    write(num_rep_42,428)'!___________________________________________________________' 
51    write(num_rep_42,428)'!  module  lect_topo_ant_gen                                '
52    write(num_rep_42,topo_groen_gen)
53    write(num_rep_42,428)'!___________________________________________________________' 
54
55
56    if ((trim(correc_surf).eq.'no').or.(trim(correc_surf).eq.'NO')) then
57       corr_firn=.false.
58    else
59       corr_firn=.true.
60    end if
61
62
63    topo_surf     = trim(dirnameinp)//trim(topo_surf)
64    correc_surf   = trim(dirnameinp)//trim(correc_surf)
65!   topo_thick    = trim(dirnameinp)//trim(topo_thick)
66    topo_bed      = trim(dirnameinp)//trim(topo_bed)
67    mask_grounded = trim(dirnameinp)//trim(mask_grounded)
68    longitude     = trim(dirnameinp)//trim(longitude)
69    latitude      = trim(dirnameinp)//trim(latitude)
70    heatflux      = trim(dirnameinp)//trim(heatflux)
71
72
73! Transformation des fichiers .dat en .nc
74
75    file_ncdf= trim(dirnameinp)//trim(runname)//'.nc'
76
77! lecture adaptee aux fichiers ZBL.dat ou netcdf ou grd
78
79    call lect_input(1,'Bsoc',1,Bsoc,topo_bed,file_ncdf)    ! socle
80    Bsoc0(:,:) = Bsoc(:,:)
81
82    call lect_input(1,'S',1,S,topo_surf,file_ncdf)         ! surface
83   
84!    call lect_input(1,'H',1,H,topo_thick,file_ncdf)       ! epaisseur calculee ensuite
85
86    if (itracebug.eq.1)  call tracebug(' avant corr firn')
87
88    if (corr_firn) then                                    ! density correction     
89       call lect_input(1,'work_tab1',1,work_tab,correc_surf,file_ncdf)
90
91       where (H(:,:).gt.0.)
92          work_tab(:,:)=min(H(:,:),work_tab(:,:))   
93          S(:,:) = S(:,:) - work_tab(:,:)                  ! corrected surface
94          H(:,:) = H(:,:) - work_tab(:,:)                  ! corrected thickness
95       end where
96    end if
97
98    if (itracebug.eq.1)  call tracebug(' apres corr firn')
99    H(:,:)=max(0.,H(:,:))
100    H0(:,:)= H(:,:)
101    S0(:,:)= S(:,:)
102
103
104    mk0(:,:)=0.
105    mk_init(:,:)=0.
106
107    call lect_input(1,'work_tab2',2,work_tab,mask_grounded,file_ncdf)  ! masque
108
109
110! definition du Mk_init dans ice2sea
111!__________________________________________
112!  outcrops         ->  eventuellement lu dans un autre fichier
113!  ocean libre      ->  0
114!  toundra          ->  1
115!  pose avec glace  ->  2
116!  epaisseur fixe   ->  3  masque pour ne pas traiter ces points
117!  ice shelves      ->  4
118
119    mk_init(:,:) = nint(work_tab(:,:))
120
121    if (itracebug.eq.1)  call tracebug(' avant worktab')
122
123
124! make consistency of input data files (flotation, thickness ...)
125! Rappel : dans param_phy_mod
126! coef_Sflot = (Row-Ro)/Row    S = coef_Sflot * H + sealevel pour les shelves
127! coef_Bflot = -Ro/Row   B = coef_Bflot * H + sealevel pour les shelves
128
129
130    do j=1,ny
131       do i=1,nx
132          if (mk_init(i,j).eq.0) then                     ! ocean
133             H(i,j)    = 1.                               ! valeur bidon pour l'ocean
134             S(i,j)    = coef_Sflot * H(i,j)
135             B(i,j)    = coef_Bflot * H(i,j)
136             Bsoc(i,j) = -100.                            ! on surcreuse le socle
137
138             flot(i,j) = .true.
139
140          else if  (mk_init(i,j).eq.1) then               ! toundra
141             S(i,j)    = max(Bsoc(i,j),0.)
142             H(i,j)    = S(i,j) - Bsoc(i,j) 
143             B(i,j)    = Bsoc(i,j)
144
145             flot(i,j) = .false.
146
147          else if  (mk_init(i,j).eq.2) then               ! glace
148             H(i,j)    = S(i,j) - Bsoc(i,j) 
149             B(i,j)    = Bsoc(i,j)
150             flot(i,j) = .false.   
151
152          else if  (mk_init(i,j).eq.3) then               ! zones a ne pas toucher
153             ! le traitement "fixe" se fait dans prescribe_mod
154             H(i,j)    = S(i,j) - Bsoc(i,j) 
155             B(i,j)    = Bsoc(i,j)
156             flot(i,j) = .false.   
157
158          else if (mk_init(i,j).eq.4) then                ! ice shelf
159             H(i,j)    = S(i,j) / coef_Sflot
160             B(i,j)    = S(i,j) - H(i,j)
161             Bsoc(i,j) = min (B(i,j)-20.,Bsoc(i,j))       ! on surcreuse le socle si besoin
162             flot(i,j)=.true.
163          end if
164
165       end do
166    end do
167
168! garder les cartes debut de run
169    Bsoc0(:,:) = Bsoc(:,:)
170    H0(:,:)= H(:,:)
171    S(:,:) = B(:,:) +H(:,:)
172    S0(:,:)= S(:,:)
173
174
175    if (itracebug.eq.1)  call tracebug(' apres consistency')
176
177
178    ! pour l'Antarctique masque mko vrai partout (version 2006)
179    MK0(:,:)=1  ! mis apres la lecture cptr
180
181
182    call lect_input(1,'Xlong',1,Xlong,longitude,file_ncdf)
183    !call lect_datfile(nx,ny,Xlong,1,longitude)      ! lecture des coordonnées geographiques
184   
185    call lect_input(1,'Ylat',1,Ylat,latitude,file_ncdf)
186    !call lect_datfile(nx,ny,Ylat,1,latitude)        !
187
188    if (itracebug.eq.1)  call tracebug(' apres lect lon/lat')
189
190
191! pour recuperer le xmin xmax ymin ymax, on s'inspire de ce que Cat a fait pour l'antarc :
192!   write(6,*) 'topo_surf',topo_surf
193!   call Read_Ncdf_var('x',trim(topo_surf),Tab1D)    ! lit le tableau x
194!   xmin = minval(Tab1D(:))
195!   xmax = maxval(Tab1d(:))
196!   call Read_Ncdf_var('y',trim(topo_surf),Tab1D)    ! lit le tableau y
197!   ymin = minval(Tab1D(:))
198!   ymax = maxval(Tab1d(:))
199
200    open(22,file=trim(dirnameinp)//'long_ZBL_CISM_5km.dat')                         ! juste pour avoir l'en tete
201    read(22,*) i,i,xmin,xmax,ymin,ymax
202    xmin=xmin/1000.
203    ymin=ymin/1000.
204    xmax=xmax/1000.
205    ymax=ymax/1000.
206    close(22)
207
208
209    !     lecture du fichier de reference pour le calcul du niveau des mers : etat actuel
210    !     pas de version correcte pour l'instant -> valeurs initiales
211    S_sealev(:,:) = S0(:,:)
212    H_sealev(:,:) = H0(:,:)
213    B_sealev(:,:) = Bsoc(:,:)
214    M_sealev(:,:) = Mk0(:,:)
215
216    if (itracebug.eq.1)  call tracebug(' apres lect entete')
217 
218    call lect_input(1,'ghf',1,ghf,heatflux,file_ncdf)               ! flux geothermique
219
220
221    ! for the purposes of SeaRISE, GTHF should be capped at a value of -0.07 w/m^2,
222    ! and the field provided in the netCDF file does not include these updated values
223    ! ghf(:,:)=min(ghf(:,:),70.)           ! pour sea rise
224
225    ! pour passer les flux des W/m2 au J/m2/an     
226    ghf(:,:)=-SECYEAR*ghf(:,:)     !  les flux sont donnes en W/m2, correction pour passer a l'annee
227    ghf0(:,:)=ghf(:,:)
228
229    if (itracebug.eq.1)  call tracebug(' a la fin d input_topo')
230
231  end subroutine input_topo
232
233
234end module lect_topo_green_gen
235
Note: See TracBrowser for help on using the repository browser.