prismtrs_set_src_epio_real.F90

Go to the documentation of this file.
00001 !------------------------------------------------------------------------
00002 ! Copyright 2006-2010, CERFACS, Toulouse, France.
00003 ! Copyright 2006-2010, NEC High Performance Computing, Duesseldorf, Germany.
00004 ! All rights reserved. Use is subject to OASIS4 license terms.
00005 !-----------------------------------------------------------------------
00006 !BOP
00007 !
00008 ! !ROUTINE: PRISMTrs_Set_src_epio_real
00009 !
00010 ! !INTERFACE
00011 subroutine prismtrs_set_src_epio_real(ida_loop, id_err)
00012 !
00013 ! !USES:
00014 !
00015   USE PRISMDrv, dummy_interface => PRISMTrs_Set_src_epio_real
00016 !
00017   IMPLICIT NONE
00018 !
00019 ! !PARAMETERS:
00020 !
00021   INTEGER, DIMENSION(PSMILe_trans_Header_length), INTENT (IN) :: ida_loop
00022 !
00023 ! ida_loop(2) : global rank of the source psmile process sending the info
00024 ! ida_loop(6) : epio id
00025 ! ida_loop(4) : source component id
00026 ! ida_loop(5) : source process id
00027 ! ida_loop(7) : source epio size 
00028 ! ida_loop(8) : size of compact lat/lon/z arrays
00029 ! ida_loop(9) : PSMILe_3D 
00030 ! ida_loop(10): indicates if the mask will be received or not
00031 !
00032 ! ! RETURN VALUE
00033 !
00034   INTEGER, INTENT (Out)               :: id_err   ! error value
00035 
00036 ! !DESCRIPTION
00037 ! Subroutine "PRISMTrs_Set_src_epio_real" insures the reception of the 
00038 ! informations about the epio sent by a model through the PSMILe.
00039 !
00040 ! !REVISED HISTORY
00041 !   Date      Programmer   Description
00042 ! ----------  ----------   -----------
00043 ! 01/12/2003  D. Declat    Creation from prismdrv_trs_set_epio_info
00044 ! 05/10/2006  S. Valcke    Revised for corner reception
00045 ! EOP
00046 !----------------------------------------------------------------------
00047 ! $Id: prismtrs_set_src_epio_real.F90 2685 2010-10-28 14:05:10Z coquart $
00048 ! $Author: coquart $
00049 !----------------------------------------------------------------------
00050 !
00051 ! 0. Local declarations
00052 !
00053   CHARACTER(LEN=len_cvs_string), SAVE  :: mycvs = 
00054      '$Id: prismtrs_set_src_epio_real.F90 2685 2010-10-28 14:05:10Z coquart $'
00055 !
00056 ! received in ida_loop
00057 !
00058   INTEGER :: il_process_global_rank, il_epio_id, il_src_comp_id
00059   INTEGER :: il_src_process
00060   INTEGER :: il_epio_size, il_lonlatz_size
00061   INTEGER :: il_src_mask, il_dimtype
00062 
00063 ! Auxiliary variables
00064 !
00065   INTEGER                            :: il_status(MPI_STATUS_SIZE)
00066 !
00067   INTEGER, PARAMETER  :: nerrp = 2
00068   INTEGER             :: ierrp (nerrp)
00069 !
00070 !----------------------------------------------------------------------
00071 !
00072 #ifdef VERBOSE
00073   PRINT *, '| | | Enter PRISMTrs_Set_src_epio_real'
00074   call psmile_flushstd
00075 #endif
00076 !
00077 ! Put received argument in local integer variables
00078   il_process_global_rank = ida_loop(2)
00079   il_epio_id             = ida_loop(6)
00080   il_src_comp_id         = ida_loop(4)
00081   il_src_process         = ida_loop(5)
00082   il_epio_size           = ida_loop(7)
00083   il_lonlatz_size        = ida_loop(8)
00084   il_dimtype             = ida_loop(9)
00085   il_src_mask            = ida_loop(10)
00086 !
00087 ! 0. Check if the epio structure is allocated and Set epio general information
00088 !
00089 ! 0.1. Check allocation
00090   IF (Number_of_Epios_allocated == 0) THEN
00091       Number_of_Epios_allocated = Number_of_Epios_allocated + 8
00092       ALLOCATE (Drv_Epios(Number_of_Epios_allocated), STAT = id_err)
00093   END IF
00094   IF (il_epio_id > Number_of_Epios_allocated) THEN
00095       PRINT *, '| | | il_epio_id greater then Number_of_Epios_allocated'
00096       call psmile_abort 
00097   END IF
00098 !
00099 ! 0.2. Set information
00100   Drv_Epios(il_epio_id)%epio_id = il_epio_id
00101   Drv_Epios(il_epio_id)%trans_rank = Appl%rank
00102   Drv_Epios(il_epio_id)%gaussred_stride = 0.5*il_lonlatz_size
00103 !
00104 ! 1. Reception of the different vectors
00105 !
00106 #ifdef VERBOSE
00107   print*, '| | | Reception of source ccordinates for EPIO :',il_epio_id,&
00108            '| | | from global source process :',il_process_global_rank, 'size :', &
00109            il_epio_size
00110   call psmile_flushstd
00111 #endif
00112 
00113 
00114 ! 1.2. Reception of the lat, lon, z and mask
00115 !
00116   ALLOCATE(Drv_Epios(il_epio_id)%src_lat_pointer_real(1:il_lonlatz_size), &
00117        stat = id_err)
00118   IF (id_err > 0) THEN
00119      ierrp (1) = id_err
00120      ierrp (2) = il_lonlatz_size
00121      id_err = PRISM_Error_Alloc
00122 
00123      call psmile_error_common ( id_err, 'Src_lat_pointer_real', &
00124           ierrp, 2, __FILE__, __LINE__ )
00125      RETURN
00126   ENDIF
00127 
00128   ALLOCATE(Drv_Epios(il_epio_id)%src_lon_pointer_real(1:il_lonlatz_size), &
00129        stat = id_err)
00130   IF (id_err > 0) THEN
00131      ierrp (1) = id_err
00132      ierrp (2) = il_lonlatz_size
00133      id_err = PRISM_Error_Alloc
00134 
00135      call psmile_error_common ( id_err, 'Src_lon_pointer_real', &
00136           ierrp, 2, __FILE__, __LINE__ )
00137      RETURN
00138   ENDIF
00139 
00140   ALLOCATE(Drv_Epios(il_epio_id)%src_z_pointer_real(1:il_lonlatz_size), &
00141        stat = id_err)
00142   IF (id_err > 0) THEN
00143      ierrp (1) = id_err
00144      ierrp (2) = il_lonlatz_size
00145      id_err = PRISM_Error_Alloc
00146 
00147      call psmile_error_common ( id_err, 'Src_z_pointer_real', &
00148           ierrp, 2, __FILE__, __LINE__ )
00149      RETURN
00150   ENDIF
00151 
00152   ALLOCATE(Drv_Epios(il_epio_id)%src_mask_pointer(1:il_epio_size), &
00153        stat = id_err)
00154   IF (id_err > 0) THEN
00155      ierrp (1) = id_err
00156      ierrp (2) = il_epio_size
00157      id_err = PRISM_Error_Alloc
00158 
00159      call psmile_error_common ( id_err, 'Src_msk_pointer', &
00160           ierrp, 2, __FILE__, __LINE__ )
00161      RETURN
00162   ENDIF
00163 
00164   CALL MPI_Recv (Drv_Epios(il_epio_id)%src_lat_pointer_real, &
00165      il_lonlatz_size, MPI_Real, &
00166      il_process_global_rank, 1, comm_drv_trans, il_status, id_err)
00167   Drv_Epios(il_epio_id)%src_lat_pointer_real(:) = &
00168      Drv_Epios(il_epio_id)%src_lat_pointer_real(:)*real_deg2rad
00169   CALL MPI_Recv (Drv_Epios(il_epio_id)%src_lon_pointer_real, & 
00170      il_lonlatz_size, MPI_Real, &
00171      il_process_global_rank, 2, comm_drv_trans, il_status, id_err)
00172   Drv_Epios(il_epio_id)%src_lon_pointer_real(:) = &
00173      Drv_Epios(il_epio_id)%src_lon_pointer_real(:)*real_deg2rad
00174   CALL MPI_Recv (Drv_Epios(il_epio_id)%src_z_pointer_real, &
00175      il_lonlatz_size, MPI_Real, &
00176      il_process_global_rank, 3, comm_drv_trans, il_status, id_err)
00177   IF (il_src_mask > 0) THEN
00178       CALL MPI_Recv (Drv_Epios(il_epio_id)%src_mask_pointer, &
00179          il_epio_size, MPI_Integer, &
00180          il_process_global_rank, 4, comm_drv_trans, il_status, id_err)
00181   ELSE
00182        Drv_Epios(il_epio_id)%src_mask_pointer(:) = 1
00183   END IF
00184 
00185 #ifdef VERBOSE
00186   PRINT *, &
00187      '| | | | Set the EPIOS latitudes, longitudes and z'
00188   call psmile_flushstd
00189 #endif
00190 
00191 !
00192 ! 3. Set the general epio information
00193 !
00194   Drv_Epios(il_epio_id)%src_comp_id = il_src_comp_id
00195   Drv_Epios(il_epio_id)%src_process = il_src_process
00196 
00197 !
00198 ! 4. Set the arrays information
00199 !
00200   Drv_Epios(il_epio_id)%src_coord_type = PRISM_Real
00201   Drv_Epios(il_epio_id)%src_size = il_epio_size 
00202   Drv_Epios(il_epio_id)%src_lonlatz_size = il_lonlatz_size
00203 !
00204 #ifdef VERBOSE  
00205   PRINT *, '| | | Quit PRISMTrs_Set_src_epio_real '
00206   call psmile_flushstd
00207 #endif
00208 
00209 END SUBROUTINE PRISMTrs_Set_src_epio_real
00210 
00211 
00212 
00213 
00214 
00215 
00216 

Generated on 18 Mar 2011 for Oasis4 by  doxygen 1.6.1