Ignore:
Timestamp:
Nov 29, 2024, 3:15:38 PM (2 weeks ago)
Author:
yann meurdesoif
Message:

Nvidia compiler has some difficulties to compile correctly some complex array constructor.
This commit decompose it the several phases in order to achieve the compilation.
Please Lionel and David, have a look to this in order to validate.
Probably, in future, when compiler heuristic will be improved, this commit can be reversed.
YM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/regr_horiz_time_climoz_m.f90

    r5268 r5353  
    139139  REAL, ALLOCATABLE :: test_o3_in(:,:)
    140140  REAL, ALLOCATABLE :: test_o3_out(:)
     141  REAL,ALLOCATABLE :: tmp(:)
    141142
    142143
     
    427428       !--- Regrid in longitude
    428429        ALLOCATE(o3_regr_lon(nlon_ou, nlat_in, nlev_in, ie-ib+1, read_climoz))
     430        tmp = [boundslon_reg(1,west),boundslon_reg(:,east)]
    429431        CALL regr_conserv(1, o3_in3, xs = lon_in_edge,                             &
    430                             xt = [boundslon_reg(1,west),boundslon_reg(:,east)],    &
    431                             vt = o3_regr_lon, slope = slopes(1,o3_in3, lon_in_edge))
     432                          xt = tmp ,                                               &
     433                          vt = o3_regr_lon, slope = slopes(1,o3_in3, lon_in_edge))
    432434        DEALLOCATE(o3_in3)
    433435
     
    436438        !--- (inverted indices in "o3_regr_lonlat" because "rlatu" is decreasing)
    437439        ALLOCATE(o3_regr_lonlat(nlon_ou, nlat_ou, nlev_in, 0:13, read_climoz))
    438         CALL regr_conserv(2, o3_regr_lon, xs = sinlat_in_edge,                     &
    439                         xt = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.], &
    440                         vt = o3_regr_lonlat(:,nlat_ou:1:- 1,:,ib:ie,:),            &
    441                    slope = slopes(2,o3_regr_lon, sinlat_in_edge))
     440        tmp = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.]   
     441        CALL regr_conserv(2, o3_regr_lon, xs = sinlat_in_edge,                       &
     442                          xt = tmp,                                                  &
     443                          vt = o3_regr_lonlat(:,nlat_ou:1:- 1,:,ib:ie,:),            &
     444                          slope = slopes(2,o3_regr_lon, sinlat_in_edge))
    442445        DEALLOCATE(o3_regr_lon)
    443446
     
    519522        !--- (inverted indices in "o3_regr_lat" because "rlatu" is decreasing)
    520523        ALLOCATE(o3_regr_lat(nlat_ou, nlev_in, 0:13, read_climoz))
     524        tmp = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.]
    521525        CALL regr_conserv(1, o3_in2, xs = sinlat_in_edge,                          &
    522                         xt = [- 1., SIN(boundslat_reg(nlat_ou-1:1:-1,south)), 1.], &
     526                        xt = tmp,                                                  &
    523527                        vt = o3_regr_lat(nlat_ou:1:- 1,:,ib:ie,:),                 &
    524528                     slope = slopes(1,o3_in2, sinlat_in_edge))
Note: See TracChangeset for help on using the changeset viewer.