source: trunk/LMDZ.MARS/libf/phymars/albedocaps.F90 @ 706

Last change on this file since 706 was 283, checked in by aslmd, 13 years ago

LMDZ.MARS:

AS: J'ai fait ce commit et fait a la main un merge avec les modifications entre temps

24/08/11 == TN

Attempts to tune the water cycle by adding outliers

+ A few structural changes !!

  • watercap.h is now obsolete and removed -- all is in surfdat.h
  • watercaptag initialized in surfini.F (up to 7 areas defined) instead of initracer.F
    • settings proposed by AS commented
    • experiments by TN decommented. use with caution.
  • water ice albedo and thermal inertia in callphys.def and inifis.F
  • water ice albedo in surfini.F
  • water ice albedo computation in albedocaps.F90
  • alb_surfice is now obsolete in physiq.F, albedo_h2o_ice is used instead
  • frost_albedo_threshold defined in surfdat.h
  • water ice thermal inertia in soil.F

TODO: * calibrate thermal inertia and ice albedo

  • have a look at subgrid-scale ice with dryness ?
File size: 11.8 KB
Line 
1subroutine albedocaps(zls,ngrid,piceco2,psolaralb,emisref)
2
3! routine which changes the albedo (and emissivity) of the surface
4! depending on the presence of CO2 ice on the surface
5
6! to use the 'getin' routine
7use ioipsl_getincom
8
9implicit none
10
11#include"dimensions.h"
12#include"dimphys.h"
13#include"surfdat.h"
14#include"callkeys.h"
15
16! arguments:
17real,intent(in) :: zls ! solar longitude (rad)
18integer,intent(in) :: ngrid
19real,intent(in) :: piceco2(ngrid) ! amount of CO2 ice on the surface (kg/m2)
20real,intent(out) :: psolaralb(ngrid,2) ! albedo of the surface
21real,intent(out) :: emisref(ngrid) ! emissivity of the surface
22
23
24! local variables:
25logical,save :: firstcall=.true.
26integer :: ig,icap
27
28! 1. Initializations
29if (firstcall) then
30  ! find out if user wants to use TES cap albedoes or not
31  TESicealbedo=.false. ! default value
32  write(*,*)" albedocaps: Use TES Cap albedoes ?"
33  call getin("TESicealbedo",TESicealbedo)
34  write(*,*)" albedocaps: TESicealbedo = ",TESicealbedo
35 
36  ! if using TES albedoes, load coeffcients
37  if (TESicealbedo) then
38    write(*,*)" albedocaps: Coefficient for Northern Cap ?"
39    TESice_Ncoef=1.0 ! default value
40    call getin("TESice_Ncoef",TESice_Ncoef)
41    write(*,*)" albedocaps: TESice_Ncoef = ",TESice_Ncoef
42   
43    write(*,*)" albedocaps: Coefficient for Southern Cap ?"
44    TESice_Scoef=1.0 ! default value
45    call getin("TESice_Scoef",TESice_Scoef)
46    write(*,*)" albedocaps: TESice_Scoef = ",TESice_Scoef
47  endif
48 
49  firstcall=.false.
50endif ! of if (firstcall)
51
52do ig=1,ngrid
53  if (ig.gt.ngrid/2+1) then
54    icap=2 ! Southern hemisphere
55  else
56    icap=1 ! Northern hemisphere
57  endif
58
59  if (piceco2(ig).gt.0) then
60    ! set emissivity of surface to be the ice emissivity
61    emisref(ig)=emisice(icap)
62    ! set the surface albedo to be the ice albedo
63    if (TESicealbedo) then
64!      write(*,*) "albedocaps: call TES_icecap_albedo"
65!      write(*,*) "albedocaps: zls=",zls," ig=",ig
66      call TES_icecap_albedo(zls,ig,psolaralb(ig,1))
67!      write(*,*) "albedocaps: psolaralb(ig,1)=",psolaralb(ig,1)
68      psolaralb(ig,2)=psolaralb(ig,1)
69    else
70      psolaralb(ig,1)=albedice(icap)
71      psolaralb(ig,2)=albedice(icap)
72    endif
73  else if (watercaptag(ig) .and. water) then
74    ! there is a water ice cap: set the surface albedo to the water ice one
75    ! to do : emissivity
76    !write(*,*) "watercaptag in albedocaps:",ig
77    emisref(ig) = 1
78    psolaralb(ig,1)=albedo_h2o_ice
79    psolaralb(ig,2)=albedo_h2o_ice
80  else
81    ! set emissivity of surface to be bare ground emissivity
82    emisref(ig)=emissiv
83    ! set the surface albedo to bare ground albedo
84    psolaralb(ig,1)=albedodat(ig)
85    psolaralb(ig,2)=albedodat(ig)
86  endif ! of if (piceco2(ig).gt.0)
87enddo ! of ig=1,ngrid
88end subroutine albedocaps
89
90!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
91subroutine TES_icecap_albedo(zls,ig,alb)
92
93implicit none
94#include"dimensions.h"
95#include"dimphys.h"
96#include"surfdat.h"
97#include"comgeomfi.h"
98#include"netcdf.inc"
99#include"datafile.h"
100
101! arguments:
102real,intent(in) :: zls ! solar longitude (rad)
103integer,intent(in) :: ig ! grid point index
104real,intent(out) :: alb ! (interpolated) TES ice albedo at that grid point
105
106! local variables:
107logical,save :: firstcall=.true.
108real,save :: zls_old ! value of zls from a previous call
109integer,save :: tinf,tsup ! encompassing time indexes of TES data
110real,save :: reltime ! relative position in-between time indexes (in [0;1])
111integer :: latinf,latsup ! encompassing latitude indexes of TES data
112real :: rellat ! relative position in-between latitude indexes (in[0;1])
113integer :: loninf,lonsup ! encompassing longitude indexes of TES data
114real :: rellon !relative position in-between longitude indexes (in[0;1])
115real,save :: pi,radeg ! to convert radians to degrees
116real :: zlsd ! solar longitude, in degrees
117real :: latd ! latitude, in degrees
118real :: lond ! longitude, in degrees
119integer :: i
120integer :: icap ! =1: Northern hemisphere =2: Southern hemisphere
121
122! TES datasets: (hard coded fixed length/sizes; for now)
123integer,parameter :: TESlonsize=72
124real,parameter :: TESdeltalon=5.0 ! step in longitude in TES files
125! longitudes, in TES files, in degrees, from TESlon(1)=-177.5 to TESlon(72)=177.5
126real,save :: TESlon(TESlonsize)
127integer,parameter :: TESlatsize=30
128real,parameter :: TESdeltalat=2.0 ! step in latitude in TES files
129! latitudes (north hemisphere file), in degrees, from TESlatn(1)=31,
130! to TESlatn(30)=89 ; TESlatn(8)=45
131real,parameter :: TESlatnmin=45. ! minimum TES latitude (North hemisphere)
132real,parameter :: TESlatsmax=-45. ! maximum TES latitude (South hemisphere)
133real,save :: TESlatn(TESlatsize)
134! latitudes (south hemisphere file), in degrees, from TESlats(1)=-89,
135! to TESlats(30)=-31 ; TESlats(23)=-45
136real,save :: TESlats(TESlatsize)
137integer,parameter :: TESlssize=72
138real,parameter :: TESdeltals=5.0 ! step in solar longitude in TES files
139! Solar longitude in TES files, TESls(1)=2.5 to TESls(72)=357.5
140real,save :: TESls(TESlssize)
141! TES North albedo (=-1 for missing values)
142real,save :: TESalbn(TESlonsize,TESlatsize,TESlssize)
143! TES South albedo (=-1 for missing values)
144real,save :: TESalbs(TESlonsize,TESlatsize,TESlssize)
145! encompassing nodes arranged as follow : 4 3
146real :: val(4)                          ! 1 2
147
148!NetCDF variables:
149integer :: ierr ! NetCDF status
150integer :: nid ! NetCDF file ID
151integer :: nvarid ! NetCDF variable ID
152
153! 0. Preliminary stuff
154if (firstcall) then
155! Load TES albedoes for Northern Hemisphere
156  ! Note: datafile() is defined in "datafile.h"
157  ierr=NF_OPEN(trim(datafile)//"/npsc_albedo.nc",NF_NOWRITE,nid)
158  IF (ierr.NE.NF_NOERR) THEN
159    write(*,*)'Problem opening npsc_albedo.nc (phymars/albedocaps.F90)'
160    write(*,*)'It should be in :',trim(datafile),'/'
161    write(*,*)'1) You can change this directory address in '
162    write(*,*)'   file phymars/datafile.h'
163    write(*,*)'2) If necessary, npsc_albedo.nc (and other datafiles)'
164    write(*,*)'   can be obtained online on:'
165    write(*,*)'   http://www.lmd.jussieu.fr/~forget/datagcm/datafile'
166    CALL ABORT
167  ENDIF
168 
169  ierr=NF_INQ_VARID(nid,"longitude",nvarid)
170  if (ierr.ne.NF_NOERR) then
171    write(*,*) "Failed to find longitude in file!"
172  else
173    ierr=NF_GET_VAR_REAL(nid,nvarid,TESlon)
174  endif
175 
176  ierr=NF_INQ_VARID(nid,"latitude",nvarid)
177  if (ierr.ne.NF_NOERR) then
178    write(*,*) "Failed to find latitude in file!"
179  else
180    ierr=NF_GET_VAR_REAL(nid,nvarid,TESlatn)
181  endif
182 
183  ierr=NF_INQ_VARID(nid,"time",nvarid)
184  if (ierr.ne.NF_NOERR) then
185    write(*,*) "Failed to find time in file!"
186  else
187    ierr=NF_GET_VAR_REAL(nid,nvarid,TESls)
188  endif
189 
190  ierr=NF_INQ_VARID(nid,"albedo",nvarid)
191  if (ierr.ne.NF_NOERR) then
192    write(*,*) "Failed to find albedo in file!"
193  else
194    ierr=NF_GET_VAR_REAL(nid,nvarid,TESalbn)
195  endif
196
197! Load albedoes for Southern Hemisphere
198  ierr=NF_OPEN(trim(datafile)//"/spsc_albedo.nc",NF_NOWRITE,nid)
199  IF (ierr.NE.NF_NOERR) THEN
200    write(*,*)'Problem opening spsc_albedo.nc (phymars/albedocaps.F90)'
201    write(*,*)'It should be in :',trim(datafile),'/'
202    write(*,*)'1) You can change this directory address in '
203    write(*,*)'   file phymars/datafile.h'
204    write(*,*)'2) If necessary, spsc_albedo.nc (and other datafiles)'
205    write(*,*)'   can be obtained online on:'
206    write(*,*)'   http://www.lmd.jussieu.fr/~forget/datagcm/datafile'
207    CALL ABORT
208  ENDIF
209
210  ierr=NF_INQ_VARID(nid,"latitude",nvarid)
211  if (ierr.ne.NF_NOERR) then
212    write(*,*) "Failed to find latitude in file!"
213  else
214    ierr=NF_GET_VAR_REAL(nid,nvarid,TESlats)
215  endif
216
217  ierr=NF_INQ_VARID(nid,"albedo",nvarid)
218  if (ierr.ne.NF_NOERR) then
219    write(*,*) "Failed to find albedo in file!"
220  else
221    ierr=NF_GET_VAR_REAL(nid,nvarid,TESalbs)
222  endif
223
224! constants:
225  pi=acos(-1.)
226  radeg=180/pi
227
228  zls_old=-999 ! dummy initialization
229
230  firstcall=.false.
231endif ! of if firstcall
232
233! 1. Identify hemisphere and encompassing latitudes
234if (ig.GT.ngridmx/2+1) then
235  icap=2 ! Southern hemisphere
236else
237  icap=1 ! Northern hemisphere
238endif
239
240! Check that latitude is such that there is TES data to use
241! (ie: latitude 45 deg and poleward) otherwise use 'default' albedoes
242latd=lati(ig)*radeg ! latitude, in degrees
243if (icap.eq.1) then
244 ! North hemisphere
245 if (latd.lt.TESlatnmin) then
246   alb=albedice(1)
247   ! the job is done; quit this routine
248   return
249 else
250   ! find encompassing latitudes
251   if (latd.ge.TESlatn(TESlatsize)) then
252     latinf=TESlatsize
253     latsup=TESlatsize
254     rellat=0.
255   else
256     do i=1,TESlatsize-1
257       if ((latd.ge.TESlatn(i)).and.(latd.lt.TESlatn(i+1))) then
258         latinf=i
259         latsup=i+1
260         rellat=(latd-TESlatn(i))/TESdeltalat
261         exit ! found encompassing indexes; quit loop
262       endif
263     enddo
264   endif
265 endif ! of if (latd.lt.TESlatnmin)
266else ! icap=2
267 ! South hemisphere
268 if (latd.gt.TESlatsmax) then
269   alb=albedice(2)
270   ! the job is done; quit this routine
271   return
272 else
273   ! find encompassing latitudes
274   if (latd.lt.TESlats(1)) then
275     latinf=1
276     latsup=1
277     rellat=0.
278   else
279     do i=1,TESlatsize-1
280       if ((latd.ge.TESlats(i)).and.(latd.lt.TESlats(i+1))) then
281         latinf=i
282         latsup=i+1
283         rellat=(latd-TESlats(i))/TESdeltalat
284         exit ! found encompassing indexes; quit loop
285       endif
286     enddo
287   endif
288 endif ! of if (latd.gt.-45.)
289endif ! of if (icap.eq.1)
290
291! 2. Identify encompassing time indexes
292if (zls.ne.zls_old) then
293  zlsd=zls*radeg ! solar longitude, in degrees
294 
295  if (zlsd.lt.TESls(1)) then
296    tinf=TESlssize
297    tsup=1
298    reltime=0.5+zlsd/TESdeltals
299  else
300    if (zlsd.ge.TESls(TESlssize)) then
301      tinf=TESlssize
302      tsup=1
303      reltime=(360.-zlsd)/TESdeltals
304    else
305      ! look for encompassing indexes
306      do i=1,TESlssize-1
307        if ((zlsd.ge.TESls(i)).and.(zlsd.lt.TESls(i+1))) then
308          tinf=i
309          tsup=i+1
310          reltime=(zlsd-TESls(i))/TESdeltals
311          exit ! quit loop, we found the indexes
312        endif
313      enddo
314    endif
315  endif ! of if (zlsd.lt.TESls(1))
316 
317  zls_old=zls ! store current zls
318endif ! of if (zls.ne.zls_old)
319
320! 3. Identify encompassing longitudes
321lond=long(ig)*radeg ! east longitude, in degrees
322if (lond.lt.TESlon(1)) then
323  loninf=TESlonsize
324  lonsup=1
325  rellon=0.5+(180.+lond)/TESdeltalon
326else
327  if (lond.ge.TESlon(TESlonsize)) then
328    loninf=TESlonsize
329    lonsup=1
330    rellon=(180-lond)/TESdeltalon
331  else
332    do i=1,TESlonsize-1
333      if ((lond.ge.TESlon(i)).and.(lond.lt.TESlon(i+1))) then
334        loninf=i
335        lonsup=i+1
336        rellon=(lond-TESlon(i))/TESdeltalon
337        exit ! quit loop, we found the indexes
338      endif
339    enddo
340  endif ! of if (lond.ge.TESlon(TESlonsize))
341endif ! of if (lond.lt.TESlon(1))
342
343! 4. Use linear interpolation in time to build encompassing nodal values
344!    encompassing nodes are arranged as follow : 4 3
345!                                                1 2
346if (icap.eq.1) then
347  ! Northern hemisphere
348  val(1)=(1.-reltime)*TESalbn(loninf,latinf,tinf) &
349         +reltime*TESalbn(loninf,latinf,tsup)
350  val(2)=(1.-reltime)*TESalbn(lonsup,latinf,tinf) &
351         +reltime*TESalbn(lonsup,latinf,tsup)
352  val(3)=(1.-reltime)*TESalbn(lonsup,latsup,tinf) &
353         +reltime*TESalbn(lonsup,latsup,tsup)
354  val(4)=(1.-reltime)*TESalbn(loninf,latsup,tinf) &
355         +reltime*TESalbn(loninf,latsup,tsup)
356else
357  ! Southern hemisphere
358  val(1)=(1.-reltime)*TESalbs(loninf,latinf,tinf) &
359         +reltime*TESalbs(loninf,latinf,tsup)
360  val(2)=(1.-reltime)*TESalbs(lonsup,latinf,tinf) &
361         +reltime*TESalbs(lonsup,latinf,tsup)
362  val(3)=(1.-reltime)*TESalbs(lonsup,latsup,tinf) &
363         +reltime*TESalbs(lonsup,latsup,tsup)
364  val(4)=(1.-reltime)*TESalbs(loninf,latsup,tinf) &
365         +reltime*TESalbs(loninf,latsup,tsup)
366endif ! of if (icap.eq.1)
367
368! 5. Use bilinear interpolation to compute albedo
369alb=(1.-rellon)*(1.-rellat)*val(1) &
370    +rellon*(1.-rellat)*val(2) &
371    +rellon*rellat*val(3) &
372    +(1.-rellon)*rellat*val(4)
373
374! 6. Apply coefficient to interpolated TES albedo
375if (icap.eq.1) then
376  alb=alb*TESice_Ncoef
377else
378  alb=alb*TESice_Scoef
379endif ! of if (icap.eq.1)
380
381end subroutine TES_icecap_albedo
382
Note: See TracBrowser for help on using the repository browser.