Ignore:
Timestamp:
10/16/17 15:22:59 (7 years ago)
Author:
dubos
Message:

devel : multiplicative factor in flux/wind reconstructions

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/diagnostics/diagflux.f90

    r585 r587  
    44  SAVE 
    55   
    6   TYPE(t_field),POINTER :: f_qfluxt(:), f_qfluxt_i(:) ! time-integrated flux of scalars and its reconstruction at cell centers 
    7    
     6  TYPE(t_field),POINTER :: f_qfluxt(:), f_qfluxt_lon(:), f_qfluxt_lat(:) ! time-integrated flux of scalars and its reconstruction at cell centers 
    87  LOGICAL :: diagflux_on 
    98  !$OMP THREADPRIVATE(diagflux_on) 
     
    1716    IF(diagflux_on) THEN 
    1817       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,nqtot, name="qfluxt") 
    19        CALL allocate_field(f_qfluxt_i,  field_t,type_real,llm,nqtot, name="qfluxt_i") 
     18       CALL allocate_field(f_qfluxt_lon,  field_t,type_real,llm,nqtot, name="qfluxt_lon") 
     19       CALL allocate_field(f_qfluxt_lat,  field_t,type_real,llm,nqtot, name="qfluxt_lat") 
    2020       CALL zero_qfluxt 
    2121    ELSE 
     22       STOP ! FIXME 
    2223       CALL allocate_field(f_qfluxt,  field_u,type_real,llm,0, name="qfluxt") 
    23        CALL allocate_field(f_qfluxt_i,  field_t,type_real,llm,0, name="qfluxt_i") 
     24       CALL allocate_field(f_qfluxt_lon,  field_t,type_real,llm,0, name="qfluxt_lon") 
     25       CALL allocate_field(f_qfluxt_lat,  field_t,type_real,llm,0, name="qfluxt_lat") 
    2426    END IF 
    2527  END SUBROUTINE init_diagflux 
     
    3840  END SUBROUTINE zero_qfluxt 
    3941 
    40   SUBROUTINE flux_centered_lonlat(f_flux, f_flux_lon, f_flux_lat) 
     42  SUBROUTINE flux_centered_lonlat(scale, f_flux, f_flux_lon, f_flux_lat) 
     43    REAL(rstd), INTENT(IN) :: scale 
    4144    TYPE(t_field),POINTER :: f_flux(:), f_flux_lon(:), f_flux_lat(:) 
    4245    REAL(rstd), POINTER :: flux(:,:,:), flux_lon(:,:,:), flux_lat(:,:,:) 
     
    4750       CALL swap_geometry(ind) 
    4851       flux=f_flux(ind) 
     52       flux_lon=f_flux_lon(ind) 
     53       flux_lat=f_flux_lat(ind) 
    4954       DO itrac=1,nqtot 
    50           CALL compute_flux_centered_lonlat(flux(:,:,itrac), flux_lon(:,:,itrac), flux_lat(:,:,itrac)) 
     55          CALL compute_flux_centered_lonlat(scale, flux(:,:,itrac), flux_lon(:,:,itrac), flux_lat(:,:,itrac)) 
    5156       END DO 
    5257    END DO 
    5358  END SUBROUTINE flux_centered_lonlat 
    5459   
    55   SUBROUTINE compute_flux_centered_lonlat(flux, flux_lon, flux_lat) 
     60  SUBROUTINE compute_flux_centered_lonlat(scale, flux, flux_lon, flux_lat) 
     61    USE wind_mod 
     62    REAL(rstd), INTENT(IN) :: scale 
    5663    REAL(rstd), INTENT(IN) :: flux(3*iim*jjm,llm) 
    5764    REAL(rstd), INTENT(OUT) :: flux_lon(iim*jjm,llm), flux_lat(iim*jjm,llm) 
    5865    REAL(rstd) :: flux_3d(iim*jjm,llm,3) 
    59     CALL compute_flux_centered(flux, flux_3d) 
     66    CALL compute_flux_centered(scale, flux, flux_3d) 
    6067    CALL compute_wind_centered_lonlat_compound(flux_3d, flux_lon, flux_lat) 
    6168  END SUBROUTINE compute_flux_centered_lonlat 
Note: See TracChangeset for help on using the changeset viewer.