Changeset 53 for trunk/libf/dyn3d


Ignore:
Timestamp:
Jan 31, 2011, 10:29:25 AM (14 years ago)
Author:
aslmd
Message:

modele principal: commit mineur:

M libf/dyn3d/leapfrog.F
M libf/dyn3d/comconst.h
M libf/dyn3d/iniacademic.F
M libf/dyn3d/conf_planete.F90
propagation des changements du commit 52 a la dynamique sequentielle

Location:
trunk/libf/dyn3d
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/libf/dyn3d/comconst.h

    r5 r53  
    1111     &                   ,dissip_factz,dissip_deltaz,dissip_zref        &
    1212     &                   ,tau_top_bound,                                &
    13      & daylen,year_day,molmass
     13     & daylen,year_day,molmass, ihf
    1414      COMMON/cpdetvenus/nu_venus,t0_venus
    1515
     
    3636
    3737      REAL nu_venus,t0_venus ! coeffs needed for Cp(T), Venus atmosphere
     38      REAL ihf  ! (W/m2) intrinsic heat flux for giant planets
    3839
    3940
  • trunk/libf/dyn3d/conf_planete.F90

    r1 r53  
    6464CALL getin('omeg',omeg)
    6565
     66! Intrinsic heat flux [default is none]
     67! Aymeric -- for giant planets
     68! [matters only if planet_type="giant"]
     69ihf = 0.
     70CALL getin('ihf',ihf)
     71
     72
     73
    6674END SUBROUTINE conf_planete
  • trunk/libf/dyn3d/iniacademic.F

    r7 r53  
    9696! --------------------------------------
    9797c
     98
     99        print *, 'This is iniacademic'
     100
    98101        ! initialize planet radius, rotation rate,...
    99102        call conf_planete
     
    155158          teta0=315.     ! mean Teta (S.H. 315K)
    156159          CALL getin('teta0',teta0)
     160          print *, 'iniacademic - teta0 ', teta0
     161          print *, 'iniacademic - rad ', rad
    157162          ttp=200.       ! Tropopause temperature (S.H. 200K)
    158163          CALL getin('ttp',ttp)
     
    200205             tetajl(j,l)=teta0-delt_y*ddsin*ddsin+eps*ddsin
    201206     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
     207             !! Aymeric -- tests particuliers
     208             if (planet_type=="giant") then
     209             tetajl(j,l)=teta0+(delt_y*
     210     &          ((sin(rlatu(j)*3.14159*eps+0.0001))**2)
     211     &          / ((rlatu(j)*3.14159*eps+0.0001)**2))
     212     &          -delt_z*log(zsig)
     213!!!             ddsin=sin(2.5*3.14159*rlatu(j))
     214!!!             tetajl(j,l)=teta0-delt_y*ddsin*ddsin
     215!!!!     &           -delt_z*(1.-ddsin*ddsin)*log(zsig)
     216             endif
    202217             ! Profil stratospherique isotherme (+vortex)
    203218             w_pv=(1.-tanh((rlatu(j)-phi_pv)/dphi_pv))/2.
     
    217232            enddo
    218233          enddo
     234          PRINT *, 'iniacademic - check',tetajl(:,int(llm/2)),rlatu(:)
    219235
    220236
  • trunk/libf/dyn3d/leapfrog.F

    r37 r53  
    472472        ENDDO ! of DO l=1,llm
    473473          call friction(ucov,vcov,dtvr)
    474        
     474   
     475       if (planet_type.eq."giant") then
     476          ! Intrinsic heat flux
     477          ! Aymeric -- for giant planets
     478          if (ihf .gt. 1.e-6) then
     479          !print *, '**** INTRINSIC HEAT FLUX ****', ihf
     480            DO ij=1,ip1jmp1
     481              teta(ij,1) = teta(ij,1)
     482     &        + dtvr * aire(ij) * ihf / cpp / masse(ij,1)
     483            ENDDO
     484          !print *, '**** d teta '
     485          !print *, dtvr * aire(ijb:ije) * ihf / cpp / masse(ijb:ije,1)
     486          endif
     487       endif
     488
     489   
    475490        ! Sponge layer (if any)
    476491        IF (ok_strato) THEN
Note: See TracChangeset for help on using the changeset viewer.