Ignore:
Timestamp:
Jul 25, 2017, 11:38:07 AM (7 years ago)
Author:
mlefevre
Message:

Update of create_readmeteo and readmeteo accordingly to Venus calendar (see README), name of Venus GCM variable and Venus backwards rotation

Location:
trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/Venus
Files:
1 added
2 edited

Legend:

Unmodified
Added
Removed
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/Venus/create_readmeteo.F90

    r1733 r1756  
    1212!------------------------------------------------------------------------!
    1313
    14 INTEGER, PARAMETER :: MONTHS_PER_YEAR = 12
    15 INTEGER, PARAMETER :: mday(MONTHS_PER_YEAR)   &
    16            = (/61,66,66,65,60,54,50,46,47,47,51,56/)
    17 
     14INTEGER, PARAMETER :: MONTHS_PER_YEAR = 100
     15INTEGER, PARAMETER :: mday = 24
    1816INTEGER :: start_day,init,i,month,day
    1917INTEGER :: ierr,nid,nvarid
     
    2220INTEGER :: no_please
    2321INTEGER :: timedim,timelen
    24 
     22INTEGER :: inc
    2523REAL, DIMENSION(100) :: param
    2624REAL, DIMENSION(:), ALLOCATABLE :: time
     
    3230interval = 0
    3331
    34 
     32!mday(:)=24
    3533!
    3634! Open input NETCDF file
     
    3836write(*,*) "Scanning netcdf file ..."
    3937ierr=NF_OPEN ("input_diagfi.nc",NF_NOWRITE,nid)
    40 ierr=NF__OPEN ("input_diagfi.nc",NF_NOWRITE,4096,nid)
    41 !ierr=nc_open("input_diagfi.nc",NC_NOWRITE,nid)
     38!ierr=NF90_OPEN("input_diagfi.nc",NF_NOWRITE,nid)
    4239IF (ierr.NE.NF_NOERR) THEN
    4340      write(*,*)'**** Please create a symbolic link called input_diagfi.nc'
     
    4542ENDIF
    4643
    47 ierr=NF_INQ_DIMID(nid,"Time",timedim)
     44ierr=NF_INQ_DIMID(nid,"time_counter",timedim)
    4845IF (ierr .NE. NF_NOERR) THEN
    4946    ierr=NF_INQ_DIMID(nid,"time",timedim)
     
    5653!
    5754ALLOCATE(time(timelen))
    58 ierr = NF_INQ_VARID (nid, "Time",nvarid)
     55ierr = NF_INQ_VARID (nid, "time_counter",nvarid)
    5956IF (ierr .NE. NF_NOERR) THEN
    6057        ierr = NF_INQ_VARID (nid, "time",nvarid)
     
    7370IF (ierr .NE. NF_NOERR) THEN
    7471        PRINT *, "Error: Readmeteo <ps> not found"
    75         stop
     72        !stop
    7673ENDIF
    7774#ifdef NC_DOUBLE
     
    9289! beware, param(4) is the day reference of start and startfi
    9390! ...have to add time(1) to get the real starting date in diagfi
    94 start_day=floor(param(4)+time(1))               
    95 start_hour=nint((param(4)-floor(param(4))+time(1))*24)  ! starting hour
    96 start_hour=MOD(start_hour,24)   
    97 IF (interval .eq. 0) interval=nint(time(1)*24)   ! interval between each time subscript
    98 
    99 
     91!start_day=floor(param(4)+time(1))             
     92!start_hour=nint((param(4)-floor(param(4))+time(1))*13) ! starting hour
     93!start_hour=MOD(start_hour,24)   
     94!IF (interval .eq. 0) interval=nint(time(1)*24)  ! interval between each time subscript
     95
     96start_day=0
     97start_hour=0
     98interval=864 ! in hours, 864 HH = 1 MM = 1/100 Vd
    10099PRINT *,'*****************'
    101100PRINT *,'GCM data file starts at sol ',start_day,'and hour',start_hour
    102101PRINT *,'GCM data interval is ',interval,'hours'
    103102
    104 CALL wrf_day(start_day,month,day)
    105 
     103month=0
     104day=0
     105!interval=864
    106106!
    107107! User defined parameters
     
    116116if (no_please == 0) stop
    117117if (no_please == 1) then
    118         my=2024
     118        my=1000
    119119        n=timelen
    120         start=1
     120        start=0
    121121        interval_subs=1
    122122else
     
    124124        write(*,*) "Starting Martian year ? ex: 24,25,26..."
    125125        read(*,*) my
    126         my=2000+my
     126        my=1000+my
    127127        write(*,*) "-- WRF data file information --"
    128128        write(*,*) "How many files do you want to create ? at least 2, max is",timelen
     
    177177END DO
    178178! WRF time reference
    179 hour=start_hour+(start-1)*interval
     179hour=interval
    180180inc_hour=interval*interval_subs
    181 IF (hour >= 24) day=day+INT(hour/24)
    182 hour=MOD(hour,24)
    183 IF (day > mday(month)) THEN
    184       day=day-mday(month)
    185       month=month+1
     181IF (hour >= 36) day=day+INT(hour/36)
     182hour=MOD(hour,36)
     183IF (day >= mday) THEN
     184      inc=INT(day/mday)
     185      day=day-inc*mday
     186      month=month+inc
    186187END IF
    187 IF (month > MONTHS_PER_YEAR) THEN
     188IF (month >= MONTHS_PER_YEAR) THEN
    188189      my=my+1
    189       month=1
     190      month=0
    190191END IF
    191192DO i=1,n
     
    207208        END IF
    208209        write(6,fmt='(A1)') 'y'
    209 IF (hour+inc_hour >= 24) day=day+INT((hour+inc_hour)/24)
    210 hour=MOD(hour+inc_hour,24)
    211 IF (day > mday(month)) THEN
    212         day=day-mday(month)
    213         month=month+1
     210IF (hour+inc_hour >= 36) day=day+INT((hour+inc_hour)/36)
     211hour=MOD(hour+inc_hour,36)
     212IF (day >= mday) THEN
     213        inc=INT(day/mday)
     214        day=day-inc*mday
     215        month=month+inc
    214216END IF       
    215 IF (month > MONTHS_PER_YEAR) THEN
     217IF (month >= MONTHS_PER_YEAR) THEN
    216218        my=my+1
    217         month=1
     219        month=0
    218220END IF       
    219221END DO
     
    221223
    222224END
    223 
    224 
    225 !--------------------------------------------------
    226 !--------------------------------------------------
    227 
    228 SUBROUTINE wrf_day(gcm_day,wrf_month,day)
    229 
    230 IMPLICIT NONE
    231 
    232 INTEGER, INTENT(INOUT) :: gcm_day
    233 INTEGER, INTENT(OUT) :: wrf_month,day
    234 
    235 INTEGER :: init,i
    236 INTEGER, PARAMETER :: MONTHS_PER_YEAR = 12
    237 INTEGER, PARAMETER :: mday(MONTHS_PER_YEAR)   &
    238            = (/61,66,66,65,60,54,50,46,47,47,51,56/)
    239 
    240 !
    241 ! Find WRF month and day
    242 !
    243 
    244 IF (gcm_day >= 669) THEN    !! gcm_day commence au jour 0
    245         PRINT *,'out of bounds ! martian year is 669 sols !'
    246         gcm_day=MOD(gcm_day,669)
    247         !STOP
    248 ENDIF
    249 
    250 
    251 
    252 init=gcm_day+1    !!+1 sinon on decale tout
    253 DO i=1,MONTHS_PER_YEAR
    254         wrf_month=i
    255         init=init-mday(i)
    256         IF (init <= 0) EXIT
    257 END DO
    258 
    259 PRINT *,'corresponding WRF month is ',wrf_month
    260 day=init+mday(wrf_month)
    261 PRINT *,'corresponding WRF day is ',day
    262 PRINT *,'*****************'
    263 
    264 END
  • trunk/MESOSCALE/LMD_MM_MARS/SRC/PREP_MARS/Venus/readmeteo.F90

    r1733 r1756  
    4141
    4242REAL :: ptop
    43 REAL, PARAMETER :: grav=3.72
     43REAL, PARAMETER :: grav=8.89
    4444LOGICAL, PARAMETER :: blank=.false.
    4545
     
    7373
    7474!! Intermediate data arrays
    75 integer :: k,l,m,n,p
     75integer :: k,l,m,n,p,i,j
    7676real, dimension(:), allocatable :: lat,lon,time,alt,aps,bps,levels,vertdsoil
    7777real, dimension(:,:), allocatable :: vide,ones,ghtsfile
     
    8181real, dimension(:,:,:), allocatable :: emissfile,co2icefile
    8282real, dimension(:,:,:), allocatable :: tnsfile,unsfile,vnsfile
    83 real, dimension(:,:,:,:), allocatable :: tfile,ufile,vfile,rfile,hfile
     83real, dimension(:,:,:,:), allocatable :: tfile,ufile,vfile,rfile,hfile,ghfile
     84real, dimension(:,:,:,:), allocatable :: pfile
    8485real, dimension(:,:,:,:), allocatable :: eta_gcm
    8586!real, dimension(:,:,:,:), allocatable :: tfileorig,ufileorig,vfileorig
     
    173174SELECT CASE(ident)
    174175CASE('LMD')
    175 ierr=NF_INQ_DIMID(nid,"Time",timedim)
     176ierr=NF_INQ_DIMID(nid,"time_counter",timedim)
    176177CASE('OXF')
    177178ierr=NF_INQ_DIMID(nid,"time",timedim)
     
    182183SELECT CASE(ident)
    183184CASE('LMD')
    184 ierr=NF_INQ_DIMID(nid,"latitude",latdim)
     185ierr=NF_INQ_DIMID(nid,"lat",latdim)
    185186CASE('OXF')
    186187ierr=NF_INQ_DIMID(nid,"lat",latdim)
     
    191192SELECT CASE(ident)
    192193CASE('LMD')
    193 ierr=NF_INQ_DIMID(nid,"longitude",londim)
     194ierr=NF_INQ_DIMID(nid,"lon",londim)
    194195CASE('OXF')
    195196ierr=NF_INQ_DIMID(nid,"lon",londim)
     
    200201SELECT CASE(ident)
    201202CASE('LMD')
    202 ierr=NF_INQ_DIMID(nid,"altitude",altdim)
     203ierr=NF_INQ_DIMID(nid,"presnivs",altdim)
    203204CASE('OXF')
    204205ierr=NF_INQ_DIMID(nid,"sigma",altdim)
     
    214215allocate(eta_gcm(lonlen,latlen,altlen,timelen))
    215216allocate(tfile(lonlen,latlen,altlen,timelen))
     217allocate(pfile(lonlen,latlen,altlen,timelen))
    216218allocate(tsoilfile(lonlen,latlen,altlen,timelen))
    217219allocate(dsoilfile(lonlen,latlen,altlen,timelen))
     
    244246allocate(gwparam(lonlen,latlen,5))
    245247allocate(ghtsfile(lonlen,latlen))    !! no scan axis
     248allocate(ghfile(lonlen,latlen,altlen,timelen))
    246249allocate(vide(lonlen,latlen))
    247250allocate(ones(lonlen,latlen))
     
    270273
    271274tfile(:,:,:,:)=0
     275pfile(:,:,:,:)=0
    272276tsoilfile(:,:,:,:)=0
    273277isoilfile(:,:,:,:)=0
     
    300304gwparam(:,:,:)=0
    301305ghtsfile(:,:)=0
     306ghfile(:,:,:,:)=0
    302307vide(:,:)=0
    303308ones(:,:)=0
     
    313318SELECT CASE(ident)
    314319CASE('LMD')
    315    ierr = NF_INQ_VARID (nid, "Time",nvarid)
     320   ierr = NF_INQ_VARID (nid, "time_counter",nvarid)
    316321CASE('OXF')
    317322   ierr = NF_INQ_VARID (nid, "time",nvarid)
     
    331336SELECT CASE(ident)
    332337CASE('LMD')
    333    ierr = NF_INQ_VARID (nid, "latitude",nvarid)
     338   ierr = NF_INQ_VARID (nid, "lat",nvarid)
    334339CASE('OXF')
    335340   ierr = NF_INQ_VARID (nid, "lat",nvarid)
     
    349354SELECT CASE(ident)
    350355CASE('LMD')
    351    ierr = NF_INQ_VARID (nid, "longitude",nvarid)
     356   ierr = NF_INQ_VARID (nid, "lon",nvarid)
    352357CASE('OXF')
    353358   ierr = NF_INQ_VARID (nid, "lon",nvarid)
     
    364369   print *,lon(1),' ... to ... ',lon(lonlen),' ... step: ',lon(lonlen)-lon(lonlen-1)
    365370
    366 SELECT CASE(ident)
    367 CASE('LMD')
    368 print *, 'Hybrid coordinates'
    369    ierr = NF_INQ_VARID (nid, "aps", nvarid)
    370    IF (ierr .NE. NF_NOERR) THEN
    371       PRINT *, "Error: Readmeteo <aps> not found"
    372       stop
    373    ENDIF
    374 #ifdef NC_DOUBLE
    375    ierr = NF_GET_VAR_DOUBLE(nid, nvarid, aps)
    376 #else
    377    ierr = NF_GET_VAR_REAL(nid, nvarid, aps)
    378 #endif
    379    ierr = NF_INQ_VARID (nid, "bps", nvarid)
    380    IF (ierr .NE. NF_NOERR) THEN
    381       PRINT *, "Error: Readmeteo <bps> not found"
    382       stop
    383    ENDIF
    384 #ifdef NC_DOUBLE
    385    ierr = NF_GET_VAR_DOUBLE(nid, nvarid, bps)
    386 #else
    387    ierr = NF_GET_VAR_REAL(nid, nvarid, bps)
    388 #endif
    389    print *,aps(1),' ... to ... ',aps(altlen)
    390    print *,bps(1),' ... to ... ',bps(altlen)
    391 CASE('OXF')
    392    ierr = NF_INQ_VARID (nid, "sigma", nvarid)
    393    IF (ierr .NE. NF_NOERR) THEN
    394       PRINT *, "Error: Readmeteo <sigma> not found"
    395       stop
    396    ENDIF
    397 #ifdef NC_DOUBLE
    398    ierr = NF_GET_VAR_DOUBLE(nid, nvarid, bps)
    399 #else
    400    ierr = NF_GET_VAR_REAL(nid, nvarid, bps)
    401 #endif
    402    print *,bps(1),' ... to ... ',bps(altlen)
    403 END SELECT
     371!SELECT CASE(ident)
     372!CASE('LMD')
     373!print *, 'Hybrid coordinates'
     374!   ierr = NF_INQ_VARID (nid, "aps", nvarid)
     375!   IF (ierr .NE. NF_NOERR) THEN
     376!      PRINT *, "Error: Readmeteo <aps> not found"
     377!      stop
     378!   ENDIF
     379!#ifdef NC_DOUBLE
     380!   ierr = NF_GET_VAR_DOUBLE(nid, nvarid, aps)
     381!#else
     382!   ierr = NF_GET_VAR_REAL(nid, nvarid, aps)
     383!#endif
     384!   ierr = NF_INQ_VARID (nid, "bps", nvarid)
     385!   IF (ierr .NE. NF_NOERR) THEN
     386!      PRINT *, "Error: Readmeteo <bps> not found"
     387!      stop
     388!   ENDIF
     389!#ifdef NC_DOUBLE
     390!   ierr = NF_GET_VAR_DOUBLE(nid, nvarid, bps)
     391!#else
     392!   ierr = NF_GET_VAR_REAL(nid, nvarid, bps)
     393!#endif
     394!   print *,aps(1),' ... to ... ',aps(altlen)
     395!   print *,bps(1),' ... to ... ',bps(altlen)
     396!CASE('OXF')
     397!   ierr = NF_INQ_VARID (nid, "sigma", nvarid)
     398!  IF (ierr .NE. NF_NOERR) THEN
     399!      PRINT *, "Error: Readmeteo <sigma> not found"
     400!      stop
     401!   ENDIF
     402!#ifdef NC_DOUBLE
     403!   ierr = NF_GET_VAR_DOUBLE(nid, nvarid, bps)
     404!#else
     405!   ierr = NF_GET_VAR_REAL(nid, nvarid, bps)
     406!#endif
     407!   print *,bps(1),' ... to ... ',bps(altlen)
     408!END SELECT
    404409
    405410
     
    443448
    444449print *,'Surface Pressure'
    445    ierr = NF_INQ_VARID (nid,"ps",nvarid)
     450   ierr = NF_INQ_VARID (nid,"psol",nvarid)
    446451   IF (ierr .NE. NF_NOERR) THEN
    447452      PRINT *, "Error: Readmeteo <ps> not found"
     
    455460
    456461print *,'Ground Temperature'
    457    ierr = NF_INQ_VARID (nid,"tsurf",nvarid)
     462   ierr = NF_INQ_VARID (nid,"tsol",nvarid)
    458463   IF (ierr .NE. NF_NOERR) THEN
    459464      PRINT *, "Error: Readmeteo <tsurf> not found"
     
    518523!   vnsfile=vfileorig(:,:,1,:)
    519524
    520 SELECT CASE(ident)
    521 CASE('LMD')
    522    print *,'Geopotential height at the ground'
    523    ierr = NF_INQ_VARID (nid,"phisinit",nvarid)
     525print *,'>>> Read 3D meteorological fields ! - This may take some time ...'
     526
     527print *,'Geopotential height'
     528   ierr = NF_INQ_VARID (nid,"geop",nvarid)
    524529   IF (ierr .NE. NF_NOERR) THEN
    525       PRINT *, "Error: Readmeteo <phisinit> not found"
     530      PRINT *, "Error: Readmeteo <geop> not found"
    526531      stop
    527532   ENDIF
    528533#ifdef NC_DOUBLE
    529    ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ghtsfile)
     534   ierr = NF_GET_VAR_DOUBLE(nid, nvarid, ghfile)
    530535#else
    531    ierr = NF_GET_VAR_REAL(nid, nvarid, ghtsfile)
     536   ierr = NF_GET_VAR_REAL(nid, nvarid, ghfile)
    532537#endif
    533 !**** from geopotential to geopotential height
    534 ghtsfile=ghtsfile/grav
    535 !****
    536 CASE('OXF')
    537 !
    538 ! geopotential height ~ altimetry
    539 !
    540 print *,'Geopotential height at the ground from file mountain_new.nc'
    541 ierr=NF_OPEN("mountain_new.nc",NF_NOWRITE,nid3)
    542     if (ierr.ne.NF_NOERR) then
    543       write(*,*) "Error: Could not open that file either"
    544       stop "Might as well stop here"
    545     endif
    546 ierr=NF_INQ_VARID(nid3,"orography",nvarid)
    547 ierr=NF_GET_VAR_REAL(nid3,nvarid,ghtsfile)
    548 if (ierr.ne.NF_NOERR) then
    549     stop "Error: Failed reading phisinit"
    550 endif
    551 ierr=NF_CLOSE(nid3)
    552 END SELECT
    553 
    554 
    555 print *,'>>> Read 3D meteorological fields ! - This may take some time ...'
     538ghtsfile=ghfile(:,:,1,1)/grav !surface geop
     539
     540print *,'Pressure'
     541   ierr = NF_INQ_VARID (nid,"pres",nvarid)
     542   IF (ierr .NE. NF_NOERR) THEN
     543      ierr = NF_INQ_VARID (nid,"p",nvarid)
     544        IF (ierr .NE. NF_NOERR) THEN
     545          PRINT *, "Error: Readmeteo <p> not found"
     546          stop
     547        ENDIF
     548   ENDIF
     549#ifdef NC_DOUBLE
     550   ierr = NF_GET_VAR_DOUBLE(nid, nvarid, pfile)
     551#else
     552   ierr = NF_GET_VAR_REAL(nid, nvarid, pfile)
     553#endif
    556554
    557555print *,'Temperature'
     
    572570
    573571print *,'Zonal wind'   
    574    ierr = NF_INQ_VARID (nid,"u",nvarid)
     572   ierr = NF_INQ_VARID (nid,"vitu",nvarid)
    575573   IF (ierr .NE. NF_NOERR) THEN
    576574      PRINT *, "Error: Readmeteo <u> not found"
     
    585583
    586584print *,'Meridional wind'
    587    ierr = NF_INQ_VARID (nid,"v",nvarid)
     585   ierr = NF_INQ_VARID (nid,"vitv",nvarid)
    588586   IF (ierr .NE. NF_NOERR) THEN
    589587      PRINT *, "Error: Readmeteo <v> not found"
     
    595593   ierr = NF_GET_VAR_REAL(nid, nvarid, vfile)
    596594#endif
    597 vnsfile=ufile(:,:,1,:)
    598 
     595vnsfile=vfile(:,:,1,:)
    599596
    600597!!------------------------
     
    762759
    763760!END SELECT
     761
     762print*,'VENUS : rotation backward -> inversion of lat and long'
     763DO i=1,latlen
     764DO j=1,lonlen
     765  psfile(j,i,:)=psfile(lonlen+1-j,latlen+1-i,:)
     766  tsfile(i,j,:)=tsfile(lonlen+1-j,latlen+1-i,:)
     767  ghtsfile(j,i)=ghtsfile(lonlen+1-j,latlen+1-i)
     768  ghfile(j,i,:,:)=ghfile(lonlen+1-j,latlen+1-i,:,:)
     769  pfile(j,i,:,:)=pfile(lonlen+1-j,latlen+1-i,:,:)
     770  tfile(j,i,:,:)=tfile(lonlen+1-j,latlen+1-i,:,:)
     771  ufile(j,i,:,:)=ufile(lonlen+1-j,latlen+1-i,:,:)
     772  vfile(j,i,:,:)=vfile(lonlen+1-j,latlen+1-i,:,:)
     773  tsoilfile(j,i,:,:)=tsoilfile(lonlen+1-j,latlen+1-i,:,:)
     774ENDDO
     775ENDDO 
    764776
    765777ierr=NF_CLOSE(nid)
     
    876888        write(1) SLAB
    877889!print *,'The field '//DESC//' was written to '//output
    878 
    879890!------------------------!   
    880891! >>> Write a variable   !
     
    894905        write(1) SLAB
    895906!print *,'The field '//DESC//' was written to '//output
    896 
    897907!------------------------!   
    898908! >>> Write a variable   !
     
    903913DESC='Meridional wind'
    904914XLVL=200100.
    905 SLAB=vnsfile(:,:,time_out(l))
     915SLAB=-1*vnsfile(:,:,time_out(l)) !VENUS ratoting backwards : v=-1*v
    906916        ! And now put everything in the destination file
    907917        ! ... Header
     
    912922        write(1) SLAB
    913923!print *,'The field '//DESC//' was written to '//output
    914 
    915924!------------------------!   
    916925! >>> Write a variable   !
     
    13661375DO k = 1,altlen
    13671376        XLVL=levels(k)
    1368         SLAB=tfile(:,:,k,time_out(l))
     1377        SLAB=tfile(:,:,k,time_out(l))
    13691378                ! And now put everything in the destination file
    13701379                ! ... Header
     
    13861395DO k = 1,altlen
    13871396        XLVL=levels(k)
    1388         SLAB=ufile(:,:,k,time_out(l))
     1397        SLAB=ufile(:,:,k,time_out(l))
    13891398                ! And now put everything in the destination file
    13901399                ! ... Header
     
    13941403                ! ... Data
    13951404                write(1) SLAB
     1405                !write(1) ufile(:,:,k,time_out(l))
    13961406END DO
    13971407!print *,'The field '//DESC//' was written to '//output
     
    14061416DO k = 1,altlen
    14071417        XLVL=levels(k)
    1408         SLAB=vfile(:,:,k,time_out(l))
     1418        SLAB=-1*vfile(:,:,k,time_out(l)) ! VENUS rotation backward : v=-1*v
    14091419                ! And now put everything in the destination file
    14101420                ! ... Header
     
    14301440SELECT CASE(ident)
    14311441CASE('LMD')
    1432         SLAB=aps(k)+bps(k)*psfile(:,:,time_out(l))
     1442        SLAB=pfile(:,:,k,time_out(l))
    14331443CASE('OXF')
    1434         SLAB=bps(k)*psfile(:,:,time_out(l))
     1444        !SLAB=bps(k)*psfile(:,:,time_out(l))
    14351445END SELECT
    14361446                ! And now put everything in the destination file
     
    14531463DO k = 1,altlen
    14541464        XLVL=levels(k)
    1455 !!*******
    1456 !! PROVISOIRE: normalement, il faudrait la hauteur geopotentielle
    1457 !!*******
    1458 !!however, not used by initialize_real
    14591465SELECT CASE(ident)
    14601466CASE('LMD')
    1461         SLAB=10000.*alog(610./(aps(k)+bps(k)*psfile(:,:,time_out(l))))
     1467        SLAB=(ghfile(:,:,k,time_out(l)))/grav
    14621468CASE('OXF')
    1463         SLAB=10000.*alog(610./(bps(k)*psfile(:,:,time_out(l))))
     1469        !SLAB=10000.*alog(610./(bps(k)*psfile(:,:,time_out(l))))
    14641470END SELECT
    14651471                ! And now put everything in the destination file
     
    15631569        XLVL=levels(k)
    15641570        SLAB=isoilfile(:,:,k,time_out(l))
     1571       
    15651572                ! And now put everything in the destination file
    15661573                ! ... Header
     
    17101717deallocate(eta_gcm)
    17111718deallocate(tfile)
     1719deallocate(pfile)
    17121720deallocate(tsoilfile)
    17131721deallocate(isoilfile)
     
    17371745deallocate(co2icefile)
    17381746deallocate(ghtsfile)    !! no scan axis
     1747deallocate(ghfile)
    17391748deallocate(vide)
    17401749deallocate(ones)
Note: See TracChangeset for help on using the changeset viewer.