Ignore:
Timestamp:
Jan 7, 2020, 2:55:41 PM (5 years ago)
Author:
dubos
Message:

simple_physics : cleanup phyparam (TBC)

Location:
dynamico_lmdz/simple_physics/phyparam/param
Files:
1 deleted
1 edited

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/phyparam/param/phyparam.F90

    r4212 r4213  
    11MODULE phyparam_mod
    22  IMPLICIT NONE
    3    
     3  PRIVATE
     4  SAVE
     5
     6  REAL, PARAMETER :: solarcst=1370., stephan=5.67e-08
     7   
     8  REAL, ALLOCATABLE :: tsurf(:),tsoil(:,:),rnatur(:), &
     9       capcal(:),fluxgrd(:), &
     10       dtrad(:,:),fluxrad(:), &
     11       q2(:,:),q2l(:,:), &
     12       albedo(:),emissiv(:),z0(:),inertie(:)
     13  !$OMP THREADPRIVATE( tsurf,tsoil,rnatur)
     14  !$OMP THREADPRIVATE( capcal,fluxgrd,dtrad,fluxrad)
     15  !$OMP THREADPRIVATE( q2,q2l)
     16  !$OMP THREADPRIVATE( albedo,emissiv,z0,inertie)         
     17
     18  INTEGER :: icount
     19  REAL    :: zday_last
     20  !$OMP THREADPRIVATE( icount,zday_last)
     21
     22  PUBLIC :: phyparam
     23
    424CONTAINS
    525 
     
    2545    USE radiative_lw, ONLY : lw
    2646    USE surface
    27     !     
     47
    2848    !=======================================================================
    29     !
    30     !   subject:
    31     !   --------
    32     !
    3349    !   Organisation of the physical parametrisations of the LMD
    3450    !   20 parameters GCM for planetary atmospheres.
     
    3955    !
    4056    !   author: Frederic Hourdin 15 / 10 /93
    41     !   -------
    42     !
    43     !   arguments:
    44     !   ----------
    45     !
    46     !   input:
    47     !   ------
    48     !
    49     !    ngrid                 Size of the horizontal grid.
    50     !                          All internal loops are performed on that grid.
    51     !    nlayer                Number of vertical layers.
    52     !    nq                    Number of advected fields
    53     !    firstcall             True at the first call
    54     !    lastcall              True at the last call
    55     !    rjourvrai                  Number of days counted from the North. Spring
    56     !                          equinoxe.
    57     !    gmtime                 hour (s)
    58     !    ptimestep             timestep (s)
    59     !    pplay(ngrid,nlayer+1) Pressure at the middle of the layers (Pa)
    60     !    pplev(ngrid,nlayer+1) intermediate pressure levels (pa)
    61     !    pphi(ngrid,nlayer)    Geopotential at the middle of the layers (m2s-2)
    62     !    pu(ngrid,nlayer)      u component of the wind (ms-1)
    63     !    pv(ngrid,nlayer)      v component of the wind (ms-1)
    64     !    pt(ngrid,nlayer)      Temperature (K)
    65     !    pq(ngrid,nlayer,nq)   Advected fields
    66     !    pudyn(ngrid,nlayer)    \
    67     !    pvdyn(ngrid,nlayer)     \ Dynamical temporal derivative for the
    68     !    ptdyn(ngrid,nlayer)     / corresponding variables
    69     !    pqdyn(ngrid,nlayer,nq) /
    70     !    pw(ngrid,?)           vertical velocity
    71     !
    72     !   output:
    73     !   -------
    74     !
    75     !    pdu(ngrid,nlayermx)        \
    76     !    pdv(ngrid,nlayermx)         \  Temporal derivative of the corresponding
    77     !    pdt(ngrid,nlayermx)         /  variables due to physical processes.
    78     !    pdq(ngrid,nlayermx)      /
    79     !    pdpsrf(ngrid)        /
    80     !
    8157    !=======================================================================
    82     !
    83     !-----------------------------------------------------------------------
    84     !
    85     !    0.  Declarations :
    86     !    ------------------
    87 
    88 #include "dimensions.h"
    89    
    90     !    Arguments :
    91     !    -----------
    92    
    93     !    inputs:
    94     !    -------
    95     INTEGER ngrid,nlayer,nq
    96    
    97     REAL ptimestep
    98     real zdtime
    99     REAL pplev(ngrid,nlayer+1),pplay(ngrid,nlayer)
    100     REAL pphi(ngrid,nlayer)
    101     REAL pphis(ngrid)
    102     REAL pu(ngrid,nlayer),pv(ngrid,nlayer)
    103     REAL pt(ngrid,nlayer),pq(ngrid,nlayer,nq)
    104     REAL pdu(ngrid,nlayer),pdv(ngrid,nlayer)
    105    
    106     !   dynamial tendencies
    107     REAL pdtdyn(ngrid,nlayer),pdqdyn(ngrid,nlayer,nq)
    108     REAL pdudyn(ngrid,nlayer),pdvdyn(ngrid,nlayer)
    109     REAL pw(ngrid,nlayer)
    110    
    111     !   Time
    112     real rjourvrai
    113     REAL gmtime
    114    
    115     !     outputs:
    116     !     --------
    117    
    118     !   physical tendencies
    119     REAL pdt(ngrid,nlayer),pdq(ngrid,nlayer,nq)
    120     REAL pdpsrf(ngrid)
    121     LOGICAL firstcall,lastcall
     58
     59    INTEGER, INTENT(IN) ::      &
     60         ngrid,                 & ! Size of the horizontal grid.
     61         nlayer,                & ! Number of vertical layers.
     62         nq                       ! Number of advected fields (tracers)
     63    LOGICAL, INTENT(IN) ::      &
     64         firstcall,             & ! True at the first call
     65         lastcall                 ! True at the last call
     66    REAL, INTENT(IN)    ::      &
     67         rjourvrai,             & ! Number of days counted from the North. Spring equinox
     68         gmtime,                & ! time of the day in seconds
     69         ptimestep,             & ! timestep (s)
     70         pplev(ngrid,nlayer+1), & ! Pressure at interfaces between layers (pa)
     71         pplay(ngrid,nlayer),   & ! Pressure at the middle of the layers (Pa)
     72         pphi(ngrid,nlayer),    & ! Geopotential at the middle of the layers (m2s-2)
     73         pphis(ngrid),          & ! surface geopotential (unused)
     74         pu(ngrid,nlayer),      & ! u component of the wind (ms-1)
     75         pv(ngrid,nlayer),      & ! v component of the wind (ms-1)
     76         pw(ngrid,nlayer),      & ! vertical velocity (unused)
     77         pt(ngrid,nlayer),      & ! Temperature (K)
     78         pq(ngrid,nlayer,nq)      ! Advected fields (unused)
     79    REAL, INTENT(OUT)   ::      & ! output : physical tendencies
     80         pdu(ngrid,nlayer),     &
     81         pdv(ngrid,nlayer),     &
     82         pdt(ngrid,nlayer),     &
     83         pdq(ngrid,nlayer,nq),  &
     84         pdpsrf(ngrid)
    12285   
    12386    !    Local variables :
    124     !    -----------------
    125    
    126     INTEGER j,l,ig,ierr,aslun,nlevel,igout,it1,it2,isoil,iq
     87    REAL, DIMENSION(ngrid) :: mu0,fract
     88    INTEGER :: j,l,ig,ierr,aslun,nlevel,igout,it1,it2,isoil,iq
    12789    INTEGER*4 day_ini
    12890    !
    129     REAL,DIMENSION(ngrid) :: mu0,fract
    130     REAL zday
     91    REAL :: zday, zdtime
    13192    REAL zh(ngrid,nlayer),z1,z2
    13293    REAL zzlev(ngrid,nlayer+1),zzlay(ngrid,nlayer)
     
    142103    REAL zdtlw(ngrid,nlayer),zdtsw(ngrid,nlayer)
    143104    REAL zfluxsw(ngrid),zfluxlw(ngrid)
    144     character*2 str2
    145105    REAL factq(nq),tauq(nq)
    146106    character*3 nomq
     
    149109    !   ----------------------
    150110   
    151     INTEGER, SAVE :: icount
    152     real, SAVE :: zday_last
    153     !$OMP THREADPRIVATE( icount,zday_last)
    154    
    155111    REAL zps_av
    156    
    157     real,allocatable,SAVE :: tsurf(:),tsoil(:,:),rnatur(:)
    158     real,allocatable,SAVE :: capcal(:),fluxgrd(:)
    159     real,allocatable,SAVE :: dtrad(:,:),fluxrad(:)
    160     real,allocatable,SAVE ::  q2(:,:),q2l(:,:)
    161     real,allocatable,SAVE ::  albedo(:),emissiv(:),z0(:),inertie(:)
    162     real,SAVE :: solarcst=1370.
    163     real,SAVE :: stephan=5.67e-08
    164    
    165     !$OMP THREADPRIVATE(tsurf,tsoil,rnatur)
    166     !$OMP THREADPRIVATE( capcal,fluxgrd,dtrad,fluxrad)
    167     !$OMP THREADPRIVATE( q2,q2l)
    168     !$OMP THREADPRIVATE( albedo,emissiv,solarcst,z0,inertie)
    169     !$OMP THREADPRIVATE( stephan)
    170    
    171    
    172     EXTERNAL ismin,ismax
    173    
    174112   
    175113    INTEGER        longcles
     
    179117       
    180118    print*,'OK DANS PHYPARAM'
    181    
    182     !-----------------------------------------------------------------------
    183     !    1. Initialisations :
    184     !    --------------------
    185    
    186     !     call initial0(ngrid*nlayermx*nqmx,pdq)
    187     nlevel=nlayer+1
    188    
    189     !     print*,'OK ',nlevel
    190    
    191     igout=ngrid/2+1
    192     !     print*,'OK PHYPARAM ',ngrid,igout
    193    
    194    
    195     zday=rjourvrai+gmtime
    196    
    197     !     print*,'OK PHYPARAM 0A nq ',nq
    198     tauq(1)=1800.
    199     tauq(2)=10800.
    200     tauq(3)=86400.
    201     tauq(4)=864000.
    202     !     print*,'OK PHYPARAM 0 B nq ',nq
    203     factq(1:4)=(1.-exp(-ptimestep/tauq(1:4)))/ptimestep
    204    
    205     !     print*,'OK PHYPARAM 0 '
    206119    print*,'nq ',nq
    207120    print*,'latitude0',ngrid,lati(1:2),lati(ngrid-1:ngrid)
     
    209122    print*,'size pdq ',ngrid*nlayer*4,ngrid*nlayer*nq, &
    210123         &      size(pdq),size(lati),size(pq),size(factq)
    211     do iq=1,4
    212        do l=1,nlayer
    213           pdq(1:ngrid,l,iq)= &
    214                &      (1.+sin(lati(1:ngrid))-pq(1:ngrid,l,iq))*factq(iq)
    215        enddo
    216     enddo
     124   
     125    nlevel=nlayer+1
     126    igout=ngrid/2+1   
     127    zday=rjourvrai+gmtime
     128
     129    pdq(:,:,:) = 0. ! we do not use tracers in this physics package
     130
     131    !-----------------------------------------------------------------------
     132    !    1. Initialisations :
     133    !    --------------------
    217134   
    218135    IF(firstcall) THEN
     
    235152       
    236153       
    237        do l=1,nlayer
    238           pdq(:,l,5)=1.+sin(lati(:))/ptimestep
    239        enddo
    240154       PRINT*,'FIRSTCALL  '
    241155       
    242156       !         zday_last=rjourvrai
    243157       zday_last=zday-ptimestep/unjours
    244        !        CALL readfi(ngrid,nlayer,nsoilmx,ldrs,
    245        !    .      day_ini,gmtime,albedo,inertie,emissiv,z0,rnatur,
    246        !    .      q2,q2l,tsurf,tsoil)
    247158       rnatur=1.
    248159       emissiv(:)=(1.-rnatur(:))*emi_mer+rnatur(:)*emi_ter
     
    362273             ztim2=COS(declin)*COS(2.*pi*(zday-.5))
    363274             ztim3=-COS(declin)*SIN(2.*pi*(zday-.5))
    364              !           call dump2d(iim,jjm-1,lati(2),'LATI  0   ')
    365              !           call dump2d(iim,jjm-1,long(2),'LONG  0   ')
    366              !           call dump2d(iim,jjm-1,sinlon(2),'sinlon0   ')
    367              !           call dump2d(iim,jjm-1,coslon(2),'coslon0   ')
    368              !           call dump2d(iim,jjm-1,sinlat(2),'sinlat   ')
    369              !           call dump2d(iim,jjm-1,coslat(2),'coslat   ')
    370275             CALL solang(ngrid,sinlon,coslon,sinlat,coslat, &
    371276             &         ztim1,ztim2,ztim3,                   &
     
    385290       ELSE
    386291          print*,'declin,ngrid,rad',declin,ngrid,rad
    387          
    388           !           call dump2d(iim,jjm-1,lati(2),'LATI      ')
    389292          CALL mucorr(ngrid,declin,lati,mu0,fract,10000.,rad)
    390293       ENDIF
    391        !           call dump2d(iim,jjm-1,fract(2),'FRACT A   ')
    392        !           call dump2d(iim,jjm-1,mu0(2),'MU0 A     ')
    393        
    394294       
    395295       !    2.2 Calcul of the radiative tendencies and fluxes:
     
    399299       
    400300       zinsol=solarcst/(dist_sol*dist_sol)
    401        print*,iim,jjm,llm,ngrid,nlayer,ngridmax,nlayer
    402        print*,'iim,jjm,llm,ngrid,nlayer,ngridmax,nlayer'
    403        !           call dump2d(iim,jjm-1,albedo(2),'ALBEDO    ')
    404        !           call dump2d(iim,jjm-1,mu0(2),'MU0       ')
    405        !           call dump2d(iim,jjm-1,fract(2),'FRACT     ')
    406        !           call dump2d(iim,jjm-1,lati(2),'LATI      ')
    407301       zps_av=1.e5
    408302       if (firstcall) then
     
    414308       &              zfluxsw,zdtsw,                &
    415309       &              lverbose)
    416        !           call dump2d(iim,jjm-1,zfluxsw(2),'SWS 1     ')
    417        !           stop
    418310       
    419311       CALL lw(ngrid,nlayer,coefir,emissiv, &
     
    579471    !   --------
    580472   
    581     !           call dump2d(iim,jjm-1,zfluxsw(2),'SWS 2     ')
    582473    print*,'zday, zday_last ',zday,zday_last,icount
    583474    if(abs(zday-zday_last-period_sort)<=ptimestep/unjours/10.) then
     
    590481       enddo
    591482       
    592        call iophys_ecrit('u',llm,'Vent zonal moy','m/s',pu)
    593        call iophys_ecrit('v',llm,'Vent meridien moy','m/s',pv)
    594        call iophys_ecrit('temp',llm,'Temperature','K',pt)
    595        call iophys_ecrit('geop',llm,'Geopotential','m2/s2',pphi)
    596        call iophys_ecrit('plev',llm,'plev','Pa',pplev(:,1:nlayer))
    597        
    598        call iophys_ecrit('du',llm,'du',' ',pdu)
    599        call iophys_ecrit('dv',llm,'du',' ',pdv)
    600        call iophys_ecrit('dt',llm,'du',' ',pdt)
    601        call iophys_ecrit('dtsw',llm,'dtsw',' ',zdtsw)
    602        call iophys_ecrit('dtlw',llm,'dtlw',' ',zdtlw)
     483       call iophys_ecrit('u',nlayer,'Vent zonal moy','m/s',pu)
     484       call iophys_ecrit('v',nlayer,'Vent meridien moy','m/s',pv)
     485       call iophys_ecrit('temp',nlayer,'Temperature','K',pt)
     486       call iophys_ecrit('geop',nlayer,'Geopotential','m2/s2',pphi)
     487       call iophys_ecrit('plev',nlayer,'plev','Pa',pplev(:,1:nlayer))
     488       
     489       call iophys_ecrit('du',nlayer,'du',' ',pdu)
     490       call iophys_ecrit('dv',nlayer,'du',' ',pdv)
     491       call iophys_ecrit('dt',nlayer,'du',' ',pdt)
     492       call iophys_ecrit('dtsw',nlayer,'dtsw',' ',zdtsw)
     493       call iophys_ecrit('dtlw',nlayer,'dtlw',' ',zdtlw)
    603494       
    604495       do iq=1,nq
    605496          nomq="tr."
    606497          write(nomq(2:3),'(i1.1)') iq
    607           call iophys_ecrit(nomq,llm,nomq,' ',pq(:,:,iq))
     498          call iophys_ecrit(nomq,nlayer,nomq,' ',pq(:,:,iq))
    608499       enddo
    609500       
     
    627518       call iotd_fin
    628519       PRINT*,'Ecriture du fichier de reinitialiastion de la physique'
    629        !        if (ierr.ne.0) then
    630        !          write(6,*)' Pb d''ouverture du fichier restart'
    631        !          write(6,*)' ierr = ', ierr
    632        !          call exit(1)
    633        !        endif
    634520       write(75)  tsurf,tsoil
    635        !    s             (tsurf(1),ig=1,iim+1),
    636        !    s             ( (tsurf(ig),ig=(j-2)*iim+2,(j-1)*iim+1),
    637        !    s              tsurf((j-2)*iim+2) ,j=2,jjm),
    638        !    s              (tsurf(ngridmax),ig=1,iim+1),
    639        !    s         (   (tsoil(1,l),ig=1,iim+1),
    640        !    s             ( (tsoil(ig,l),ig=(j-2)*iim+2,(j-1)*iim+1),
    641        !    s              tsoil((j-2)*iim+2,l) ,ig=2,jjm),
    642        !    s              (tsoil(ngridmax,l),ig=1,iim+1)
    643        !    s          ,l=1,nsoilmx)
    644521    ENDIF   
    645522   
    646523  END SUBROUTINE phyparam
    647524
     525
     526  SUBROUTINE alloc_phyparam
     527  END SUBROUTINE alloc_phyparam
    648528END MODULE phyparam_mod
Note: See TracChangeset for help on using the changeset viewer.