Changeset 4236 for dynamico_lmdz


Ignore:
Timestamp:
Jan 22, 2020, 9:46:46 PM (5 years ago)
Author:
dubos
Message:

simple_physics : some Python bindings

Location:
dynamico_lmdz/simple_physics
Files:
8 added
9 edited
3 moved

Legend:

Unmodified
Added
Removed
  • dynamico_lmdz/simple_physics/bash/compile_XCodeML.sh

    r4230 r4236  
    11#!/bin/bash
    22
     3
     4# Compiles the omni-compiler suite, especially the Fortran front-end F_Front
     5# which is used to parse the physics code and (later) check that coding standards are followed.
     6
     7# F_Front will be installed in the directory from which this script has been invoked.
     8# Before executing this script, cd to the directory where you want to install.
     9# e.g. > cd $HOME/local . Then F_Front will be in $HOME/local/bin .
     10
     11# There are chances this script fails on OSX if the standard gcc is used. You can try with a more recent gcc, which is easy to
     12# install through Homebrew. The XML library libxml2 will be required too :
     13#   * install gcc and libxml2 : > brew install gcc libxml2
     14#   * check : > which gfortran
     15#   * cd to simple_physics/bash/omnicompiler-1.3.2
     16#   * run the configure script with :
     17#          > CC=/usr/local/bin/gcc-9 ./configure --prefix=$HOME/local --with-libxml2=/usr/local/Cellar/libxml2/2.9.10/
     18#    (your version numbers may be different
     19#   * make all install
     20#   * even if the full build fails, you may find a working F_Front in xcodeml-tools/F-FrontEnd/src :
     21#          > xcodeml-tools/F-FrontEnd/src/F_Front --help
     22#   * copy F_Front where desired
     23 
    324PREFIX=$(pwd)
    425ROOT=$(dirname $0)
  • dynamico_lmdz/simple_physics/phyparam/Makefile

    r4235 r4236  
    1616all : obj $(OBJECTS) lib/libphyparam.so
    1717
     18py : clean all
     19        bash/extract_cython.sh
     20        cd python ; rm -rf build *.c ; python setup.py build_ext --inplace
     21        cd python ; python -c 'import phyparam as phys ; phys.setup(100.); phys.alloc(30,100) ; phys.coldstart(30, 100.)'
    1822obj :
    1923        @rm -rf obj include lib xml tmp *~ */*~
    2024        @mkdir obj include lib xml tmp
    2125
    22 clean :
     26clean : nice
    2327        @rm -rf obj include lib xml tmp *~ */*~
    2428        @mkdir obj include lib xml tmp
    25         @../bash/concatenate_all_code.sh $(NAMES) > tmp/all_code
    26         @../bash/makedeps.sh tmp/all_code >  Makefile.inc
     29        @bash/concatenate_all_code.sh $(NAMES) > tmp/all_code
     30        @bash/makedeps.sh tmp/all_code >  Makefile.inc
    2731
    2832nice:
    29         ../bash/beautify.sh physics/*.F90
     33        bash/beautify.sh physics/*.F90
    3034
    3135%.so : $(OBJECTS)
  • dynamico_lmdz/simple_physics/phyparam/dynphy_lonlat/iniphysiq_mod.F90

    r4223 r4236  
    8787    CALL setup_phyparam
    8888
    89     CALL iniphyparam(klon_omp,nlayer, &
    90          punjours, &
    91          pdayref,ptimestep, &
    92          prad,pg,pr,pcpp)
     89    CALL iniphyparam(ptimestep, punjours, prad, pg, pr, pcpp)
    9390   
    9491    !$OMP END PARALLEL
  • dynamico_lmdz/simple_physics/phyparam/physics/error_mod.F90

    r4235 r4236  
    1111  INTERFACE check_NaN
    1212     MODULE PROCEDURE check_NaN1, check_NaN2
    13   END INTERFACE check_NaN
     13  END INTERFACE
    1414
    1515  PUBLIC :: check_NaN
  • dynamico_lmdz/simple_physics/phyparam/physics/iniphyparam_mod.F90

    r4235 r4236  
    1010CONTAINS
    1111
    12   SUBROUTINE iniphyparam(ngrid,nlayer, &
    13        &           punjours,              &
    14        &           pdayref,ptimestep,     &
    15        &           prad,pg,pr,pcpp)
    16     USE callkeys
     12  SUBROUTINE read_params(ptimestep) BIND(C, name='phyparam_setup')
     13    !$cython header void phyparam_setup(double);
     14    !$cython wrapper def setup(timestep) : phy.phyparam_setup(timestep)
     15    USE read_param_mod
    1716    USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours,mugaz
     17    USE astronomy
    1818    USE planet, ONLY : coefir, coefvis
    19     USE astronomy
    2019    USE turbulence, ONLY : lmixmin, emin_turb
    2120    USE surface
    22     USE read_param_mod
     21    USE callkeys
     22    REAL, INTENT(IN), VALUE :: ptimestep
    2323
    24     INTEGER, INTENT(IN) :: &
    25          ngrid, &       ! Size of the horizontal grid
    26          nlayer, &      ! Number of vertical layers.
    27          pdayref        ! Day of reference for the simulation
    28     REAL, INTENT(IN)  :: ptimestep, prad, pg, pr, pcpp, punjours
    29 
    30     CALL read_param('unjours', 86400., unjours,'unjours')
    31     CALL read_param('planet_rad',prad,planet_rad,'planet_rad')
    32     CALL read_param('g',9.8           ,g,'g')
    33     CALL read_param('cpp',1004.       ,cpp,'cpp')
    34     CALL read_param('mugaz',28.       ,mugaz,'mugaz')
     24    CALL read_param('planet_rad',6.4e6 ,planet_rad,'planet_rad')
     25    CALL read_param('g',9.8            ,g,'g')
     26    CALL read_param('cpp',1004.        ,cpp,'cpp')
     27    CALL read_param('mugaz',28.        ,mugaz,'mugaz')
    3528    r=perfect_gas_const/mugaz
    3629    rcp=r/cpp
    3730
    38     CALL read_param('year_day',360.   ,year_day,'year_day')
    39     CALL read_param('periheli',150.   ,periheli,'periheli')
    40     CALL read_param('aphelie',150.    ,aphelie,'aphelie')
    41     CALL read_param('peri_day',0.     ,peri_day,'peri_day')
    42     CALL read_param('obliquit',23.    ,obliquit,'obliquit')
    43     CALL read_param('Cd_mer',.01      ,Cd_mer,'Cd_mer')
    44     CALL read_param('Cd_ter',.01      ,Cd_ter,'Cd_ter')
    45     CALL read_param('I_mer',3000.    ,I_mer,'I_mer')
    46     CALL read_param('I_ter',3000.    ,I_ter,'I_ter')
    47     CALL read_param('alb_ter',.112    ,alb_ter,'alb_ter')
    48     CALL read_param('alb_mer',.112    ,alb_mer,'alb_mer')
    49     CALL read_param('emi_mer',1.      ,emi_mer,'emi_mer')
    50     CALL read_param('emi_mer',1.      ,emi_mer,'emi_mer')
     31    CALL read_param('unjours', 86400.,  unjours,'unjours')
     32    CALL read_param('year_day',360.    ,year_day,'year_day')
     33    CALL read_param('periheli',150.    ,periheli,'periheli')
     34    CALL read_param('aphelie',150.     ,aphelie,'aphelie')
     35    CALL read_param('peri_day',0.      ,peri_day,'peri_day')
     36    CALL read_param('obliquit',23.     ,obliquit,'obliquit')
     37
     38    CALL read_param('Cd_mer',.01       ,Cd_mer,'Cd_mer')
     39    CALL read_param('Cd_ter',.01       ,Cd_ter,'Cd_ter')
     40    CALL read_param('I_mer',3000.      ,I_mer,'I_mer')
     41    CALL read_param('I_ter',3000.      ,I_ter,'I_ter')
     42    CALL read_param('alb_ter',.112     ,alb_ter,'alb_ter')
     43    CALL read_param('alb_mer',.112     ,alb_mer,'alb_mer')
     44    CALL read_param('emi_mer',1.       ,emi_mer,'emi_mer')
     45    CALL read_param('emi_mer',1.       ,emi_mer,'emi_mer')
    5146    CALL read_param('emin_turb',1.e-16 ,emin_turb,'emin_turb')
    52     CALL read_param('lmixmin',100.    ,lmixmin,'lmixmin')
    53     CALL read_param('coefvis',.99     ,coefvis,'coefvis')
    54     CALL read_param('coefir',.08      ,coefir,'coefir')
     47    CALL read_param('lmixmin',100.     ,lmixmin,'lmixmin')
    5548
    56     CALL read_param('callrad',.true.,callrad,'appel rayonnement')
    57     CALL read_param('calldifv',.true.,calldifv,'appel difv')
    58     CALL read_param('calladj',.true.,calladj,'appel adj')
    59     CALL read_param('callsoil',.true.,callsoil,'appel soil')
    60     CALL read_param('season',.true.,season,'with seasonal cycle')
    61     CALL read_param('diurnal',.false.,diurnal,'with diurnal cycle')
    62     CALL read_param('lverbose',.true.,lverbose,'lverbose')
    63     CALL read_param('period_sort',1.,period_sort,'period sorties en jour')
     49    CALL read_param('coefvis',.99      ,coefvis,'coefvis')
     50    CALL read_param('coefir',.08       ,coefir,'coefir')
     51
     52    CALL read_param('callrad',  .true.,  callrad,   'appel rayonnement')
     53    CALL read_param('calldifv', .true.,  calldifv,  'appel difv')
     54    CALL read_param('calladj',  .true.,  calladj,   'appel adj')
     55    CALL read_param('callsoil', .true.,  callsoil,  'appel soil')
     56    CALL read_param('season',   .true.,  season,    'with seasonal cycle')
     57    CALL read_param('diurnal',  .false., diurnal,   'with diurnal cycle')
     58    CALL read_param('lverbose', .true.,  lverbose,  'lverbose')
     59    CALL read_param('period_sort', 1., period_sort, 'period sorties en jour')
     60
     61    !   choice of the frequency of the computation of radiations
     62    IF(diurnal) THEN
     63       iradia=NINT(unjours/(20.*ptimestep))
     64    ELSE
     65       iradia=NINT(unjours/(4.*ptimestep))
     66    ENDIF
     67    iradia=1
     68
     69    dtphys=ptimestep
     70  END SUBROUTINE read_params
     71
     72  SUBROUTINE iniphyparam(ptimestep, punjours, prad, pg, pr, pcpp)
     73    USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours
     74    USE callkeys
     75    REAL, INTENT(IN)  :: ptimestep, punjours, prad, pg, pr, pcpp
     76
     77    CALL read_params(ptimestep)
    6478
    6579    CALL check_mismatch('unjours', punjours, unjours)
     
    7892    WRITELOG(*,*) ' Cycle diurne ',diurnal
    7993
    80     !   choice of the frequency of the computation of radiations
    81     IF(diurnal) THEN
    82        iradia=NINT(punjours/(20.*ptimestep))
    83     ELSE
    84        iradia=NINT(punjours/(4.*ptimestep))
    85     ENDIF
    86     iradia=1
    87     WRITELOG(*,*) 'unjours',punjours
     94    WRITELOG(*,*) 'unjours',unjours
    8895    WRITELOG(*,*) 'The radiative transfer is computed each ', &
    8996         &   iradia,' physical time-step or each ', &
    9097         &   iradia*ptimestep,' seconds'
    91 
    92     dtphys=ptimestep
    9398
    9499    LOG_INFO('iniphyparam')
  • dynamico_lmdz/simple_physics/phyparam/physics/logging.F90

    r4235 r4236  
    33  ! see also use_logging.h
    44  ! macro LOGBUF accumulates log output into logging_buffer
    5 
    65  IMPLICIT NONE
    76  SAVE
     
    98
    109  INTERFACE  ! Explicit interfaces for plugins
    11 
    1210     ! Plugin that typically prints all lines in the loggin buffer 'buf' and prepends tags (log level, timestamp, ...)
    13      SUBROUTINE plugin(lev, tag, buf)
    14        INTEGER, INTENT(IN) :: lev
    15        CHARACTER(*), INTENT(IN) :: tag, buf(:)
     11     SUBROUTINE plugin(lev, taglen, tag, buflen, bufsize, buf) BIND(C)
     12       USE, INTRINSIC :: iso_c_binding, ONLY : c_char, c_null_char, c_int
     13       INTEGER(c_int), INTENT(IN), VALUE :: lev, taglen, buflen, bufsize
     14       CHARACTER(KIND=c_char), INTENT(IN) :: tag(taglen), buf(buflen, bufsize)
    1615     END SUBROUTINE plugin
    1716
    1817     ! Plugin that writes into string 'line' information about the gridpoint of index 'index'
    19      SUBROUTINE plugin_log_gridpoint(index, line)
    20        INTEGER, INTENT(IN) :: index ! index of gridpoint
    21        CHARACTER(*), INTENT(OUT) :: line
     18     SUBROUTINE plugin_log_gridpoint(index, line_len, line) BIND(C)
     19       USE, INTRINSIC :: iso_c_binding, ONLY : c_char, c_null_char, c_int
     20       INTEGER(c_int), INTENT(IN), VALUE :: index, line_len ! index of gridpoint, LEN(line)
     21       CHARACTER(KIND=c_char), INTENT(OUT) :: line(line_len)
    2222     END SUBROUTINE plugin_log_gridpoint
    2323
     
    3030#ifndef XCODEML
    3131  ! Note F2003/F2008: XCodeML cannot parse procedure pointers
    32   PROCEDURE(plugin), POINTER, PUBLIC :: flush_plugin => NULL()
    33   PROCEDURE(plugin_log_gridpoint), POINTER, PUBLIC :: log_gridpoint_plugin => NULL()
     32  PUBLIC :: flush_plugin, log_gridpoint_plugin
     33  PROCEDURE(plugin), POINTER :: flush_plugin => NULL()
     34  PROCEDURE(plugin_log_gridpoint), POINTER :: log_gridpoint_plugin => NULL()
    3435#endif
    3536
     
    4950CONTAINS
    5051
     52  SUBROUTINE set_plugins(flush_plugin_c) BIND(C, name='phyparam_set_plugins_logging')
     53    !$cython header void phyparam_set_plugins_logging(void *);
     54    USE, INTRINSIC :: ISO_C_BINDING
     55    TYPE(C_FUNPTR), INTENT(IN), VALUE :: flush_plugin_c
     56    CALL C_F_PROCPOINTER(flush_plugin_c, flush_plugin)
     57  END SUBROUTINE set_plugins
     58
    5159  SUBROUTINE missing_plugin(name, mod)
    5260    CHARACTER(*), INTENT(IN) :: name, mod
     
    5664    CALL flush_log(log_level_warn, 'missing_plugin')
    5765  END SUBROUTINE missing_plugin
     66
     67  !-------------------------------------------------------------------------------------------------
    5868
    5969  SUBROUTINE flush_log(lev,tag)
     
    6676       WRITE(*,*) '        see logging.F90'
    6777    END IF
    68     IF(logging_lineno>0 .AND. lev<=max_log_level) CALL flush_plugin(lev, TRIM(tag), logging_buf(1:logging_lineno))
     78    IF(logging_lineno>0 .AND. lev<=max_log_level) &
     79         CALL flush_plugin(lev, LEN(tag), TRIM(tag), linesize, logging_lineno, logging_buf)
    6980    logging_lineno=0
    7081#endif
    7182  END SUBROUTINE flush_log
    7283
    73   SUBROUTINE default_flush_plugin(lev, tag, buf)
    74     INTEGER, INTENT(IN) :: lev
    75     CHARACTER(*), INTENT(IN) :: tag, buf(:)
     84  SUBROUTINE default_flush_plugin(lev, taglen, tag, buflen, bufsize, buf)
     85    USE, INTRINSIC :: iso_c_binding, ONLY : c_char, c_null_char, c_int
     86    INTEGER(c_int), INTENT(IN), VALUE :: lev, taglen, buflen, bufsize
     87    CHARACTER(KIND=c_char), INTENT(IN) :: tag(taglen), buf(buflen, bufsize)
    7688    CHARACTER(100) :: prefix
     89    CHARACTER(buflen+1) :: line
    7790    INTEGER :: i
    7891    WRITE(prefix,*) '[', dbtag(lev), ' ', tag, ']'
    79     DO i=1, SIZE(buf)
    80        WRITE(*,*) TRIM(prefix), TRIM(buf(i))
     92    DO i=1, bufsize
     93       WRITE(line,*) buf(:,i)
     94       WRITE(*,*) TRIM(prefix), TRIM(line)
    8195    END DO
    8296  END SUBROUTINE default_flush_plugin
     97
     98  !-------------------------------------------------------------------------------------------------
    8399
    84100  SUBROUTINE log_gridpoint(index)
     
    91107       WRITE(*,*) '        see logging.F90'
    92108    END IF
    93     CALL log_gridpoint_plugin(index, logging_buf(logging_lineno))
     109    CALL log_gridpoint_plugin(index, linesize, logging_buf(logging_lineno))
    94110#endif
    95111  END SUBROUTINE log_gridpoint
    96112
    97   SUBROUTINE default_log_gridpoint(index, line)
    98     INTEGER, INTENT(IN) :: index ! index of gridpoint
    99     CHARACTER(*), INTENT(OUT) :: line
     113  SUBROUTINE default_log_gridpoint(index, line_len, line)
     114    USE, INTRINSIC :: iso_c_binding, ONLY : c_char, c_null_char, c_int
     115    INTEGER(c_int), INTENT(IN), VALUE :: index, line_len ! index of gridpoint, LEN(line)
     116    CHARACTER(KIND=c_char), INTENT(OUT) :: line(line_len)
    100117    line=' '
    101118  END SUBROUTINE default_log_gridpoint
  • dynamico_lmdz/simple_physics/phyparam/physics/phyparam_mod.F90

    r4229 r4236  
    3434       &            pplev,pplay,pphi,           &
    3535       &            pu,pv,pt,                   &
    36        &            pdu,pdv,pdt,pdpsrf)
     36       &            pdu,pdv,pdt,pdpsrf) BIND(C, name='phyparam_phyparam')
    3737    USE phys_const, ONLY : g, rcp, r, unjours
    3838    USE surface,    ONLY : soil
     
    4545    !   20 parameters GCM for planetary atmospheres.
    4646    !   It includes:
    47     !   raditive transfer (long and shortwave) for CO2 and dust.
     47    !   radiative transfer (long and shortwave) for CO2 and dust.
    4848    !   vertical turbulent mixing
    4949    !   convective adjsutment
     50    !   heat diffusion in the soil
    5051    !
    5152    !   author: Frederic Hourdin 15 / 10 /93
    5253    !=======================================================================
    5354
    54     INTEGER, INTENT(IN) ::      &
     55    INTEGER, INTENT(IN), VALUE :: &
    5556         ngrid,                 & ! Size of the horizontal grid.
    5657         nlayer                   ! Number of vertical layers.
    57     LOGICAL, INTENT(IN) ::      &
     58    LOGICAL, INTENT(IN), VALUE  :: &
    5859         firstcall,             & ! True at the first call
    5960         lastcall                 ! True at the last call
    60     REAL, INTENT(IN)    ::      &
     61    REAL, INTENT(IN), VALUE     ::      &
    6162         rjourvrai,             & ! Number of days counted from the North. Spring equinox
    6263         gmtime,                & ! time of the day in seconds
    63          ptimestep,             & ! timestep (s)
     64         ptimestep                ! timestep (s)
     65    REAL, INTENT(IN) :: &
    6466         pplev(ngrid,nlayer+1), & ! Pressure at interfaces between layers (pa)
    6567         pplay(ngrid,nlayer),   & ! Pressure at the middle of the layers (Pa)
     
    431433  END SUBROUTINE radiative_tendencies
    432434
    433   SUBROUTINE alloc(ngrid, nlayer)
     435  SUBROUTINE alloc(ngrid, nlayer) BIND(C, name='phyparam_alloc')
     436    !$cython header void phyparam_alloc(int, int);
     437    !$cython wrapper def alloc(ngrid, nlayer) : phy.phyparam_alloc(ngrid, nlayer)
    434438    USE astronomy, ONLY : iniorbit
    435439    USE surface, ONLY : zc,zd
    436     INTEGER, INTENT(IN) :: ngrid, nlayer
     440    INTEGER, INTENT(IN), VALUE :: ngrid, nlayer
    437441    LOGICAL, PARAMETER :: firstcall=.TRUE.
    438442    ! allocate arrays for internal state
     
    448452  END SUBROUTINE alloc
    449453
    450   SUBROUTINE precompute
     454  SUBROUTINE precompute() BIND(C, name='phyparam_precompute')
     455    !$cython header void phyparam_precompute();
     456    !$cython wrapper def precompute() : phy.phyparam_precompute()
    451457    USE surface
    452458    ! precompute time-independent arrays
     
    458464  END SUBROUTINE precompute
    459465
    460   SUBROUTINE coldstart(ngrid, ptimestep)
     466  SUBROUTINE coldstart(ngrid, ptimestep) BIND(C, name='phyparam_coldstart')
     467    !$cython header void phyparam_coldstart(int, double);
     468    !$cython wrapper def coldstart (ngrid, timestep): phy.phyparam_coldstart(ngrid, timestep)
    461469    ! create internal state to start a run without a restart file
    462470    USE surface, ONLY : soil
    463     INTEGER, INTENT(IN) :: ngrid
    464     REAL, INTENT(iN)    :: ptimestep
     471    INTEGER, INTENT(IN), VALUE :: ngrid
     472    REAL, INTENT(IN),    VALUE :: ptimestep
    465473    tsurf(:)   = tsoil_init
    466474    tsoil(:,:) = tsoil_init
  • dynamico_lmdz/simple_physics/phyparam/physics/read_param_mod.F90

    r4235 r4236  
    4343  INTERFACE read_param
    4444     PROCEDURE read_paramr, read_parami, read_paramb
    45   END INTERFACE read_param
     45  END INTERFACE
    4646
    4747  PUBLIC :: read_param
  • dynamico_lmdz/simple_physics/phyparam/physics/writefield_mod.F90

    r4235 r4236  
    2424  INTERFACE writefield
    2525     PROCEDURE writefield1, writefield2
    26   END INTERFACE writefield
     26  END INTERFACE
    2727
    2828  PUBLIC :: writefield
Note: See TracChangeset for help on using the changeset viewer.