Changeset 2793


Ignore:
Timestamp:
Feb 16, 2017, 8:57:30 AM (7 years ago)
Author:
fhourdin
Message:

Petite correction a la precedente commission de iophys

File:
1 edited

Legend:

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

    r2734 r2793  
     1!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     2! Interface pour ecrire en netcdf avec les routines d'enseignement
     3! iotd de Frederic Hourdin
     4!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     5
    16      subroutine iophys_ecrit(nom,lllm,titre,unite,px)
    27
     
    6267      end
    6368
     69!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     70! Version avec reindexation pour appeler depuis les routines internes
     71! à la sous surface
     72!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
     73
     74
     75    subroutine iophys_ecrit_index(nom,lllm,titre,unite,knon,knindex,px)
     76
     77    USE mod_phys_lmdz_para, ONLY: klon_omp
     78    USE dimphy, ONLY : klon
     79    USE mod_grid_phy_lmdz, ONLY: klon_glo
     80    IMPLICIT NONE
     81
     82! This subroutine returns the sea surface temperature already read from limit.nc
     83!
     84
     85! Arguments on input:
     86    INTEGER lllm
     87    CHARACTER (len=*) :: nom,titre,unite
     88    REAL px(klon_omp,lllm)
     89    INTEGER, INTENT(IN)                  :: knon     ! nomber of points on compressed grid
     90    INTEGER, DIMENSION(klon), INTENT(IN) :: knindex  ! grid point number for compressed grid
     91    REAL, DIMENSION(klon,lllm) :: varout
     92
     93    INTEGER :: i,l
     94
     95    IF (klon/=klon_omp) THEN
     96      print*,'klon, klon_omp',klon,klon_omp
     97      STOP'probleme de dimension parallele'
     98    ENDIF
     99
     100    varout(1:klon,1:lllm)=0.
     101    DO l = 1, lllm
     102    DO i = 1, knon
     103       varout(knindex(i),l) = px(i,l)
     104    END DO
     105    END DO
     106    CALL iophys_ecrit(nom,lllm,titre,unite,varout)
     107
     108  END SUBROUTINE iophys_ecrit_index
     109
    64110!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    65111      SUBROUTINE iophys_ini
     
    68114      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
    69115      USE dimphy, ONLY: klev
     116      USE mod_grid_phy_lmdz, ONLY: klon_glo
    70117
    71118      IMPLICIT NONE
     
    88135
    89136real pi
     137INTEGER nlat_eff
    90138
    91139!   Arguments:
     
    94142!$OMP MASTER
    95143    IF (is_mpi_root) THEN       
     144
     145! Bidouille pour gerer le fait que lat_reg contient deux latitudes
     146! en version uni-dimensionnelle (chose qui pourrait être résolue
     147! par ailleurs)
     148IF (klon_glo==1) THEN
     149   nlat_eff=1
     150ELSE
     151   nlat_eff=size(lat_reg)
     152ENDIF
    96153pi=2.*asin(1.)
    97154call iotd_ini('phys.nc   ', &
    98 !iim,jjp1,llm,rlonv(1:iim)*180./pi,rlatu*180./pi,presnivs)
    99 size(lon_reg),size(lat_reg),klev,lon_reg(:)*180./pi,lat_reg*180./pi,presnivs)
     155size(lon_reg),nlat_eff,klev,lon_reg(:)*180./pi,lat_reg*180./pi,presnivs)
    100156    ENDIF
    101157!$OMP END MASTER
Note: See TracChangeset for help on using the changeset viewer.