source: trunk/INPUT/MISMIP_3D/mismip3.f90 @ 80

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

initial import GRISLI trunk

File size: 6.6 KB
Line 
1program make_grisli_input
2
3!-------------------------------------------------------!
4!      Programm writen by V. Peyaud, nov 2011           !
5!                                                       !
6!      This is the squeleton of the programs            !
7!        that generates NetCDF input file for Grisli    !
8!                                                       !
9!-------------------------------------------------------!
10
11use netcdf
12use  io_netcdf_grisli
13!use sorties_ncdf_grisli
14implicit none
15
16
17! ---------------------------------------
18!      5 km   10 km
19! nx   321    161
20! ny    21     11
21! dx   5000.  10000.
22integer,parameter :: nx = 321      ! length of the 1st dim
23integer,parameter :: ny = 23       ! length of the 2nd dim
24real,parameter    :: dx  =5000.    ! resolution (m, calcule a partir du fichier .nc)
25real,parameter    :: dy  =5000.    ! resolution (m)
26integer           :: i,j           ! indexes
27! ---------------------------------------
28character(len=30) :: fil_sortie  ! output file
29integer                        :: status         ! utilise dans les appels netcdf
30integer                        :: ncid
31character(len=3), dimension(2) :: dimname        ! le nom de dimension dont on teste l'existence
32real*8,dimension(:),  pointer  :: Tab1d          ! pointeur vers les variables dimensions (et 1D)
33real*8,dimension(:,:),pointer  :: Tab            ! pointeur vers les variables 2D
34! ---------------------------------------
35character(len=20),dimension(3) :: dimnames2dxymaj       !< dimensions pour netcdf pour tableau 2d pour les noeud majeur
36real,dimension(nx,ny) :: S, H, B, Bsoc,Ubar,Usurf,Uslid,betamx  ! ,allocatable
37real,dimension(nx) :: xx
38real,dimension(ny) :: yy
39! ---------------------------------------
40character(len=50) :: inputfile ! input file
41real,dimension(nx) :: SW, HW, Bw, Bwsoc,Ubarw,Usurfw,Uslidw,betamxw
42
43
44! coordinates en m
45
46do i=1,nx
47     xx(i) = -(nx-1)/2.*dx + (i-1)*dx
48enddo
49do j=1,ny
50     yy(j) = -(ny-1)/2.*dy + (j-1)*dy
51enddo 
52
53!Use the standard output from Winnie
54
55! m3_1Stnd05_class01_rec01.nc
56!inputfile='profil_mismip3d_stnd5.nc' ! 5 km winnie standard run
57
58!inputfile='profil_Winnie_StndA5_steady_float_1D.nc'        ! 5 km winnie standard run
59inputfile='profil_Winnie_StndA5_steady_newbeta_1D.nc'       ! 5 km avec les valeurs de glissement et deformation de
60                                                            ! mismip
61
62allocate(Tab1d(nx))
63    call Read_Ncdf_var1d_Real('S',trim(inputfile),Tab1d)
64
65write(6,*) trim(inputfile),Tab1d(161)
66    SW=Tab1d
67deallocate(Tab1d)
68
69allocate(Tab1d(nx))
70    call Read_Ncdf_var1d_Real('H',trim(inputfile),Tab1d)
71    HW=Tab1d
72deallocate(Tab1d)
73allocate(Tab1d(nx))
74    call Read_Ncdf_var1d_Real('B',trim(inputfile),Tab1d)
75    BW=Tab1d
76deallocate(Tab1d)
77allocate(Tab1d(nx))
78    call Read_Ncdf_var1d_Real('Bsoc',trim(inputfile),Tab1d)
79    BWsoc=Tab1d
80deallocate(Tab1d)
81allocate(Tab1d(nx))
82    call Read_Ncdf_var1d_Real('Ubar',trim(inputfile),Tab1d)
83    Ubarw=Tab1d
84deallocate(Tab1d)
85allocate(Tab1d(nx))
86    call Read_Ncdf_var1d_Real('Usurf',trim(inputfile),Tab1d)
87    Usurfw=Tab1d
88deallocate(Tab1d)
89allocate(Tab1d(nx))
90    call Read_Ncdf_var1d_Real('Uslid',trim(inputfile),Tab1d)
91    Uslidw=Tab1d
92deallocate(Tab1d)
93allocate(Tab1d(nx))
94    call Read_Ncdf_var1d_Real('Betamx',trim(inputfile),Tab1d)
95    betamxw=Tab1d
96deallocate(Tab1d)
97
98
99do i=1,nx
100    S(i,:)      = SW(i)
101    H(i,:)      = HW(i)
102    B(i,:)      = BW(i)
103    Bsoc(i,:)   = BWsoc(i)
104    Ubar(i,:)   = Ubarw(i)
105    Usurf(i,:)  = Usurfw(i)
106    Uslid(i,:)  = Uslidw(i)
107    betamx(i,:) = betamxw(i)
108 enddo
109write(6,*) 'apres lecture sw(161)=',Sw(161),'     S(161,12)=',S(161,12)
110
111!    Bsoc(i,:)=-800+(i-1)*dx
112!enddo
113!Bsoc(:,:) = 0.
114!B(:,:)    = Bsoc(:,:)
115!H(:,:)    = 100.
116!S(:,:)    = B(:,:)+H(:,:)
117
118!
119! creation et fermeture du fichier output
120
121write(*,*) ncid
122fil_sortie='topo2grisli.nc'
123
124status  = nf90_create(trim(fil_sortie),nf90_write,ncid)
125if (status/=nf90_noerr) then   
126       write(*,*)"unable to create netcdf file : ",trim(fil_sortie),ncid
127endif
128
129status  = nf90_close(ncid)
130status  = nf90_open(trim(fil_sortie),nf90_write,ncid)
131if (status/=nf90_noerr) then   
132       write(*,*)"unable to close netcdf file : ",ncid
133endif
134
135dimname(1)='x'
136dimname(2)='y'
137
138write(6,*) "writing topo in NC file"
139write(6,*) "n ",nx,ny
140
141
142! ecriture dans le fichier output
143
144call write_ncdf_dim(dimname(1),trim(fil_sortie),nx)
145call write_ncdf_dim(dimname(2),trim(fil_sortie),ny)
146
147! Allouer & Deallouer chaque fois pour eviter des conflits d'identifiants
148
149allocate(Tab1d(nx))
150    Tab1d(:)=xx(:)
151    call write_ncdf_var(dimname(1),dimname(1),trim(fil_sortie), Tab1d ,'float')
152deallocate(Tab1d)
153allocate(Tab1d(ny))
154    Tab1d(:)=yy(:)   
155    call write_ncdf_var(dimname(2),dimname(2),trim(fil_sortie), Tab1d ,'float')
156
157!call Copy_Ncdf_att_var(dimname(1),trim(filin),trim(fil_sortie))
158
159allocate(Tab(nx,ny))
160    Tab=S
161    call write_ncdf_var('S',dimname(:),trim(fil_sortie), Tab ,'float')
162deallocate(Tab)
163allocate(Tab(nx,ny))
164    Tab=H
165    call write_ncdf_var('H',dimname(:),trim(fil_sortie), Tab ,'float')
166deallocate(Tab)
167allocate(Tab(nx,ny))
168    Tab=B
169    call write_ncdf_var('B',dimname(:),trim(fil_sortie), Tab ,'float')
170deallocate(Tab)
171allocate(Tab(nx,ny))
172    Tab=Bsoc
173    call write_ncdf_var('Bsoc',dimname(:),trim(fil_sortie), Tab ,'float')
174deallocate(Tab)
175allocate(Tab(nx,ny))
176    Tab=Ubar
177    call write_ncdf_var('Ubar',dimname(:),trim(fil_sortie), Tab ,'float')
178deallocate(Tab)
179allocate(Tab(nx,ny))
180    Tab=Uslid
181    call write_ncdf_var('Uslid',dimname(:),trim(fil_sortie), Tab ,'float')
182deallocate(Tab)
183allocate(Tab(nx,ny))
184    Tab=Usurf
185    call write_ncdf_var('Usurf',dimname(:),trim(fil_sortie), Tab ,'float')
186deallocate(Tab)
187allocate(Tab(nx,ny))
188    Tab=betamx
189    call write_ncdf_var('betamx',dimname(:),trim(fil_sortie), Tab ,'float')
190deallocate(Tab)
191
192
193!call write_ncdf_var(dimname(1),dimname(1),trim(fil_sortie),Tab1d,'float')
194!call Copy_Ncdf_att_var(dimname(1),trim(filin),trim(fil_sortie))
195
196
197!call write_ncdf_dim('x',trim(fil_sortie(j)),nx)
198!call write_ncdf_dim('y',trim(fil_sortie(j)),ny)
199
200!call write_ncdf_var('S',dimnames2dxymaj,trim(fil_sortie),   S  ,'double')
201!call write_ncdf_var('H',dimnames2dxymaj,trim(fil_sortie(k)),   H   ,nrecs(k),idef(k,p),'double')
202!call write_ncdf_var('Bsoc',dimnames2dxymaj,trim(fil_sortie(k)),Bsoc,nrecs(k),idef(k,p),'double')
203!call write_ncdf_var('B',dimnames2dxymaj,trim(fil_sortie(k)),  ,B   ,nrecs(k),idef(k,p),'double')
204
205!            read(72,*)
206!            read(72,*)
207!            read(72,*)
208!            read(72,*)
209!            read(72,*) long_name
210!            read(72,*) standard_name
211!            read(72,*) unit
212!            read(72,*) descriptions
213!            read(72,*)
214
215
216end program make_grisli_input
Note: See TracBrowser for help on using the repository browser.