source: trunk/SOURCES/Ant15_CISM_files/lect-Ant_CISM_15_dat.f90 @ 159

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

initial import GRISLI trunk

File size: 4.5 KB
Line 
1!> \file lect-Ant_CISM_15_dat.f90
2!!Module pour la lecture de la topographie
3!<
4
5!> \namespace lect_topo_ant_CISM_15
6!! Module pour la lecture de la topographie
7!! \author ...
8!! \date ...
9!! @note Used module
10!! @note   - use module3D_phy
11!! @note   - use param_phy_mod
12!<
13
14module lect_topo_ant_CISM_15
15
16  use module3D_phy
17  use param_phy_mod
18  use interface_input
19  character(len=100) :: topo_surf      !< surface
20  character(len=100) :: correc_surf    !< ice-real correction
21  character(len=100) :: topo_thick     !< thickness
22  character(len=100) :: topo_bed       !< bedrock
23  character(len=100) :: mask_grounded  !< mask
24  character(len=100) :: longitude      !< longitude
25  character(len=100) :: latitude       !< latitude
26  character(len=100) :: heatflux       !< geothermal heat flux
27
28  real,dimension(nx,ny) :: work_tab 
29  Character(len=100) :: file_ncdf      !< fichier netcdf issue des fichiers .dat
30
31contains
32
33  subroutine input_topo
34
35    namelist/topo_CISM_15/topo_surf,correc_surf,topo_thick,topo_bed,mask_grounded,longitude,latitude,heatflux
36
37428 format(A)
38
39    rewind(num_param)                     ! pour revenir au debut du fichier param_list.dat
40    read(num_param,topo_CISM_15)
41
42    write(num_rep_42,428)'!___________________________________________________________' 
43    write(num_rep_42,428)'!  module  lect_topo_ant_CISM        '
44    write(num_rep_42,topo_CISM_15)
45    write(num_rep_42,428)'!___________________________________________________________' 
46
47
48    topo_surf     = trim(dirnameinp)//trim(topo_surf)
49    correc_surf   = trim(dirnameinp)//trim(correc_surf)
50    topo_thick    = trim(dirnameinp)//trim(topo_thick)
51    topo_bed      = trim(dirnameinp)//trim(topo_bed)
52    mask_grounded = trim(dirnameinp)//trim(mask_grounded)
53    longitude     = trim(dirnameinp)//trim(longitude)
54    latitude      = trim(dirnameinp)//trim(latitude)
55    heatflux      = trim(dirnameinp)//trim(heatflux)
56
57    file_ncdf= trim(dirnameinp)//trim(runname)//'.nc'
58
59
60    ! lecture adaptee aux fichiers ZBL.dat
61
62    !call lect_datfile(nx,ny,Bsoc,1,topo_bed)               ! bedrock
63    call lect_input(3,'Bsoc',1,Bsoc,topo_bed,file_ncdf)
64
65    Bsoc0(:,:) = Bsoc(:,:)
66
67    call lect_input(3,'S',1,S,topo_surf,file_ncdf)
68    !call lect_datfile(nx,ny,S,1,topo_surf)                 ! surface
69
70
71    call lect_input(3,'H',1,H,topo_thick,file_ncdf)
72    !call lect_datfile(nx,ny,H,1,topo_thick)                ! thickness
73
74
75    !call lect_datfile(nx,ny,work_tab,1,correc_surf)        ! density correction
76    call lect_input(3,'work_tab1',1,work_tab,correc_surf,file_ncdf)
77
78    where (H(:,:).gt.0.)
79       work_tab(:,:)=min(H(:,:),work_tab(:,:))   
80       S(:,:) = S(:,:) - work_tab(:,:)                     ! corrected surface
81       H(:,:) = H(:,:) - work_tab(:,:)                     ! corrected thickness
82    end where
83    H(:,:)=max(0.,H(:,:))
84    H0(:,:)= H(:,:)
85    S0(:,:)= S(:,:)
86
87
88    call lect_input(3,'work_tab2',1,work_tab,mask_grounded,file_ncdf)
89    !call lect_datfile(nx,ny,work_tab,1,mask_grounded)      ! masque
90
91    mk0(:,:) = int(work_tab)
92
93
94    ! pour l'Antarctique masque mko vrai partout (version 2006)
95    MK0(:,:)=1
96
97    ! determination des flot
98    do j=1,ny
99       do i=1,nx
100          if ((Bsoc(i,j)+H(i,j)*ro/row -sealevel).lt.0.) then
101             flot(i,j)=.true.
102          else
103             flot(i,j)=.false.
104          endif
105       enddo
106    enddo
107
108    ! le calcul des courbures du socle devrait etre dans le dragging
109
110    call lect_input(1,'Xlong',1,Xlong,longitude,file_ncdf)
111    !call lect_datfile(nx,ny,Xlong,1,longitude)      ! lecture des coordonnées geographiques
112
113    call lect_input(1,'Ylat',1,Ylat,latitude,file_ncdf)
114    !call lect_datfile(nx,ny,Ylat,1,latitude)        !
115
116    open(22,file=longitude)
117    read(22,*) i,i,xmin,xmax,ymin,xmax
118    xmin=xmin/1000.
119    ymin=ymin/1000.
120    xmax=xmax/1000.
121    ymax=ymax/1000.
122    close(22)
123
124
125    !     lecture du fichier de reference pour le calcul du niveau des mers : etat actuel
126    !     pas de version correcte pour l'instant -> valeurs initiales
127    S_sealev(:,:) = S0(:,:)
128    H_sealev(:,:) = H0(:,:)
129    B_sealev(:,:) = Bsoc(:,:)
130    M_sealev(:,:) = Mk0(:,:)
131
132
133    call lect_input(1,'ghf',1,ghf,heatflux,file_ncdf)
134    !call lect_datfile(nx,ny,ghf,1,heatflux)
135
136
137    ! for the purposes of SeaRISE, GTHF should be capped at a value of -0.07 w/m^2,
138    ! and the field provided in the netCDF file does not include these updated values
139
140    ghf(:,:)=min(ghf(:,:),0.07)
141
142    ! pour passer les flux des W/m2 au J/m2/an     
143    ghf(:,:)=-SECYEAR*ghf(:,:)
144
145
146  end subroutine input_topo
147
148
149end module lect_topo_ant_CISM_15
Note: See TracBrowser for help on using the repository browser.