prismdrv.F90

Go to the documentation of this file.
00001 !------------------------------------------------------------------------
00002 ! Copyright 2006-2010, CERFACS, Toulouse, France.
00003 ! All rights reserved. Use is subject to OASIS4 license terms.
00004 !------------------------------------------------------------------------
00005 !BOP
00006 !
00007 !
00008 ! !MODULE: PRISMDrv
00009 MODULE PRISMDrv
00010 
00011 ! !PUBLIC TYPES
00012   USE PSMILe_common
00013   USE PRISMDrv_Constants
00014 
00015   IMPLICIT NONE
00016 
00017 ! !DESCRIPTION
00018 ! This module describes the general variables used by the driver and the 
00019 ! driver's routines
00020 !
00021 ! !REVISED HISTORY
00022 !   Date      Programmer   Description
00023 ! ----------  ----------   -----------
00024 ! 03/10/2002  D. Declat    Creation
00025 ! 06/03/2008  J. Charles   Modifications added for the use of bundle fields
00026 !
00027 ! EOP
00028 !----------------------------------------------------------------------
00029 ! $Id: prismdrv.F90 2963 2011-02-17 14:52:53Z coquart $
00030 ! $Author: coquart $
00031 !----------------------------------------------------------------------
00032 !
00033 ! Structure for Process Management
00034 ! ================================
00035 !
00036 !  appli_name     : name of the application
00037 !
00038 !  comp_name      : name of the component
00039 !
00040 !  global_comp_id : global id of the component
00041 !
00042 !  global_rk      : global rank of the process
00043 !
00044   TYPE Drv_Proc_manage
00045 
00046     Character(len=max_name)          :: appli_name    
00047     Character(len=max_name), Pointer :: comp_name(:)
00048     Integer, Pointer                 :: global_rank(:)
00049     Integer                          :: comps_per_rank
00050     Integer, Pointer                 :: global_comp_id(:)
00051 
00052   END TYPE Drv_Proc_manage
00053 !
00054 !----------------------------------------------------------------------
00055 !
00056 ! Structure for Grid
00057 ! ==================
00058 !
00059 ! The grids table
00060 !
00061 !  status        : Status of the grid information (see PSMILe statuses)
00062 !
00063 !  grid_name     : name of the grid 
00064 !
00065 !  grid_id       : Id of the grid for the component comp_id
00066 !  comp_id       : Id of the component the grid belongs
00067 ! 
00068 !  ***_units     : units of the ***
00069 !  ***_min       : minimum of the ***
00070 !  ***_max       : maximum of the *** 
00071 !  ***_pointer   : *** array
00072 !
00073 !  vrt_stand_name 
00074 !  vrt_formula_terms 
00075 !
00076 !  ig_grid_type  : type of structure for the grid
00077 !  ig_volume_type : type of volume
00078 !
00079 !  pole_covered  : indicates if the pole are covered or not
00080 !  extent        : extent of the grid in the dimension
00081 !  size          : size of the grid (nb of points)
00082 !  overlap       : number of overlaping points in the dimension 
00083 !  periodic      : periodicity in the dimension 
00084 !                  (PSMILe_true or PSMILe_false)
00085 !  timedep       : time dependency of the dimension 
00086 !                  (at max 3 dimensions i,j,k)
00087 !
00088   TYPE Drv_Grid
00089 
00090     Integer                     :: grid_id
00091     Integer                     :: status
00092 
00093     Integer                     :: comp_id
00094 
00095     Integer                     :: lon_units
00096     Integer                     :: lat_units
00097     Integer                     :: z_units
00098 
00099     Integer                     :: grid_type
00100 
00101     Integer                     :: pole_covered     
00102     Integer                     :: size
00103     Integer, Dimension(3)       :: overlap    
00104     Integer, Dimension(3)       :: periodic         
00105     Integer, Dimension(3)       :: extent         
00106     Integer, Dimension(3)       :: timedep 
00107 
00108     Character(len=max_name)     :: grid_name
00109 
00110     Character(len=max_name)     :: vrt_stand_name
00111     Character(len=max_name)     :: vrt_formula_terms 
00112 
00113     Double Precision, Dimension(:), Pointer :: lon_pointer
00114     Double Precision, Dimension(:), Pointer :: lat_pointer
00115     Double Precision, Dimension(:), Pointer :: z_pointer
00116 
00117 
00118   END TYPE Drv_Grid
00119 
00120 !
00121 !======================================================================
00122 !
00123 ! Structure for EPIO
00124 ! ==================
00125 !
00126 ! The EPIO is the ensemble of points used in the interpolation operations
00127 !
00128 ! The following structure defines the storage of the EPIOS and EPIOT for
00129 ! on one association source component/ target component
00130 !
00131   TYPE Drv_EPIO
00132 
00133     Integer           :: epio_id     ! id set by the transformer (T)
00134     Integer           :: trans_rank  ! rank of the T process treating this epio
00135     Integer           :: status      ! indicates if this index has already been
00136                                      ! used (needed for the allocation process)
00137     Integer           :: src_comp_id ! source component global id
00138     Integer           :: tgt_comp_id ! target component global id
00139     Integer           :: src_process ! local rank of the source process
00140     Integer           :: tgt_process ! local rank of the target process
00141     Integer           :: src_status  ! status to inform if the src EPIO has 
00142                                      ! already been set or not
00143     Integer           :: tgt_status  ! status to inform if the tgt EPIO has 
00144                                      ! already been set or not
00145     Integer           :: src_size    ! number of source points in the EPIO
00146     Integer           :: src_lonlatz_size !size of source lat/lon/z compact 
00147                                      ! arrays (points or corners)
00148     Integer           :: src_nbr_corner ! number of corner for the source grid
00149     Integer           :: tgt_size    ! number of target points in the EPIO
00150     Integer           :: tgt_nbr_corner ! number of corner for the target grid
00151     Integer           :: weights_status ! indicates if the weights were already
00152                                         ! calculated or not
00153     Integer           :: src_coord_type ! PRISM_Real or PRISM_Double_Precision
00154     Integer           :: tgt_coord_type ! PRISM_Real or PRISM_Double_Precision
00155     INTEGER           :: max_links_map1 ! current size of link arrays
00156     INTEGER           :: num_links_map1 ! actual number of links for remapping
00157     INTEGER           :: resize_increment ! default to increase array size
00158     INTEGER           :: src_grid_type    ! source grid type
00159     INTEGER           :: gaussred_stride  ! stride in lat/lon corner array
00160              ! between cell minimum and maximum values.
00161     Integer, Pointer  :: src_mask_pointer(:) ! mask for source epio
00162     Integer, Pointer  :: tgt_mask_pointer(:) ! mask for source epio
00163     Integer, Pointer  :: index_array(:,:) ! for each EPIO target point, indices
00164              ! to access the compact arrays of corresponding source 
00165              ! point/corner latitudes, longitudes, and z
00166     Integer, Pointer  :: same_lat(:) ! array of integer to know if the bascule must
00167              ! be done or not for each target point for gaussian reduced source grid
00168     Integer, Pointer  :: nbsrccells_pertgtpt(:) ! for each EPIO target point, 
00169              ! the number of corresponding source cells (used for  conservative
00170              ! remapping only as this number varies for each tgt pt)
00171     INTEGER, POINTER  :: srcepio_add(:) ! array containing for each element of
00172              ! the lon/lat/z compact arrays the corresponding rank in the total
00173              ! number of epio source points
00174     INTEGER, POINTER  :: grid1_add_map1(:) ! for each 2d conservative remapping
00175              ! link: rank of the corresponding source point in the total
00176              ! number of epio source points
00177     INTEGER, POINTER  :: grid2_add_map1(:) ! for each 2d conservative remapping
00178              ! link: rank of the corresponding target point in the total
00179              ! number of epio target points
00180     REAL, POINTER     :: src_lat_pointer_real(:) ! source epio point/corner 
00181              ! latitude (compact array)
00182     Real, Pointer     :: src_lon_pointer_real(:) ! source epio point/corner 
00183              ! longitude (compact array)
00184     Real, Pointer     :: src_z_pointer_real(:)   ! source epio point/corner 
00185              ! position in the vertical dimension (compact array)
00186     Real, Pointer     :: tgt_lat_pointer_real(:) ! target epio point/corner 
00187              ! latitude (not compact array)
00188     Real, Pointer     :: tgt_lon_pointer_real(:) ! target epio point/corner 
00189              ! longitude (not compact array)
00190     Real, Pointer     :: tgt_z_pointer_real(:)   ! target epio point/corner 
00191              ! position in the vertical dimension (compact array)
00192     Double Precision, Pointer     :: src_lat_pointer_dble(:) ! see above
00193     Double Precision, Pointer     :: src_lon_pointer_dble(:) ! see above
00194     Double Precision, Pointer     :: src_z_pointer_dble(:)   ! see above
00195     Double Precision, Pointer     :: tgt_lat_pointer_dble(:) ! see above
00196     Double Precision, Pointer     :: tgt_lon_pointer_dble(:) ! see above
00197     Double Precision, Pointer     :: tgt_z_pointer_dble(:)   ! see above 
00198     Double Precision, Pointer     :: weights(:,:) ! interpolation weights
00199     DOUBLE PRECISION, POINTER     :: wts_map1(:,:)! 2d cons remapping weights
00200     DOUBLE PRECISION, POINTER     :: grid1_area(:)! area of source epio cell
00201               ! as provided by the component 
00202     DOUBLE PRECISION, POINTER     :: grid2_area(:)! area of target epio cell
00203               ! as calculated by the 2d conservative remappin    
00204   END TYPE Drv_EPIO
00205 
00206 !  
00207 !======================================================================
00208 !
00209 ! Structure for files
00210 ! ===================
00211 !
00212   TYPE Drv_file_struct
00213 
00214     CHARACTER(len=max_name)    :: file_name
00215     INTEGER                    :: suffix
00216     INTEGER                    :: file_format  
00217     INTEGER                    :: file_set        
00218     INTEGER                    :: file_threading  
00219     INTEGER                    :: file_pack    
00220     DOUBLE PRECISION           :: file_scal  
00221     DOUBLE PRECISION           :: file_add
00222     DOUBLE PRECISION           :: fill_val   
00223   END TYPE Drv_file_struct
00224 !  
00225 !======================================================================
00226 !
00227 ! Structure for interpolations
00228 ! ============================
00229 !
00230 ! See prism/src/lib/common_oa4/src/psmile_smioc.F90 for comments
00231 !
00232   TYPE Drv_Interp
00233 
00234     Integer                 :: interp_id
00235 
00236     Integer                 :: interp_type  
00237     Integer, Dimension(3)   :: interp_method
00238     Integer                 :: nb_neighbors 
00239 
00240     Integer, Dimension(3)   :: arg1
00241     Integer, Dimension(3)   :: arg2
00242     Integer, Dimension(3)   :: arg3
00243     Integer, Dimension(3)   :: arg4
00244     Integer, Dimension(3)   :: arg5
00245     Integer, Dimension(3)   :: arg6
00246     Integer, Dimension(3)   :: arg7
00247     Type (Drv_file_struct)  :: arg10
00248 
00249     Character(len=max_name) :: arg9
00250 
00251     Double Precision        :: arg8
00252 
00253   END TYPE Drv_Interp
00254 
00255 !
00256 !======================================================================
00257 ! 
00258 ! Structure for local transformations
00259 ! ===================================
00260 !
00261 ! transf_id     : Global id of the transformation
00262 !
00263 ! scat_gath     : indicates if a scattering or a gathering is needed 
00264 !                    (PSMILe_scat or PSMILe_gather or PSMILe_undef)
00265 !
00266 ! reduc_type    : type of reduction for each dimension (PSMILe_min,
00267 !                    PSMILe_max, PSMILe_ave, PSMILe_undef)
00268 !
00269 ! bndl_combi_type : type of bndl_combine 
00270 !   ->PSMIle_var_mask: in the comb, the bundle is masked with its mask
00271 !   ->PSMILe_ext_mask: in the combination, the bundle is masked with an 
00272 !                           ext mask coming from a file 
00273 !   ->PSMILe_undef: no bundle combination
00274 ! bndl_combi_ext_mask_name: meaningful if PSMILe_ext_mask
00275 ! bndl_combi_ext_mask_file: meaningful if PSMILe_ext_mask 
00276 ! 
00277 ! mask_type     : type of masking 
00278 !   ->PSMIle_var_mask: the transient is masked with its mask
00279 !   ->PSMILe_ext_mask: the transient is masked with an 
00280 !                           ext mask coming from a file 
00281 !   ->PSMILe_undef: no masking 
00282 !
00283 ! ext_mask_name : meaningful if PSMILe_ext_mask
00284 ! ext_mask_file : meaningful if PSMILe_ext_mask
00285 ! mask_value    : mask value 
00286 !
00287 ! extrap_nnbr   : nb of neighbours in case of extrapolation
00288 !
00289 ! extrap_wfile  : name of the file the weights for the
00290 !                               extrapolation are stored
00291 !
00292 ! add_scalar    : scalar to add to the field
00293 ! mult_scalar   : scalar to multiply the field
00294 !
00295 ! src_size      : size of the source partition
00296 ! src_field     : source field partition
00297 ! 
00298 ! trans_size    : size of the transformed partition 
00299 ! trans_field   : transformed field partition
00300 !
00301   TYPE Drv_Transf
00302 
00303     Integer                   :: transf_id
00304 
00305     Integer                   :: status    
00306     Integer                   :: request    
00307 
00308     Integer                   :: scat_gather
00309 
00310     Integer                   :: bndl_combi_type
00311     Integer                   :: mask_type
00312 
00313     Integer                   :: extrap_nnbr
00314 
00315     Integer, Dimension(4)     :: reduc_type
00316 
00317     Character(len=max_name)   :: bndl_combi_ext_mask_name
00318     Type (Drv_file_struct)    :: bndl_combi_ext_mask_file
00319 
00320     Character(len=max_name)   :: ext_mask_name
00321     Type (Drv_file_struct)    :: ext_mask_file
00322 
00323     Type (Drv_file_struct)    :: extrap_wfile
00324 
00325     Double Precision          :: mask_value
00326 
00327     Double Precision          :: add_scalar
00328     Double Precision          :: mult_scalar
00329 
00330   END TYPE Drv_Transf
00331   
00332 !
00333 !======================================================================
00334 !
00335 ! Structure for the Fields exchange
00336 !==================================
00337 !
00338 ! trans_out_id    : Global id for the transient out variable
00339 ! trans_in_id     : Global id for the transient in variable
00340 !
00341 ! epio_id         : Global id of the corresponding epio
00342 !
00343 ! interp_id       : Global id of the corresponding interpolation 
00344 !                   (refers to the interpolation table)
00345 ! interp_state    : state of the interpolation (UNDO, DONE)
00346 !
00347 ! transf_id       : Global id of the corresponding transformations
00348 !                   (refers to the transformation table)
00349 ! transf_state    : state of the interpolation (UNDO, DONE)
00350 !
00351 ! trans_in_field_size : size of the target field
00352 ! trans_in_field      : target field
00353 ! trans_in_nbr_allocated_fields
00354 !                     : number of fields that would fit into the
00355 !                       memory currently allocated for
00356 !                       trans_in_field_[int,real,dble]
00357 ! trans_in_nbr_allocated_sums
00358 !                     : number of sums that would fit into the
00359 !                       memory currently allocated for
00360 !                       trans_in_field_[int,dble]
00361 ! 
00362   TYPE Drv_Exchange
00363 
00364     Integer                    :: trans_out_id
00365     Integer                    :: trans_in_id
00366     Integer                    :: epio_id
00367 
00368     Integer                    :: conservation
00369 
00370     Integer                    :: interp_id
00371     Integer                    :: interp_status
00372 
00373     Integer                    :: transf_id
00374     Integer                    :: transf_status
00375 
00376     Integer                    :: trans_in_field_size
00377     Integer                    :: trans_in_status
00378     Integer                    :: trans_in_request
00379 
00380     Integer                    :: trans_in_nbr_allocated_fields
00381     Integer                    :: trans_in_nbr_allocated_sums
00382 
00383     Integer                    :: trans_in_field_type  
00384 
00385     Integer, Pointer           :: trans_in_field_int(:)
00386     Real, Pointer              :: trans_in_field_real(:)
00387     Double Precision, Pointer  :: trans_in_field_dble(:) 
00388 
00389     Integer, Pointer           :: global_sum_int(:)
00390     Double Complex, Pointer    :: global_sum_dble(:)
00391 
00392   END TYPE Drv_Exchange
00393 
00394 !
00395 !======================================================================
00396 !
00397 ! Structure for persistent variables 
00398 ! ==================================
00399 !
00400 !  local_name    : local name of the persistent variable
00401 !
00402 !  stand_name    : standard name of the persistent variable
00403 !
00404 !  comp_name     : name of the component the persistent belongs
00405 !
00406 !  comp_id       : component id the persistent belongs (set by the drv)
00407 !
00408 !  persist_type  : variable type (PSMILe_local or PSMILe_global)
00409 !
00410 !  units         : unit of the persistent variable
00411 !  persist_min   : minimum value for the variable
00412 !  persist_max   : maximum value for the variable
00413 !
00414 !  datatype      : numerical type of the variable 
00415 !
00416 !  persist       : value of the persistent variable
00417 !
00418    TYPE Drv_persistent
00419 
00420      Integer                 :: comp_id
00421      Integer                 :: persist_type
00422 
00423      Integer                 :: units             
00424      Integer                 :: datatype 
00425 
00426      Character(len=max_name) :: local_name  
00427      Character(len=max_name) :: stand_name
00428  
00429      Character(len=max_name) :: comp_name   
00430               
00431      Double Precision        :: persist_min              
00432      Double Precision        :: persist_max
00433      Double Precision        :: persist 
00434    
00435    END TYPE Drv_persistent
00436 !
00437 !======================================================================
00438 !----------------------------------------------------------------------
00439 !
00440 ! Global information
00441 !
00442 !----------------------------------------------------------------------
00443 !
00444 ! Name of the different applications of the simulation
00445   Character(LEN=max_name), Dimension(:), ALLOCATABLE :: cga_appli_name
00446 
00447 ! Name of the different application executables of the simulation
00448   Character(LEN=max_name), Dimension(:), ALLOCATABLE :: cga_appli_exe_name
00449 
00450 ! Argument of the different application executables of the simulation
00451   Character(LEN=max_name), Dimension(:), ALLOCATABLE :: cga_appli_args
00452 
00453 ! Name of the different hosts for all applications
00454   Character(LEN=max_name), Dimension(:), ALLOCATABLE :: cga_appli_hostname
00455 
00456 ! Name of the different components for each application
00457   Character(LEN=max_name), Dimension(:), ALLOCATABLE :: cga_appli_compname
00458 
00459 ! Number of hosts for each application
00460   Integer, Dimension(:), ALLOCATABLE :: iga_appli_nb_hosts
00461 
00462 ! Number of processes for each application
00463   Integer, Dimension(:), ALLOCATABLE :: iga_appli_nb_pes
00464 
00465 ! Number of components for each application
00466   Integer, Dimension(:), ALLOCATABLE :: iga_appli_nb_comps
00467 
00468 ! Number of arguments for each application
00469   Integer, Dimension(:), ALLOCATABLE :: iga_appli_nb_args
00470 
00471 ! Number of processes for each hosts of an application
00472   Integer, Dimension(:), ALLOCATABLE :: iga_appli_hostnbprocs 
00473 
00474 ! Total number of rank sets for each application in the experiment 
00475   Integer, Dimension(:), ALLOCATABLE :: iga_appli_nbtot_ranksets
00476 
00477 ! Total number of rank sets in the experiment 
00478   Integer :: ig_nbtot_ranksets
00479 
00480 ! Number of rank sets (min-max-inc) for all components for all applications
00481   Integer, Dimension(:), ALLOCATABLE :: iga_appli_compnbranksets
00482 
00483 ! Array of rank sets (min-max-inc) for all components for all applications
00484   Integer, Dimension(:,:), ALLOCATABLE :: iga_appli_compranks
00485 
00486 ! Stdout redirected or not for all applications
00487   Integer, Dimension(:), ALLOCATABLE :: iga_appli_redirect
00488 
00489 ! Dates of the simulations
00490   TYPE(PRISM_Time_Struct) :: sga_experiment_start_date
00491   TYPE(PRISM_Time_Struct) :: sga_experiment_end_date
00492   TYPE(PRISM_Time_Struct) :: sga_run_start_date
00493   TYPE(PRISM_Time_Struct) :: sga_run_end_date
00494 !
00495 ! * Dimensionning numbers
00496 !
00497   Integer :: ig_driver_nb_pes   ! nb of pes for the driver
00498 !
00499   Integer :: ig_nb_appl         ! nb of applications
00500   Integer :: ig_nb_tot_pes      ! nb of processes
00501   Integer :: ig_nb_tot_hosts    ! total number of hosts 
00502   Integer :: ig_nb_tot_comps    ! total number of comps 
00503   Integer :: ig_nb_tot_args     ! total number of args 
00504 
00505 ! Number of Fortran unit sets, grids, transients  and  persistents
00506   INTEGER :: ig_nb_tot_unitsets ! total number of Forrean unit sets
00507   INTEGER :: ig_nb_tot_grids    ! total number of grids
00508   INTEGER :: ig_nb_tot_transi   ! total number of transients
00509   INTEGER :: ig_nb_tot_persis   ! total number of presistents
00510 
00511 ! MPI implementation
00512   Integer :: ig_MPI
00513 
00514 !
00515 ! * Communicators
00516 !
00517   Integer :: comm_drv_global     ! Global communicator
00518   Integer :: comm_drv_local      ! Driver communicator
00519   Integer :: comm_drv_psmile     ! communicator that gathers psmile appli.
00520 
00521   Integer :: driver_rank
00522 
00523   Integer :: comm_drv_trans  ! Global communicator dedicated to the trans.
00524 
00525 !
00526 ! ** comm_coupling        : Array - Coupler internal communicator for
00527 !                           communication with individual applications
00528   Integer, Dimension (:), ALLOCATABLE :: comm_coupling
00529 
00530 !
00531 ! Management of the applications name, components name and id and process rank
00532 !
00533   TYPE (Drv_Proc_manage) , Dimension(:), POINTER   :: Drv_Procs
00534 
00535 ! Management of the grids information
00536 !
00537 ! Grids table
00538   TYPE (Drv_Grid), Dimension(:), POINTER   :: Drv_Grids
00539 ! Dimensioning variables
00540   Integer :: Number_of_Grids_drv       ! Number of grids
00541 
00542 ! Dimensioning variables
00543   Integer :: Number_of_Epios_allocated  ! Number of allocated Epios
00544 ! EPIOS, EPIOT arrays
00545   TYPE (Drv_EPIO), Dimension(:), POINTER    :: Drv_Epios
00546 
00547 !
00548 ! Management of the transients information
00549 !
00550 ! Interpolations table
00551   TYPE (Drv_Interp), Dimension(:), POINTER  :: Drv_Interps
00552 ! Transformations table
00553   TYPE (Drv_Transf), Dimension(:), POINTER  :: Drv_Transfs
00554 ! Exchange table
00555   TYPE (Drv_Exchange),Dimension(:), POINTER :: Drv_Exchanges
00556 
00557 ! Dimensioning variables
00558   Integer :: Number_of_comms         ! Number of exchanges of Transients
00559   Integer :: Number_of_Interps       ! Number of interpolations 
00560   Integer :: Number_of_Transfs       ! Number of transformations
00561   Integer :: Number_of_Exchanges     ! Number of exchanges transiting
00562 !
00563 !======================================================================
00564 !----------------------------------------------------------------------
00565 ! 
00566 ! Interfaces of PRISM-Driver/Transformer routines
00567 !
00568 !----------------------------------------------------------------------
00569 ! 
00570 
00571   INTERFACE
00572 
00573     subroutine prismdrv_init (id_err)
00574       Integer, Intent (Out) :: id_err
00575     end subroutine prismdrv_init
00576 
00577     subroutine prismdrv_init_appl (id_err)
00578       Integer, Intent (Out) :: id_err
00579     end subroutine prismdrv_init_appl
00580 
00581     subroutine prismdrv_def_mpi_comm (id_err)
00582       Integer, Intent (Out) :: id_err
00583     end subroutine prismdrv_def_mpi_comm
00584 
00585     subroutine prismdrv_finalize (id_err)
00586       Integer, Intent (Out) :: id_err
00587     end subroutine prismdrv_finalize
00588 
00589 !=======
00590 
00591     subroutine prismdrv_set_scc_info (id_err)
00592       Integer, Intent (Out) :: id_err
00593     end subroutine prismdrv_set_scc_info
00594 
00595 !=======
00596     subroutine prismdrv_spawn_child ( exec, args, n_args, application_number, &
00597    n_hosts, hostnames, npes, intracomm, intercomm, ierror )
00598       USE PSMILe_common
00599       CHARACTER(len=*),INTENT(In)         :: exec
00600       INTEGER,INTENT(In)                  :: n_args
00601       CHARACTER(len=*),INTENT(In)         :: args (n_args)
00602       INTEGER,INTENT(In)                  :: application_number
00603       INTEGER,INTENT(In)                  :: n_hosts
00604       CHARACTER(len=*),INTENT(In)         :: hostnames (n_hosts)
00605       INTEGER,INTENT(In)                  :: npes (n_hosts)
00606       INTEGER, INTENT(In)                 :: intracomm
00607       INTEGER,INTENT(Out)                 :: intercomm
00608       INTEGER,INTENT(Out)                 :: ierror
00609     end subroutine prismdrv_spawn_child
00610 
00611 !=======
00612     subroutine prismdrv_set_smioc_info (id_err)
00613       Integer, Intent (Out) :: id_err
00614     end subroutine prismdrv_set_smioc_info
00615 
00616     subroutine prismdrv_init_smioc_struct (id_err)
00617       Integer, Intent (Out) :: id_err
00618     end subroutine prismdrv_init_smioc_struct
00619 
00620     subroutine prismdrv_finalize_smioc_struct (id_err)
00621       Integer, Intent (Out) :: id_err
00622     end subroutine prismdrv_finalize_smioc_struct
00623 
00624     subroutine prismdrv_get_udef_transients ( id_err )
00625       Integer, Intent (Out) :: id_err
00626     end subroutine prismdrv_get_udef_transients
00627 
00628 
00629 !======================================================================
00630 
00631     subroutine prismtrs_main (id_err)
00632       Integer, Intent (Out) :: id_err
00633     end subroutine prismtrs_main
00634 
00635 !=======
00636  
00637     subroutine prismtrs_bcast2trs (id_err)
00638       Integer, Intent (Out) :: id_err
00639     end subroutine prismtrs_bcast2trs
00640 
00641 !=======
00642     subroutine prismtrs_conserv2d_weight(                          &
00643        id_epiosrc_size, id_epiotgt_size,                           &
00644        id_src_nbr_corner, id_tgt_nbr_corner,                       & 
00645        id_src_lonlatz_size,                                        &
00646        id_index_size1,                                             &
00647        dda_src_lat, dda_src_lon, dda_src_z,                        &
00648        dda_tgt_lat, dda_tgt_lon, dda_tgt_z,                        &
00649        ida_nbsrccells_pertgtpt,                                    &
00650        ida_index_array,                                            &
00651        ida_srcepio_add,                                            &
00652        id_epio_id,                                                 &
00653        id_interp_id,                                               &
00654        id_idim,                                                    &
00655        id_num_wts,                                                 & 
00656        id_err) 
00657   !
00658       INTEGER :: id_epiosrc_size, id_epiotgt_size
00659       INTEGER :: id_src_nbr_corner, id_tgt_nbr_corner
00660       INTEGER :: id_src_lonlatz_size
00661       INTEGER :: id_index_size1
00662       DOUBLE PRECISION, DIMENSION(id_src_lonlatz_size) :: dda_src_lat
00663       DOUBLE PRECISION, DIMENSION(id_src_lonlatz_size) :: dda_src_lon 
00664       DOUBLE PRECISION, DIMENSION(id_src_lonlatz_size) :: dda_src_z
00665       DOUBLE PRECISION, DIMENSION(id_epiotgt_size,id_tgt_nbr_corner) :: dda_tgt_lat
00666       DOUBLE PRECISION, DIMENSION(id_epiotgt_size,id_tgt_nbr_corner) :: dda_tgt_lon 
00667       DOUBLE PRECISION, DIMENSION(id_epiotgt_size,id_tgt_nbr_corner) :: dda_tgt_z
00668       INTEGER, DIMENSION(id_epiotgt_size)                  :: ida_nbsrccells_pertgtpt
00669       INTEGER, DIMENSION(id_index_size1,id_src_nbr_corner) :: ida_index_array
00670       INTEGER, DIMENSION(id_index_size1)                   :: ida_srcepio_add
00671       INTEGER :: id_epio_id     ! EPIO Id
00672       INTEGER :: id_interp_id   ! Interpolation Id
00673       INTEGER :: id_idim        ! Dimension concerned with the current interpolation
00674       INTEGER :: id_num_wts     ! Number of weights for 2D conservative remapping
00675       INTEGER :: id_err
00676     end subroutine prismtrs_conserv2d_weight
00677 
00678 !=======
00679     subroutine prismtrs_remap_conserv (     &
00680        grid1_size, grid2_size,              &
00681        grid1_corners, grid2_corners,        &
00682        id_src_lonlatz_size,                 &
00683        id_index_size1,                      &
00684        grid1_corner_lat, grid1_corner_lon,  &
00685        grid2_corner_lat, grid2_corner_lon,  &
00686        ida_nbsrccells_pertgtpt,             &
00687        ida_index_array,                     &
00688        ida_srcepio_add,                     &
00689        id_epio_id,                          &
00690        id_interp_id,                        &
00691        id_idim,                             &
00692        num_wts,                             &
00693        id_err)
00694       INTEGER :: grid1_size, grid2_size
00695       INTEGER :: grid1_corners, grid2_corners
00696       INTEGER :: id_src_lonlatz_size
00697       INTEGER :: id_index_size1
00698       DOUBLE PRECISION, DIMENSION (id_src_lonlatz_size)       :: grid1_corner_lat
00699       DOUBLE PRECISION, DIMENSION (id_src_lonlatz_size)       :: grid1_corner_lon
00700       DOUBLE PRECISION, DIMENSION (grid2_size, grid2_corners) :: grid2_corner_lat
00701       DOUBLE PRECISION, DIMENSION (grid2_size, grid2_corners) :: grid2_corner_lon
00702       INTEGER, DIMENSION(grid2_size)                          :: ida_nbsrccells_pertgtpt
00703       INTEGER, DIMENSION(id_index_size1,grid1_corners)        :: ida_index_array
00704       INTEGER, DIMENSION(id_index_size1)                      :: ida_srcepio_add
00705       INTEGER :: id_epio_id   ! EPIO Id
00706       INTEGER :: id_interp_id ! Interpolation Id
00707       INTEGER :: id_idim      ! Dimension concerned with the current interpolation
00708       INTEGER :: num_wts      ! Number of weights for 2D conservative remapping
00709       INTEGER :: id_err
00710     end subroutine prismtrs_remap_conserv
00711 
00712 !=======
00713  
00714     subroutine prismtrs_deallocate (id_err)
00715       Integer, Intent (Out) :: id_err
00716     end subroutine prismtrs_deallocate
00717 
00718 !=======
00719 
00720     subroutine prismtrs_resize_remap_vars(increment, id_epio_id, num_wts)
00721       INTEGER, INTENT(in) :: increment, id_epio_id, num_wts
00722     end subroutine prismtrs_resize_remap_vars
00723 
00724 !=======
00725 
00726     subroutine prismtrs_intersection(location,intrsct_lat,intrsct_lon,lcoinc, &
00727                              beglat, beglon, endlat, endlon, begseg, &
00728                              lbegin, lrevers, &
00729                              num_srch_cells, id_nbcorners, &
00730                              srch_corner_lat, srch_corner_lon, srch_add)
00731       INTEGER, INTENT(in) :: num_srch_cells, id_nbcorners
00732       DOUBLE PRECISION, DIMENSION(id_nbcorners, num_srch_cells), INTENT(in) ::
00733          srch_corner_lat, srch_corner_lon
00734       INTEGER, DIMENSION(num_srch_cells), INTENT(in) :: srch_add
00735       LOGICAL, INTENT(in) :: lbegin, lrevers 
00736       DOUBLE PRECISION, INTENT(in) :: beglat, beglon, endlat, endlon
00737       DOUBLE PRECISION, dimension(2), intent(inout) :: begseg 
00738       INTEGER, INTENT(out) :: location 
00739       LOGICAL, INTENT(out) :: lcoinc
00740       DOUBLE PRECISION, intent(out) ::  intrsct_lat, intrsct_lon
00741     end subroutine prismtrs_intersection
00742 
00743 !=======
00744 
00745     subroutine prismtrs_line_integral(lcl_weights, & 
00746                              in_phi1, in_phi2, theta1, theta2, &
00747                              grid1_lon, grid2_lon, num_wts) 
00748       DOUBLE PRECISION, INTENT(in) ::  in_phi1, in_phi2, theta1, theta2,  
00749          grid1_lon, grid2_lon 
00750       INTEGER, INTENT(in) :: num_wts 
00751       DOUBLE PRECISION, DIMENSION(2*num_wts), INTENT(out) ::  lcl_weights 
00752     end subroutine prismtrs_line_integral
00753 
00754 !=======
00755 
00756     subroutine prismtrs_loop (id_err)
00757       Integer, Intent (Out) :: id_err
00758     end subroutine prismtrs_loop
00759 
00760 !=======
00761 
00762     subroutine prismtrs_pole_intersection(location, &
00763                       intrsct_lat,intrsct_lon,lcoinc,lthresh, &
00764                       beglat, beglon, endlat, endlon, begseg, lrevers, &
00765                       num_srch_cells, id_nbcorners, &
00766                       srch_corner_lat, srch_corner_lon, srch_add)
00767 
00768       INTEGER, INTENT(in) :: num_srch_cells, id_nbcorners
00769       DOUBLE PRECISION, DIMENSION(id_nbcorners, num_srch_cells), INTENT(in) ::
00770            srch_corner_lat, srch_corner_lon
00771       INTEGER, DIMENSION(num_srch_cells), INTENT(in) :: srch_add
00772       DOUBLE PRECISION, INTENT(in) ::  beglat, beglon, endlat, endlon 
00773       DOUBLE PRECISION, DIMENSION(2), INTENT(inout) ::  begseg 
00774       LOGICAL, INTENT(in) :: lrevers   
00775 !
00776       INTEGER, INTENT(inout) :: location 
00777       LOGICAL, INTENT(out) :: lcoinc
00778       LOGICAL, INTENT(inout) :: lthresh
00779       DOUBLE PRECISION, intent(out) ::  intrsct_lat, intrsct_lon
00780     end subroutine prismtrs_pole_intersection
00781 
00782 !=======
00783 
00784     subroutine prismtrs_set_src_epio_dble(ida_loop, id_err)
00785       USE PSMILe_common
00786       INTEGER, DIMENSION(PSMILe_trans_Header_length), INTENT (IN) :: ida_loop
00787       INTEGER, INTENT (Out)            :: id_err 
00788     end subroutine prismtrs_set_src_epio_dble
00789 
00790     subroutine prismtrs_set_src_epio_real(ida_loop, id_err)
00791       USE PSMILe_common
00792       INTEGER, DIMENSION(PSMILe_trans_Header_length), INTENT (IN) :: ida_loop
00793       INTEGER, INTENT (Out)            :: id_err 
00794     end subroutine prismtrs_set_src_epio_real
00795 
00796     subroutine prismtrs_set_tgt_epio_dble(ida_loop, id_err)
00797       USE PSMILe_common
00798       INTEGER, DIMENSION(PSMILe_trans_Header_length), INTENT (IN) :: ida_loop
00799       INTEGER, INTENT (Out)            :: id_err 
00800     end subroutine prismtrs_set_tgt_epio_dble
00801 
00802     subroutine prismtrs_set_tgt_epio_real(ida_loop, id_err)
00803       USE PSMILe_common
00804       INTEGER, DIMENSION(PSMILe_trans_Header_length), INTENT (IN) :: ida_loop
00805       INTEGER, INTENT (Out)            :: id_err 
00806     end subroutine prismtrs_set_tgt_epio_real
00807 
00808 !=======
00809 
00810     subroutine prismtrs_set_epio_trans(id_process_global_rank, id_err)
00811       INTEGER, INTENT (IN)             :: id_process_global_rank
00812       INTEGER, INTENT (Out)            :: id_err 
00813     end subroutine prismtrs_set_epio_trans
00814 
00815 !=======
00816 
00817     subroutine prismtrs_store_link_cnsrv(add1, add2, lcl_weights, id_action, id_epio_id, num_wts)
00818       INTEGER, INTENT(in) :: add1, add2, id_action, id_epio_id, num_wts
00819       DOUBLE PRECISION, dimension(2*num_wts), intent(in) :: lcl_weights
00820     end subroutine prismtrs_store_link_cnsrv
00821 
00822 !=======
00823 
00824     subroutine prismtrs_get_trans_rank (id_trans_rank,             &
00825                                         id_err)
00826       INTEGER, INTENT (Out)           :: id_trans_rank
00827       INTEGER, INTENT (Out)           :: id_err
00828     end subroutine prismtrs_get_trans_rank
00829 
00830     subroutine prismtrs_get_epio_handle (id_epio_id,               &
00831                                          id_err)
00832       INTEGER, INTENT (Out)           :: id_epio_id
00833       INTEGER, INTENT (Out)           :: id_err
00834     end subroutine prismtrs_get_epio_handle
00835 
00836     subroutine prismtrs_set_triple_links(id_transient_out_id,     &
00837                                          id_transient_in_id,      &
00838                                          id_epio_id,              &
00839                                          id_err)
00840       INTEGER, INTENT (In)            :: id_transient_out_id
00841       INTEGER, INTENT (In)            :: id_transient_in_id
00842       INTEGER, INTENT (IN)            :: id_epio_id
00843       INTEGER, INTENT (Out)           :: id_err
00844     end subroutine prismtrs_set_triple_links
00845 
00846 !=======
00847 
00848     subroutine prismtrs_set_neighbors3d(id_process_global_rank,   &
00849                                         id_epio_id,               &
00850                                         id_epio_tgt_size,       &
00851                                         id_nb_neighbors,          &
00852                                         id_source_size,      &
00853                                         id_source_grid_type,      &
00854                                         id_err)
00855       INTEGER, INTENT (IN)         :: id_process_global_rank
00856       INTEGER, INTENT (IN)         :: id_epio_id
00857       INTEGER, INTENT (IN)         :: id_epio_tgt_size
00858       INTEGER, INTENT (IN)         :: id_nb_neighbors
00859       INTEGER, INTENT (IN)         :: id_source_size
00860       INTEGER, INTENT (IN)         :: id_source_grid_type
00861       INTEGER, INTENT (Out)        :: id_err
00862     end subroutine prismtrs_set_neighbors3d
00863 
00864 !=======
00865 
00866     subroutine prismtrs_set_neighbors2d1d(id_process_global_rank,   &
00867                                           id_epio_id,               &
00868                                           id_epio_field_size,       &
00869                                           id_nb_neighbors,          &
00870                                           id_err)
00871       INTEGER, INTENT (IN)         :: id_process_global_rank
00872       INTEGER, INTENT (IN)         :: id_epio_id
00873       INTEGER, INTENT (IN)         :: id_epio_field_size
00874       INTEGER, INTENT (IN)         :: id_nb_neighbors
00875       INTEGER, INTENT (Out)        :: id_err 
00876     end subroutine prismtrs_set_neighbors2d1d
00877 
00878 !=======
00879 
00880     subroutine prismtrs_mind_dble(id_process_global_rank,  &
00881                                   id_transient_out_id,     &
00882                                   id_epio_id,              &
00883                                   il_trans_out_size,       &      
00884                                   nbr_fields,              &      
00885                                   id_err)
00886       INTEGER, INTENT (In)     :: id_process_global_rank
00887       INTEGER, INTENT (In)     :: id_transient_out_id
00888       INTEGER, INTENT (IN)     :: id_epio_id
00889       INTEGER, INTENT (IN)     :: il_trans_out_size
00890       INTEGER, INTENT (IN)     :: nbr_fields
00891       INTEGER, INTENT (Out)    :: id_err 
00892     end subroutine prismtrs_mind_dble
00893 
00894 !=======
00895 
00896     subroutine prismtrs_sort_add(add1, add2, weights, num_links, num_wts)
00897       INTEGER, INTENT(in) :: num_links, num_wts
00898       INTEGER, INTENT(inout), DIMENSION(num_links) :: add1, add2
00899       DOUBLE PRECISION, INTENT(inout), DIMENSION(num_wts, num_links) :: weights
00900     end subroutine prismtrs_sort_add
00901 
00902 !=======
00903 
00904     subroutine prismtrs_mind_real(id_process_global_rank,  &
00905                                   id_transient_out_id,     &
00906                                   id_epio_id,              &
00907                                   il_trans_out_size,       &      
00908                                   nbr_fields,              &      
00909                                   id_err)
00910       INTEGER, INTENT (In)     :: id_process_global_rank
00911       INTEGER, INTENT (In)     :: id_transient_out_id
00912       INTEGER, INTENT (IN)     :: id_epio_id
00913       INTEGER, INTENT (IN)     :: il_trans_out_size
00914       INTEGER, INTENT (IN)     :: nbr_fields
00915       INTEGER, INTENT (Out)    :: id_err 
00916     end subroutine prismtrs_mind_real
00917 
00918 !=======
00919 
00920     subroutine prismtrs_mind_int(id_process_global_rank,  &
00921                                  id_transient_out_id,     &
00922                                  id_epio_id,              &
00923                                  il_trans_out_size,       &      
00924                                  nbr_fields,              &      
00925                                  id_err)
00926       INTEGER, INTENT (In)    :: id_process_global_rank
00927       INTEGER, INTENT (In)    :: id_transient_out_id
00928       INTEGER, INTENT (IN)    :: id_epio_id
00929       INTEGER, INTENT (IN)    :: il_trans_out_size
00930       INTEGER, INTENT (IN)    :: nbr_fields
00931       INTEGER, INTENT (Out)   :: id_err 
00932     end subroutine prismtrs_mind_int
00933 
00934 !=======
00935 
00936     subroutine prismtrs_interp(id_exchange_id,       &
00937                                id_epio_id,           &
00938                                id_trans_out_size,    &
00939                                dda_trans_out,        &
00940                                id_trans_in_size,     &
00941                                dda_trans_in,         &
00942                                nbr_fields,           &
00943                                id_err)
00944       INTEGER, INTENT (In)       :: id_exchange_id
00945       INTEGER, INTENT (In)       :: id_epio_id
00946       INTEGER, INTENT (In)       :: id_trans_out_size
00947       DOUBLE PRECISION,DIMENSION(id_trans_out_size),INTENT(IN) :: dda_trans_out
00948       INTEGER, INTENT (In)       :: id_trans_in_size
00949       DOUBLE PRECISION,DIMENSION(id_trans_in_size),INTENT(Out) :: dda_trans_in
00950       INTEGER, INTENT (In)       :: nbr_fields
00951       INTEGER, INTENT (Out)      :: id_err
00952     end subroutine prismtrs_interp
00953 
00954 !=======
00955 
00956     subroutine prismtrs_apply_weights(il_src_size,       &
00957                                       dda_trans_out,     &
00958                       il_tgt_size,       &
00959                       dda_trans_in,      &
00960                       ida_mask,          &
00961                       id_nb_neighbors,   &  
00962                       ida_neighbors,     &
00963                       dda_weights,       &
00964                       nbr_fields,        &
00965                       id_err)
00966       INTEGER, INTENT (IN)         :: il_src_size
00967       INTEGER, INTENT (IN)         :: nbr_fields 
00968       DOUBLE PRECISION, DIMENSION(il_src_size*nbr_fields),INTENT(IN)  :: dda_trans_out
00969       INTEGER, INTENT (IN)         :: il_tgt_size
00970       DOUBLE PRECISION, DIMENSION(il_tgt_size*nbr_fields),INTENT(Out) :: dda_trans_in
00971       INTEGER, DIMENSION(il_tgt_size), INTENT(IN) :: ida_mask
00972       INTEGER, INTENT (IN)         :: id_nb_neighbors
00973       INTEGER, DIMENSION(il_tgt_size,id_nb_neighbors),INTENT(IN):: 
00974        ida_neighbors
00975       DOUBLE PRECISION, DIMENSION(il_tgt_size,id_nb_neighbors), INTENT(IN) :: dda_weights
00976       INTEGER, INTENT (Out)        :: id_err 
00977     end subroutine prismtrs_apply_weights
00978 
00979 !=======
00980 
00981     subroutine prismtrs_apply_weights_2dcons(il_src_size,    &
00982                                              dda_trans_out,  &
00983                                              il_tgt_size,    &
00984                                              dda_trans_in,   &
00985                                              ida_mask,       &
00986                                              id_nb_links,    &  
00987                                              ida_grid1_add,  &
00988                                              ida_grid2_add,  &
00989                                              id_num_wts,     &
00990                                              dda_wts_map1,   &
00991                                              nbr_fields,     &
00992                                              id_err)
00993       INTEGER, INTENT (IN)                              :: il_src_size
00994       INTEGER, INTENT (IN)                              :: nbr_fields 
00995       DOUBLE PRECISION, DIMENSION(il_src_size*nbr_fields), INTENT(IN) :: dda_trans_out
00996       INTEGER, INTENT (IN)                              :: il_tgt_size
00997       INTEGER, DIMENSION(il_tgt_size), INTENT(IN)       :: ida_mask
00998       INTEGER, INTENT (IN)                              :: id_nb_links
00999       INTEGER, DIMENSION(id_nb_links), INTENT (IN)      :: ida_grid1_add
01000       INTEGER, DIMENSION(id_nb_links), INTENT (IN)      :: ida_grid2_add
01001       INTEGER, INTENT(in)                               :: id_num_wts
01002       DOUBLE PRECISION, DIMENSION(id_num_wts,id_nb_links), INTENT(IN) :: dda_wts_map1
01003 
01004       DOUBLE PRECISION, DIMENSION(il_tgt_size*nbr_fields), INTENT (Out) :: dda_trans_in
01005       INTEGER, INTENT (Out)               :: id_err   ! error value
01006     end subroutine prismtrs_apply_weights_2Dcons
01007 
01008 !=======   
01009 
01010     subroutine prismtrs_apply_grads ( il_src_size,      &
01011                                       dda_trans_out,    &
01012                       ida_src_mask,     &
01013                       il_tgt_size,      &
01014                       dda_trans_in,     &
01015                       ida_tgt_mask,     &
01016                       id_nb_neighbors,  &  
01017                       ida_neighbors,    &
01018                       dda_weights,      &
01019                                       nbr_fields,       &
01020                       id_err)
01021       INTEGER, INTENT (IN)         :: il_src_size
01022       INTEGER, INTENT (IN)         :: nbr_fields 
01023       DOUBLE PRECISION, DIMENSION(il_src_size*nbr_fields),INTENT(IN) :: dda_trans_out
01024       INTEGER, DIMENSION(il_src_size), INTENT(IN) :: ida_src_mask
01025       INTEGER, INTENT (IN)         :: il_tgt_size
01026       DOUBLE PRECISION, DIMENSION(il_tgt_size*nbr_fields),INTENT(Out) :: dda_trans_in
01027       INTEGER, DIMENSION(il_tgt_size), INTENT(IN) :: ida_tgt_mask
01028       INTEGER, INTENT (IN)         :: id_nb_neighbors
01029       INTEGER, DIMENSION(il_tgt_size,id_nb_neighbors),INTENT(IN):: 
01030        ida_neighbors
01031       DOUBLE PRECISION, DIMENSION(il_tgt_size,id_nb_neighbors), INTENT(IN) :: dda_weights
01032       INTEGER, INTENT (Out)        :: id_err 
01033     end subroutine prismtrs_apply_grads
01034     
01035 !=======
01036 
01037     subroutine prismtrs_target_real(id_process_global_rank,  &
01038                                     id_transient_in_id,      &
01039                                     id_epio_id,              &
01040                                     nbr_fields,              &
01041                                     id_err)
01042       INTEGER, INTENT (In)       :: id_process_global_rank
01043       INTEGER, INTENT (In)       :: id_transient_in_id
01044       INTEGER, INTENT (IN)       :: id_epio_id
01045       INTEGER, INTENT (IN)       :: nbr_fields      
01046       INTEGER, INTENT (Out)      :: id_err
01047     end subroutine prismtrs_target_real
01048 
01049     subroutine prismtrs_target_dble(id_process_global_rank,  &
01050                                     id_transient_in_id,      &
01051                                     id_epio_id,              &
01052                                     nbr_fields,              &
01053                                     id_err)
01054       INTEGER, INTENT (In)       :: id_process_global_rank
01055       INTEGER, INTENT (In)       :: id_transient_in_id
01056       INTEGER, INTENT (IN)       :: id_epio_id
01057       INTEGER, INTENT (IN)       :: nbr_fields      
01058       INTEGER, INTENT (Out)      :: id_err
01059     end subroutine prismtrs_target_dble
01060 
01061     subroutine prismtrs_target_int(id_process_global_rank,  &
01062                                    id_transient_in_id,      &
01063                                    id_epio_id,              &
01064                                    nbr_fields,              &
01065                                    id_err)
01066       INTEGER, INTENT (In)      :: id_process_global_rank
01067       INTEGER, INTENT (In)      :: id_transient_in_id
01068       INTEGER, INTENT (IN)      :: id_epio_id
01069       INTEGER, INTENT (IN)      :: nbr_fields      
01070       INTEGER, INTENT (Out)     :: id_err
01071     end subroutine prismtrs_target_int
01072 
01073 !======================================================================
01074 
01075     subroutine prismtrs_distwght_weight_2d(id_src_size,         &
01076                                            dda_src_lat,         &
01077                                            dda_src_lon,         &
01078                                            ida_src_mask,        &
01079                                            id_tgt_size,         &
01080                                            dda_tgt_lat,         &
01081                                            dda_tgt_lon,         &
01082                                            ida_tgt_mask,        &
01083                                            id_nb_neighbors,     &
01084                                            ida_neighbor_index,  & 
01085                                            dda_weights,         &
01086                                            id_err)
01087       INTEGER, INTENT (IN)              :: id_src_size
01088       INTEGER, INTENT (IN)              :: id_tgt_size
01089       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lat
01090       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lon
01091       INTEGER, DIMENSION(id_src_size), INTENT (IN) :: ida_src_mask
01092       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lat
01093       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lon
01094       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01095       INTEGER, INTENT (IN)              :: id_nb_neighbors
01096       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (IN) :: ida_neighbor_index
01097       DOUBLE PRECISION, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (Out) :: dda_weights
01098       INTEGER, INTENT (Out)             :: id_err
01099     end subroutine prismtrs_distwght_weight_2d
01100 
01101     subroutine prismtrs_gauswght_weight_2d(id_src_size,         &
01102                                            dda_src_lat,         &
01103                                            dda_src_lon,         &
01104                                            ida_src_mask,        &
01105                                            id_tgt_size,         &
01106                                            dda_tgt_lat,         &
01107                                            dda_tgt_lon,         &
01108                                            ida_tgt_mask,        &
01109                                            dd_gaus_var,         &
01110                                            id_nb_neighbors,     &
01111                                            ida_neighbor_index,  & 
01112                                            dda_weights,         &
01113                                            id_err)
01114       INTEGER, INTENT (IN)              :: id_src_size
01115       INTEGER, INTENT (IN)              :: id_tgt_size
01116       DOUBLE PRECISION, DIMENSION(id_src_size)   :: dda_src_lat
01117       DOUBLE PRECISION, DIMENSION(id_src_size)   :: dda_src_lon
01118       INTEGER, DIMENSION(id_src_size), INTENT (IN) :: ida_src_mask
01119       DOUBLE PRECISION, DIMENSION(id_tgt_size)   :: dda_tgt_lat
01120       DOUBLE PRECISION, DIMENSION(id_tgt_size)   :: dda_tgt_lon
01121       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01122       DOUBLE PRECISION, INTENT (IN)     :: dd_gaus_var
01123       INTEGER, INTENT (IN)              :: id_nb_neighbors
01124       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (INOUT) :: ida_neighbor_index
01125       DOUBLE PRECISION, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (Out) :: dda_weights
01126       INTEGER, INTENT (Out)             :: id_err
01127     end subroutine prismtrs_gauswght_weight_2d
01128 
01129     subroutine prismtrs_bilinear_weight_2d(id_src_size,         &
01130                                            dda_src_lat,         &
01131                        dda_src_lon,         &
01132                        id_tgt_size,         &
01133                        dda_tgt_lat,         &
01134                        dda_tgt_lon,         &
01135                        ida_tgt_mask,        &
01136                        ida_neighbor_index,  & 
01137                        dda_weights,         &
01138                        id_err)
01139       INTEGER, INTENT (IN)            :: id_src_size
01140       INTEGER, INTENT (IN)            :: id_tgt_size
01141       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lat
01142       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lon
01143       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lat
01144       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lon
01145       INTEGER, DIMENSION(id_tgt_size), INTENT(IN) :: ida_tgt_mask
01146       INTEGER, DIMENSION(id_tgt_size,4), INTENT(IN) :: ida_neighbor_index
01147       DOUBLE PRECISION, DIMENSION(id_tgt_size,4), INTENT(Out) :: dda_weights
01148       INTEGER, INTENT (Out)           :: id_err
01149     end subroutine prismtrs_bilinear_weight_2d
01150 
01151 
01152     subroutine prismtrs_bicubic_weight_2d(id_src_size,         &
01153                                            dda_src_lat,         &
01154                        dda_src_lon,         &
01155                        id_tgt_size,         &
01156                        dda_tgt_lat,         &
01157                        dda_tgt_lon,         &
01158                        ida_tgt_mask,        &
01159                        ida_neighbor_index,  &
01160                                            ida_same_lat,        &
01161                        dda_weights,         &
01162                        id_err)
01163       INTEGER, INTENT (IN)            :: id_src_size
01164       INTEGER, INTENT (IN)            :: id_tgt_size
01165       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lat
01166       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lon
01167       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lat
01168       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lon
01169       INTEGER, DIMENSION(id_tgt_size), INTENT(IN) :: ida_tgt_mask
01170       INTEGER, DIMENSION(id_tgt_size,16), INTENT(IN) :: ida_neighbor_index
01171       INTEGER, DIMENSION(id_tgt_size), INTENT(IN) :: ida_same_lat
01172       DOUBLE PRECISION, DIMENSION(id_tgt_size,16), INTENT(Out) :: dda_weights
01173       INTEGER, INTENT (Out)           :: id_err
01174     end subroutine prismtrs_bicubic_weight_2d
01175 
01176 
01177     subroutine prismtrs_bicubic_grad_2d (  id_src_size,         &
01178                                            dda_src_lat,         &
01179                        dda_src_lon,         &
01180                        ida_src_mask,        &
01181                        id_tgt_size,         &
01182                        dda_tgt_lat,         &
01183                        dda_tgt_lon,         &
01184                        ida_tgt_mask,        &
01185                        ida_neighbor_index,  & 
01186                        dda_weights,         &
01187                        id_err)
01188       INTEGER, INTENT (IN)            :: id_src_size
01189       INTEGER, INTENT (IN)            :: id_tgt_size
01190       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lat
01191       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lon
01192       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lat
01193       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lon
01194       INTEGER, DIMENSION(id_src_size), INTENT(IN) :: ida_src_mask
01195       INTEGER, DIMENSION(id_tgt_size), INTENT(IN) :: ida_tgt_mask
01196       INTEGER, DIMENSION(id_tgt_size,16), INTENT(IN) :: ida_neighbor_index
01197       DOUBLE PRECISION, DIMENSION(id_tgt_size,16), INTENT(Out) :: dda_weights
01198       INTEGER, INTENT (Out)           :: id_err
01199     end subroutine prismtrs_bicubic_grad_2d
01200 
01201 
01202     subroutine prismtrs_linear_weight_for_2d1d(id_src_size,         &
01203                                                dda_src_z,           &
01204                            id_tgt_size,         &
01205                            dda_tgt_z,           &
01206                            ida_tgt_mask,        &
01207                            id_nb_neighbors,     & 
01208                            ida_neighbor_index,  &
01209                            dda_weights,         &
01210                            id_err)
01211       INTEGER, INTENT (IN)                     :: id_src_size
01212       INTEGER, INTENT (IN)                     :: id_tgt_size
01213       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_z
01214       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_z
01215       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01216       INTEGER, INTENT (IN)                     :: id_nb_neighbors
01217       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT(INOUT) :: 
01218      ida_neighbor_index
01219       DOUBLE PRECISION, DIMENSION(id_tgt_size, id_nb_neighbors),INTENT (InOut)::
01220      dda_weights
01221       INTEGER, INTENT (Out)                    :: id_err
01222     end subroutine prismtrs_linear_weight_for_2d1d
01223 
01224     subroutine prismtrs_distwght_weight_2d1d(id_src_size,         &
01225                                              dda_src_lat,         &
01226                                              dda_src_lon,         &
01227                                              dda_src_z,           &
01228                                              ida_src_mask,        &
01229                                              id_tgt_size,         &
01230                                              dda_tgt_lat,         &
01231                                              dda_tgt_lon,         &
01232                                              dda_tgt_z,           &
01233                                              ida_tgt_mask,        &
01234                                              id_nb_neighbors,     &
01235                                              ida_neighbor_index,  & 
01236                                              dda_weights,         &
01237                                              id_err)
01238       INTEGER, INTENT (IN)                :: id_src_size
01239       INTEGER, INTENT (IN)                :: id_tgt_size
01240       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lat
01241       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lon
01242       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_z
01243       INTEGER, DIMENSION(id_src_size), INTENT (IN) :: ida_src_mask
01244       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lat
01245       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lon
01246       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_z
01247       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01248       INTEGER, INTENT (IN) :: id_nb_neighbors
01249       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (InOut) :: ida_neighbor_index
01250       DOUBLE PRECISION, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (Out) :: dda_weights
01251       INTEGER, INTENT (Out)               :: id_err
01252     end subroutine prismtrs_distwght_weight_2d1d
01253 
01254     subroutine prismtrs_bilinear_weight_2d1d(id_src_size,         &
01255                                              dda_src_lat,         &
01256                                              dda_src_lon,         &
01257                                              dda_src_z,           &
01258                                              id_tgt_size,         &
01259                                              dda_tgt_lat,         &
01260                                              dda_tgt_lon,         &
01261                                              dda_tgt_z,           &
01262                                              ida_neighbor_index,  & 
01263                                              dda_weights,         &
01264                                              id_err)
01265       INTEGER, INTENT (IN)                     :: id_src_size
01266       INTEGER, INTENT (IN)                     :: id_tgt_size
01267       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lat
01268       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lon
01269       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_z
01270       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lat
01271       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lon
01272       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_z
01273       INTEGER, DIMENSION(id_tgt_size,10), INTENT(INOUT) :: ida_neighbor_index
01274       DOUBLE PRECISION, DIMENSION(id_tgt_size,8), INTENT (Out) :: dda_weights
01275       INTEGER, INTENT (Out)               :: id_err
01276     end subroutine prismtrs_bilinear_weight_2d1d
01277 
01278 
01279     subroutine prismtrs_distwght_weight_3d(id_src_size,         &
01280                                            dda_src_lat,         &
01281                                            dda_src_lon,         &
01282                                            dda_src_z,           &
01283                                            ida_src_mask,        &
01284                                            id_tgt_size,         &
01285                                            dda_tgt_lat,         &
01286                                            dda_tgt_lon,         &
01287                                            dda_tgt_z,           &
01288                                            ida_tgt_mask,        &
01289                                            id_nb_neighbors,     &
01290                                            ida_neighbor_index,  & 
01291                                            dda_weights,         &
01292                                            id_err)
01293       INTEGER, INTENT (IN)              :: id_src_size
01294       INTEGER, INTENT (IN)              :: id_tgt_size
01295       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lat
01296       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lon
01297       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_z
01298       INTEGER, DIMENSION(id_src_size), INTENT (IN) :: ida_src_mask
01299       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lat
01300       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lon
01301       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_z
01302       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01303       INTEGER, INTENT (IN)              :: id_nb_neighbors
01304       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (IN) :: ida_neighbor_index
01305       DOUBLE PRECISION, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (Out) :: dda_weights
01306       INTEGER, INTENT (Out)             :: id_err
01307     end subroutine prismtrs_distwght_weight_3d
01308 
01309     subroutine prismtrs_gauswght_weight_3d(id_src_size,         &
01310                                            dda_src_lat,         &
01311                                            dda_src_lon,         &
01312                                            dda_src_z,           &
01313                                            ida_src_mask,        &
01314                                            id_tgt_size,         &
01315                                            dda_tgt_lat,         &
01316                                            dda_tgt_lon,         &
01317                                            dda_tgt_z,           &
01318                                            ida_tgt_mask,        &
01319                                            dd_gaus_var,         &
01320                                            id_nb_neighbors,     &
01321                                            ida_neighbor_index,  & 
01322                                            dda_weights,         &
01323                                            id_err)
01324       INTEGER, INTENT (IN)              :: id_src_size
01325       INTEGER, INTENT (IN)              :: id_tgt_size
01326       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lat
01327       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_lon
01328       DOUBLE PRECISION, DIMENSION(id_src_size)  :: dda_src_z
01329       INTEGER, DIMENSION(id_src_size), INTENT (IN) :: ida_src_mask
01330       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lat
01331       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_lon
01332       DOUBLE PRECISION, DIMENSION(id_tgt_size)  :: dda_tgt_z
01333       INTEGER, DIMENSION(id_tgt_size), INTENT (IN) :: ida_tgt_mask
01334       DOUBLE PRECISION, INTENT (IN)     :: dd_gaus_var
01335       INTEGER, INTENT (IN)              :: id_nb_neighbors
01336       INTEGER, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (IN) :: ida_neighbor_index
01337       DOUBLE PRECISION, DIMENSION(id_tgt_size,id_nb_neighbors), INTENT (Out) :: dda_weights
01338       INTEGER, INTENT (Out)             :: id_err
01339     end subroutine prismtrs_gauswght_weight_3d
01340 
01341     subroutine prismtrs_trilinear_weight(id_src_size,         &
01342                                          dda_src_lat,         &
01343                                          dda_src_lon,         &
01344                                          dda_src_z,           &
01345                                          id_tgt_size,         &
01346                                          dda_tgt_lat,         &
01347                                          dda_tgt_lon,         &
01348                                          dda_tgt_z,           &
01349                                          ida_tgt_mask,        &
01350                                          ida_neighbor_index,  & 
01351                                          dda_weights,         &
01352                                          id_err)
01353       INTEGER, INTENT (IN)                     :: id_src_size
01354       INTEGER, INTENT (IN)                     :: id_tgt_size
01355       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lat
01356       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_lon
01357       DOUBLE PRECISION, DIMENSION(id_src_size) :: dda_src_z
01358       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lat
01359       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_lon
01360       DOUBLE PRECISION, DIMENSION(id_tgt_size) :: dda_tgt_z
01361       INTEGER, DIMENSION(id_tgt_size), INTENT(IN)   :: ida_tgt_mask
01362       INTEGER, DIMENSION(id_tgt_size,8), INTENT(IN) :: ida_neighbor_index
01363       DOUBLE PRECISION, DIMENSION(id_tgt_size,8), INTENT(Out) :: dda_weights
01364       INTEGER, INTENT (Out)           :: id_err
01365     end subroutine prismtrs_trilinear_weight
01366 
01367 !======================================================================
01368 
01369     subroutine prismdrv_get_smioc_file_name(id_comp_id,       &
01370                                             cda_file_name,    &
01371                                             id_file_name_len, &
01372                                             id_err)
01373       INTEGER, INTENT (In)                :: id_comp_id
01374       CHARACTER(LEN=256), INTENT (Out)    :: cda_file_name
01375       INTEGER, INTENT (Out)               :: id_file_name_len
01376       INTEGER, INTENT (Out)               :: id_err
01377     end subroutine prismdrv_get_smioc_file_name
01378 
01379 !======================================================================
01380 
01381 subroutine prismtrs_enqueue_in_field_dble(field, field_size, exchange_id, ierror)
01382    integer, intent(in)                   :: field_size
01383    double precision, intent(in)          :: field(field_size)
01384    integer, intent(in)                   :: exchange_id
01385    integer, intent(out)                  :: ierror
01386 end subroutine prismtrs_enqueue_in_field_dble
01387 
01388 subroutine prismtrs_enqueue_in_field_real(field, field_size, exchange_id, ierror)
01389    integer, intent(in)                   :: field_size
01390    real, intent(in)                      :: field(field_size)
01391    integer, intent(in)                   :: exchange_id
01392    integer, intent(out)                  :: ierror
01393 end subroutine prismtrs_enqueue_in_field_real
01394 
01395 subroutine prismtrs_enqueue_in_field_int(field, field_size, exchange_id, ierror)
01396    integer, intent(in)                   :: field_size
01397    integer, intent(in)                   :: field(field_size)
01398    integer, intent(in)                   :: exchange_id
01399    integer, intent(out)                  :: ierror
01400 end subroutine prismtrs_enqueue_in_field_int
01401 
01402 subroutine prismtrs_dequeue_in_field_dble(field_size, exchange_id, ierror)
01403    integer, intent(in)       :: field_size
01404    integer, intent(in)       :: exchange_id
01405    integer, intent(out)      :: ierror
01406 end subroutine prismtrs_dequeue_in_field_dble
01407 
01408 subroutine prismtrs_dequeue_in_field_real(field_size, exchange_id, ierror)
01409    integer, intent(in)       :: field_size
01410    integer, intent(in)       :: exchange_id
01411    integer, intent(out)      :: ierror
01412 end subroutine prismtrs_dequeue_in_field_real
01413 
01414 subroutine prismtrs_dequeue_in_field_int(field_size, exchange_id, ierror)
01415    integer, intent(in)       :: field_size
01416    integer, intent(in)       :: exchange_id
01417    integer, intent(out)      :: ierror
01418 end subroutine prismtrs_dequeue_in_field_int
01419 
01420 subroutine prismtrs_enqueue_glob_sum_dble(global_sum, nbr_fields, exchange_id, ierror)
01421    integer, intent(in)          :: nbr_fields
01422    double complex, intent(in)   :: global_sum(nbr_fields)
01423    integer, intent(in)          :: exchange_id
01424    integer, intent(out)         :: ierror
01425 end subroutine prismtrs_enqueue_glob_sum_dble
01426 
01427 subroutine prismtrs_enqueue_glob_sum_int(global_sum, nbr_fields, exchange_id, ierror)
01428    integer, intent(in)  :: nbr_fields
01429    integer, intent(in)  :: global_sum(nbr_fields) 
01430    integer, intent(in)  :: exchange_id
01431    integer, intent(out) :: ierror
01432 end subroutine prismtrs_enqueue_glob_sum_int
01433 
01434 subroutine prismtrs_dequeue_glob_sum_dble(nbr_fields, exchange_id, ierror)
01435    integer, intent(in)  :: nbr_fields
01436    integer, intent(in)  :: exchange_id
01437    integer, intent(out) :: ierror
01438 end subroutine prismtrs_dequeue_glob_sum_dble
01439 
01440 subroutine prismtrs_dequeue_glob_sum_int(nbr_fields, exchange_id, ierror)
01441    integer, intent(in)  :: nbr_fields
01442    integer, intent(in)  :: exchange_id
01443    integer, intent(out) :: ierror
01444 end subroutine prismtrs_dequeue_glob_sum_int
01445 
01446 subroutine prismdrv_init_drv_exchange(exchange_id)
01447    integer, intent(in) :: exchange_id
01448 end subroutine prismdrv_init_drv_exchange
01449 
01450 !======================================================================
01451   END INTERFACE
01452 
01453 END MODULE PRISMDrv

Generated on 18 Mar 2011 for Oasis4 by  doxygen 1.6.1