Changeset 2098


Ignore:
Timestamp:
Jul 22, 2014, 12:51:23 PM (10 years ago)
Author:
lguez
Message:

Replaced 360 in calbeta_clim by length of current year according to
chosen calendar. Length of current year is given by
ioget_year_len. Since we already need this for ozone, moved the call
to ioget_year_len from physiq to phys_cal_mod and created variable
year_len of module phys_cal_mod.

Control the output from minmaxqfi.

Non-ASCII characters in comments are not always rendered properly and
they risk being lost. See revision 1740.

Location:
LMDZ5/trunk
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/phylmd/calbeta_clim.F90

    r1907 r2098  
    55
    66SUBROUTINE calbeta_clim(klon,time,lat_radian,beta)
    7  
    8 !======================================================================
    9 ! Auteur(s): A.K. TRAORE
    10 !======================================================================
    11 !USE phys_local_var_mod, ONLY : ideal_beta !pour faire la variable dans le
    12 ! physiq.f pour des sorties directes de beta
    13 !==============================================
    147
    15 implicit none
    16 integer klon,nt,j,it
    17 real logbeta(klon),pi
    18 real lat(klon),lat_radian(klon)
    19 integer time
    20 real time_radian
    21 real lat_sahel,beta(klon)
    22 real lat_nord,lat_sud
    23 !==============================================
     8  !======================================================================
     9  ! Auteur(s): A.K. TRAORE
     10  !======================================================================
    2411
    25 pi=2.*asin(1.)
    26 beta=0.
    27    
    28             !calcul des cordonnees
     12  !USE phys_local_var_mod, ONLY : ideal_beta !pour faire la variable dans le
     13  ! physiq.f pour des sorties directes de beta
    2914
    30 !  print*,'LATITUDES BETA ',lat_radian
    31    time_radian=(time+15.)*2.*pi/360.
     15  USE phys_cal_mod, only: year_len
    3216
    33    print*,'BETA time_radian',time_radian,time
     17  implicit none
     18  integer klon,nt,j,it
     19  real logbeta(klon),pi
     20  real lat(klon),lat_radian(klon)
     21  integer time
     22  real time_radian
     23  real lat_sahel,beta(klon)
     24  real lat_nord,lat_sud
     25  !==============================================
    3426
    35    lat(:)=180.*lat_radian(:)/pi !lat(:)=lat_radian(:)
    36        
    37    lat_sahel=-5*sin(time_radian)+13
    38    lat_nord=lat_sahel+25.
    39    lat_sud=lat_sahel-25.
    40 do j=1,klon
    41     !===========
    42         if (lat(j) < 5. ) then
    43                
    44                 logbeta(j)=0.2*(lat(j)-lat_sud)-1.6
    45                 beta(j)=10**(logbeta(j))
    46                 beta(j)=max(beta(j),0.03)
    47                 beta(j)=min(beta(j),0.22)
    48 !              print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
    49     !===========
    50         elseif (lat(j) < 22.) then !lat(j)<22.
    51                
    52                 logbeta(j)=-0.25*(lat(j)-lat_sahel)-1.6
    53                 beta(j)=10**(logbeta(j))
    54                 beta(j)=max(beta(j),1.e-2)
    55                 beta(j)=min(beta(j),0.22)
    56 !              print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
    57     !===========
    58         else
    59               logbeta(j)=0.25*(lat(j)-lat_nord)-1.
    60               beta(j)=10**(logbeta(j))
    61               beta(j)=max(beta(j),1.e-2)
    62               beta(j)=min(beta(j),0.25)
    63 !              print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
    64         endif
    65     !===========
    66 enddo
    67 end
     27  pi=2.*asin(1.)
     28  beta=0.
     29
     30  !calcul des cordonnees
     31
     32  ! print*,'LATITUDES BETA ',lat_radian
     33  time_radian=(time+15.)*2.*pi / year_len
     34
     35  print*,'BETA time_radian',time_radian,time
     36
     37  lat(:)=180.*lat_radian(:)/pi !lat(:)=lat_radian(:)
     38
     39  lat_sahel=-5*sin(time_radian)+13
     40  lat_nord=lat_sahel+25.
     41  lat_sud=lat_sahel-25.
     42  do j=1,klon
     43     !===========
     44     if (lat(j) < 5. ) then
     45
     46        logbeta(j)=0.2*(lat(j)-lat_sud)-1.6
     47        beta(j)=10**(logbeta(j))
     48        beta(j)=max(beta(j),0.03)
     49        beta(j)=min(beta(j),0.22)
     50        ! print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
     51        !===========
     52     elseif (lat(j) < 22.) then !lat(j)<22.
     53
     54        logbeta(j)=-0.25*(lat(j)-lat_sahel)-1.6
     55        beta(j)=10**(logbeta(j))
     56        beta(j)=max(beta(j),1.e-2)
     57        beta(j)=min(beta(j),0.22)
     58        ! print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
     59        !===========
     60     else
     61        logbeta(j)=0.25*(lat(j)-lat_nord)-1.
     62        beta(j)=10**(logbeta(j))
     63        beta(j)=max(beta(j),1.e-2)
     64        beta(j)=min(beta(j),0.25)
     65        ! print*,'j,lat,lat_radian,beta',j,lat(j),lat_radian(j),beta(j)
     66     endif
     67     !===========
     68  enddo
     69
     70end SUBROUTINE calbeta_clim
  • LMDZ5/trunk/libf/phylmd/minmaxqfi.F90

    r1907 r2098  
    1414  INTEGER,DIMENSION(klon)     :: jadrs
    1515  INTEGER                     :: i, jbad, k
     16
     17  include "iniprint.h"
    1618 
    1719  DO k = 1, klev
     
    2426     ENDDO
    2527     IF (jbad.GT.0) THEN
    26         WRITE(*,*)comment
    27         DO i = 1, jbad
    28            WRITE(*,*) "i,k,q=", jadrs(i),k,zq(jadrs(i),k)
    29         ENDDO
     28        WRITE(*,*)comment, "k = ", k, "jbad > 0"
     29        if (prt_level >= 1) then
     30           DO i = 1, jbad
     31              WRITE(*,*) "i,q=", jadrs(i), zq(jadrs(i),k)
     32           ENDDO
     33        end if
    3034     ENDIF
    3135  ENDDO
  • LMDZ5/trunk/libf/phylmd/phys_cal_mod.F90

    r1907 r2098  
    1010  INTEGER :: days_elapsed  ! number of whole days since start of the simulation
    1111  INTEGER :: mth_len       ! number of days in the current month
     12  INTEGER year_len ! number of days in the current year
    1213  REAL    :: hour
    1314  REAL    :: jD_1jan
     
    2122    ! This subroutine updates the module saved variables.
    2223
    23     USE IOIPSL
     24    USE IOIPSL, only: ju2ymds, ymds2ju, ioget_mon_len, ioget_year_len
    2425   
    2526    REAL, INTENT(IN) :: jD_cur ! jour courant a l'appel de la physique (jour julien)
     
    3738    mth_len = ioget_mon_len(year_cur,mth_cur)
    3839
     40    year_len = ioget_year_len(year_cur)
     41
    3942  END SUBROUTINE phys_cal_update
    4043
  • LMDZ5/trunk/libf/phylmd/physiq.F90

    r2090 r2098  
    1111
    1212  USE ioipsl, only: histbeg, histvert, histdef, histend, histsync, &
    13        histwrite, ju2ymds, ymds2ju, ioget_year_len, getin
     13       histwrite, ju2ymds, ymds2ju, getin
    1414  USE comgeomphy
    15   USE phys_cal_mod
     15  USE phys_cal_mod, only: year_len, mth_len, days_elapsed, jh_1jan, year_cur, &
     16       mth_cur, phys_cal_update
    1617  USE write_field_phy
    1718  USE dimphy
     
    15761577     ! Ozone from a file
    15771578     ! Update required ozone index:
    1578      ro3i = int((days_elapsed + jh_cur - jh_1jan) / ioget_year_len(year_cur) &
    1579           * 360.) + 1
     1579     ro3i = int((days_elapsed + jh_cur - jh_1jan) / year_len * 360.) + 1
    15801580     if (ro3i == 361) ro3i = 360
    15811581     ! (This should never occur, except perhaps because of roundup
  • LMDZ5/trunk/makelmdz

    r2097 r2098  
    192192
    193193###############################################################
    194 # lecture des chemins propres à l'architecture de la machine #
     194# lecture des chemins propres \`a l'architecture de la machine #
    195195###############################################################
    196196rm -f .void_file
  • LMDZ5/trunk/makelmdz_fcm

    r2097 r2098  
    33# This is a script in Bash.
    44
    5 # FH : on ne crée plus le fichier arch.mk qui est supposé exister par
     5# FH : on ne cr\'ee plus le fichier arch.mk qui est suppos\'e exister par
    66# FH : ailleurs.
    7 # FH : ulterieurement, ce fichier sera pré-existant pour une série
    8 # FH : de configurations en versions optimisées et debug qui seront
    9 # FH : liés (ln -s) avec arch.mk en fonction de l'architecture.
    10 # FH : Pour le moment, cette version est en test et on peut créer les
    11 # FH : arch.mk en lançant une première fois makegcm.
     7# FH : ulterieurement, ce fichier sera pr\'e-existant pour une s\'erie
     8# FH : de configurations en versions optimis\'ees et debug qui seront
     9# FH : li\'es (ln -s) avec arch.mk en fonction de l'architecture.
     10# FH : Pour le moment, cette version est en test et on peut cr\'eer les
     11# FH : arch.mk en lan\c{}cant une premi\`ere fois makegcm.
    1212#
    1313##set -x
     
    192192
    193193###############################################################
    194 # lecture des chemins propres à l'architecture de la machine #
     194# lecture des chemins propres \`a l'architecture de la machine #
    195195###############################################################
    196196rm -f .void_file
  • LMDZ5/trunk/tools/diffdef.sh

    r2082 r2098  
    22# Author: Lionel GUEZ
    33
    4 # This script compares files "!(traceur).def" in two directories. The
    5 # script uses GNU versions of the utilities cut, sort and uniq.
     4# This script compares files "*.def" other than "traceur.def" in two
     5# directories. The script uses GNU versions of the utilities cut, sort
     6# and uniq.
    67
    78# See guide:
Note: See TracChangeset for help on using the changeset viewer.