Ignore:
Timestamp:
Jun 4, 2015, 4:23:32 PM (10 years ago)
Author:
slebonnois
Message:

SL: update of the Venus GCM, + corrections on routines used for newstart/start2archive for Titan and Venus, + some modifications on tools

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dynlonlat_phylonlat/phyvenus/newstart.F

    r1403 r1442  
    2424      use exner_hyb_m, only: exner_hyb
    2525      use exner_milieu_m, only: exner_milieu
     26      USE comconst_mod
     27      USE comvert_mod, ONLY: ap,bp,presnivs,pa,preff,nivsigs,nivsig,
     28     .                       aps,bps,scaleheight,pseudoalt,
     29     .                       disvert_type,pressure_exner
    2630
    2731      implicit none
     
    2933#include "dimensions.h"
    3034#include "paramet.h"
    31 #include "comconst.h"
    3235#include "comdissnew.h"
    33 #include "comvert.h"
    3436#include "comgeom2.h"
    3537#include "logic.h"
     
    140142      integer, dimension(4) :: start,counter
    141143      REAL phisinverse(iip1,jjp1)  ! geopotentiel au sol avant inversion
    142       logical topoflag,albedoflag,razvitu,razvitv
     144      logical topoflag,notopo,albedoflag,razvitu,razvitv,uini
     145      logical razTS,raztemp
     146      real, dimension(:), allocatable :: tvira,dzst,zkm
    143147      real    albedo
    144148     
     
    880884       topoflag = . FALSE .
    881885       CALL getin('topoflag',topoflag)
     886! notopo = T: we go back to flat surface
     887       notopo = .FALSE.
     888       CALL getin('notopo',notopo)
    882889
    883890        print*,zmeaold(2,1:10)
     
    906913     .            0.0,jjm,rlonu,rlatv,.true.)
    907914
     915       ELSE IF ( notopo ) THEN
     916          print*,'Flattening the topography'
     917          phis=0.
     918          zmea=0.
     919          zstd=0.
     920          zsig=0.
     921          zgam=0.
     922          zthe=0.
     923          zpic=0.
     924          zval=0.
    908925       ELSE
    909926          print*,'Using existing topography'
     
    950967
    951968c Temperature de surface
    952       call interp_horiz (tsurfold,tsurfS,imold,jmold,iim,jjm,1,
    953      &                   rlonuold,rlatvold,rlonu,rlatv)
    954       call gr_dyn_fi (1,iip1,jjp1,ngridmx,tsurfS,tsurf)
    955 c     write(44,*) 'tsurf', tsurf
     969! razTS need to be in the specific run.def for newstart
     970      razTS = . FALSE .
     971      CALL getin('razTS',razTS)
     972
     973      if (razTS) then
     974        tsurf(:) = 735.
     975      else 
     976       call interp_horiz (tsurfold,tsurfS,imold,jmold,iim,jjm,1,
     977     &                   rlonuold,rlatvold,rlonu,rlatv)
     978       call gr_dyn_fi (1,iip1,jjp1,ngridmx,tsurfS,tsurf)
     979c      write(44,*) 'tsurf', tsurf
     980      endif
    956981
    957982c Temperature du sous-sol
    958       call interp_horiz(tsoilold,tsoilS,
     983      if (razTS) then
     984        tsoil(:,:)=735.
     985      else 
     986       call interp_horiz(tsoilold,tsoilS,
    959987     &                  imold,jmold,iim,jjm,nsoilmx,
    960988     &                   rlonuold,rlatvold,rlonu,rlatv)
    961       call gr_dyn_fi (nsoilmx,iip1,jjp1,ngridmx,tsoilS,tsoil)
    962 c     write(45,*) 'tsoil',tsoil
     989       call gr_dyn_fi (nsoilmx,iip1,jjp1,ngridmx,tsoilS,tsoil)
     990c      write(45,*) 'tsoil',tsoil
     991      endif
    963992
    964993! CHANGING ALBEDO: may be done through run.def
     
    10501079      CALL pression(ip1jmp1, ap, bp, ps, p3d)
    10511080         if (disvert_type==1) then
    1052            CALL exner_hyb(  ip1jmp1, ps, p3d, pks, pk, pkf )
     1081           CALL exner_hyb(  ip1jmp1, ps, p3d,pks, pk, pkf )
    10531082         else ! we assume that we are in the disvert_type==2 case
    10541083           CALL exner_milieu( ip1jmp1, ps, p3d, pks, pk, pkf )
     
    10671096c     enddo
    10681097
     1098! raztemp need to be in the specific run.def for newstart
     1099      raztemp = . FALSE .
     1100      CALL getin('raztemp',raztemp)
     1101
     1102! Reinitialisation of temperature to VIRA profile lisse
     1103      if (raztemp) then
     1104
     1105        allocate(tvira(0:lmold),dzst(0:lmold),zkm(0:lmold))
     1106        print*,"Venus = temperature initiale imposee = VIRA lisse "
     1107        dzst(0) = 0.0
     1108        dzst(1) = -log(p3d(1,1,2)/preff)*r/g
     1109        do l=2,lmold
     1110           dzst(l)=-log(p3d(1,1,l+1)/p3d(1,1,l))*r/g
     1111        enddo
     1112        tvira(0) = 735.
     1113        zkm(0) = 0.0
     1114        do l=1,lmold
     1115          zkm(l) = zkm(l-1)+tvira(l-1)*dzst(l)/1000. ! approx avec T(l-1)
     1116          if(zkm(l).lt.60.) then
     1117            tvira(l)=735.-7.95*zkm(l)
     1118          else
     1119            tvira(l)=AMAX1(258.-3.*(zkm(l)-60.),168.)
     1120          endif
     1121          zkm(l) = zkm(l-1)+(tvira(l-1)+tvira(l))/2.*dzst(l)/1000.
     1122        enddo
     1123        do l=1,lmold
     1124         do j=1,jmold+1
     1125          do i=1,imold+1
     1126            told(i,j,l)=tvira(l)
     1127          enddo
     1128         enddo
     1129        enddo
     1130      endif  ! end raztemp
     1131
    10691132      write (*,*) 'told ', told (1,jmold+1,1)  ! INFO
    10701133      call interp_vert
     
    10871150      teta(iip1,:,:) =  teta(1,:,:)
    10881151
     1152! RESETING U TO uini: may be done through run.def
     1153       uini = .FALSE.
     1154       CALL getin('uini',uini)
    10891155! RESETING U TO 0: may be done through run.def
    10901156       razvitu = . FALSE .
     
    11101176      call scal_wind(us,vs,unat,vnat)
    11111177! Reseting u=0
    1112       if (razvitu) then
    1113            unat(:,:,:) = 0.
     1178      if ((razvitu).and..not.(uini)) then
     1179         unat(:,:,:) = 0.
     1180      endif
     1181! Reseting u=uini
     1182      if ((uini).and..not.(razvitu)) then
     1183         do j=1,jjp1
     1184           do l=1,llm
     1185             if (p3d(1,j,l).gt.3e3) then
     1186               unat(:,j,l) = -110./8.03*log(p3d(:,j,l)/9.2e6)
     1187             else
     1188               unat(:,j,l) = 110./6.62*(log(p3d(:,j,l)/9.2e6)+14.65)
     1189             endif
     1190             if (abs(rlatS(1,j)).gt.50.) then
     1191              unat(:,j,l)=unat(:,j,l)*(90.-abs(rlatS(:,j)))/40.
     1192             endif
     1193           enddo
     1194         enddo
     1195      endif
     1196! incompatible options
     1197      if ((uini).and.(razvitu)) then
     1198         print*,"You have to choose between razvitu and uini..."
     1199         stop
    11141200      endif
    11151201      write (*,*) 'unat ', unat (1,2,1)    ! INFO
     1202
    11161203      do l=1,llm
    11171204        do j = 1, jjp1
Note: See TracChangeset for help on using the changeset viewer.