Ignore:
Timestamp:
Apr 16, 2010, 11:50:10 AM (14 years ago)
Author:
Ehouarn Millour
Message:

Added possibility to run in "Shallow Water" mode. SW mode is automatically set if the number of atmospheric layers is 1.
To use SW mode, the model should be compiled without physics (makelmdz_fcm -p nophys) and/or without calls to the physics (i.e. set iflag_phys=0 in gcm.def).

-Updated some definitions and comments in run.def & gcm.def

-Fixed misplaced #ifdef CPP_EARTH in calfis.F + some write(lunout,*)

-Specific initialisation of fields for SW are done in sw_case_williamson91_6 (called by iniacademic, when read_start=.false.)

  • Checked (on Vargas & Brodie) that these changes don't alter usual bench GCM outputs.

EM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/branches/LMDZ4V5.0-dev/libf/dyn3dpar/iniacademic.F

    r1299 r1363  
    88      USE filtreg_mod
    99      USE infotrac, ONLY : nqtot
     10      USE control_mod
     11 
    1012
    1113c%W%    %G%
     
    3133c
    3234c=======================================================================
    33       USE control_mod
    3435      IMPLICIT NONE
    3536c-----------------------------------------------------------------------
     
    4647#include "temps.h"
    4748#include "iniprint.h"
     49#include "logic.h"
    4850
    4951c   Arguments:
     
    5557      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
    5658      REAL teta(ip1jmp1,llm)                 ! temperature potentielle
    57       REAL q(ip1jmp1,llm,nqtot)              ! champs advectes
     59      REAL q(ip1jmp1,llm,nqtot)               ! champs advectes
    5860      REAL ps(ip1jmp1)                       ! pression  au sol
    5961      REAL masse(ip1jmp1,llm)                ! masse d'air
     
    8486        time_0=0.
    8587        day_ref=0
    86         annee_ref=0
     88        annee_ref=0
    8789
    8890        im         = iim
     
    105107        ang0       = 0.
    106108
     109        if (llm.eq.1) then
     110          ! specific initializations for the shallow water case
     111          kappa=1
     112        endif
     113       
    107114        CALL iniconst
    108115        CALL inigeom
    109116        CALL inifilr
    110117
    111         ps=0.
    112         phis=0.
     118        if (llm.eq.1) then
     119          ! initialize fields for the shallow water case, if required
     120          if (.not.read_start) then
     121            phis(:)=0.
     122            q(:,:,1)=1.e-10
     123            q(:,:,2)=1.e-15
     124            q(:,:,3:nqtot)=0.
     125            CALL sw_case_williamson91_6(vcov,ucov,teta,masse,ps)
     126          endif
     127        endif
     128
     129        if (iflag_phys.eq.2) then
     130          ! initializations for the academic case
     131          ps(:)=1.e5
     132          phis(:)=0.
    113133c---------------------------------------------------------------------
    114134
    115         taurappel=10.*daysec
     135          taurappel=10.*daysec
    116136
    117137c---------------------------------------------------------------------
     
    119139c   --------------------------------------
    120140
    121         DO l=1,llm
    122          zsig=ap(l)/preff+bp(l)
    123          if (zsig.gt.0.3) then
    124            lsup=l
    125            tetarappell=1./8.*(-log(zsig)-.5)
    126            DO j=1,jjp1
     141          DO l=1,llm
     142            zsig=ap(l)/preff+bp(l)
     143            if (zsig.gt.0.3) then
     144             lsup=l
     145             tetarappell=1./8.*(-log(zsig)-.5)
     146             DO j=1,jjp1
    127147             ddsin=sin(rlatu(j))-sin(pi/20.)
    128148             tetajl(j,l)=300.*(1+1./18.*(1.-3.*ddsin*ddsin)+tetarappell)
    129            ENDDO
    130           else
     149             ENDDO
     150            else
    131151c   Choix isotherme au-dessus de 300 mbar
    132            do j=1,jjp1
    133              tetajl(j,l)=tetajl(j,lsup)*(0.3/zsig)**kappa
    134            enddo
    135           endif ! of if (zsig.gt.0.3)
    136         ENDDO ! of DO l=1,llm
    137 
    138         do l=1,llm
    139            do j=1,jjp1
     152             do j=1,jjp1
     153               tetajl(j,l)=tetajl(j,lsup)*(0.3/zsig)**kappa
     154             enddo
     155            endif ! of if (zsig.gt.0.3)
     156          ENDDO ! of DO l=1,llm
     157
     158          do l=1,llm
     159            do j=1,jjp1
    140160              do i=1,iip1
    141161                 ij=(j-1)*iip1+i
    142162                 tetarappel(ij,l)=tetajl(j,l)
    143163              enddo
    144            enddo
    145         enddo
     164            enddo
     165          enddo
    146166
    147167c       call dump2d(jjp1,llm,tetajl,'TEQ   ')
    148168
    149         ps=1.e5
    150         phis=0.
    151         CALL pression ( ip1jmp1, ap, bp, ps, p       )
    152         CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
    153         CALL massdair(p,masse)
     169          CALL pression ( ip1jmp1, ap, bp, ps, p       )
     170          CALL exner_hyb( ip1jmp1, ps, p,alpha,beta, pks, pk, pkf )
     171          CALL massdair(p,masse)
    154172
    155173c  intialisation du vent et de la temperature
    156         teta(:,:)=tetarappel(:,:)
    157         CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
    158         call ugeostr(phi,ucov)
    159         vcov=0.
    160         q(:,:,1   )=1.e-10
    161         q(:,:,2   )=1.e-15
    162         q(:,:,3:nqtot)=0.
     174          teta(:,:)=tetarappel(:,:)
     175          CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     176          call ugeostr(phi,ucov)
     177          vcov=0.
     178          q(:,:,1   )=1.e-10
     179          q(:,:,2   )=1.e-15
     180          q(:,:,3:nqtot)=0.
    163181
    164182
    165183c   perturbation aleatoire sur la temperature
    166         idum  = -1
    167         zz = ran1(idum)
    168         idum  = 0
    169         do l=1,llm
    170            do ij=iip2,ip1jm
     184          idum  = -1
     185          zz = ran1(idum)
     186          idum  = 0
     187          do l=1,llm
     188            do ij=iip2,ip1jm
    171189              teta(ij,l)=teta(ij,l)*(1.+0.005*ran1(idum))
    172            enddo
    173         enddo
    174 
    175         do l=1,llm
    176            do ij=1,ip1jmp1,iip1
     190            enddo
     191          enddo
     192
     193          do l=1,llm
     194            do ij=1,ip1jmp1,iip1
    177195              teta(ij+iim,l)=teta(ij,l)
    178            enddo
    179         enddo
     196            enddo
     197          enddo
    180198
    181199
     
    187205
    188206c   initialisation d'un traceur sur une colonne
    189         j=jjp1*3/4
    190         i=iip1/2
    191         ij=(j-1)*iip1+i
    192         q(ij,:,3)=1.
    193      
     207          j=jjp1*3/4
     208          i=iip1/2
     209          ij=(j-1)*iip1+i
     210          q(ij,:,3)=1.
     211        endif ! of if (iflag_phys.eq.2)
     212       
    194213      else
    195214        write(lunout,*)"iniacademic: planet types other than earth",
Note: See TracChangeset for help on using the changeset viewer.