Ignore:
Timestamp:
11/22/12 14:54:21 (11 years ago)
Author:
dsolyga
Message:

Introduced the new subroutine moycum_index. Works the same way as moycum but make computations only on index points. Used only when scatter operation is performed. Help to reduce the computational time of ORCHIDEE. For the other models, should not change the results.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • IOIPSL/trunk/src/mathelp.f90

    r845 r1927  
    1010!- 
    1111  PRIVATE 
    12   PUBLIC :: mathop,moycum,buildop 
     12  PUBLIC :: mathop,moycum,moycum_index,buildop 
    1313!- 
    1414  INTERFACE mathop 
     
    31193119END SUBROUTINE moycum 
    31203120!=== 
     3121SUBROUTINE moycum_index( opp, px, py, pwx, nbi, ind ) 
     3122!--------------------------------------------------------------------- 
     3123!- Does time operations on index points  
     3124!--------------------------------------------------------------------- 
     3125  IMPLICIT NONE 
     3126!- 
     3127 
     3128  !! 0. Parameters and variables declaration 
     3129 
     3130  !! 0.1 Input variables 
     3131 
     3132  CHARACTER(LEN=7), INTENT(in)        :: opp  !! Operation performed 
     3133  INTEGER, INTENT(in)                 :: nbi  !! Size of index vector 
     3134  INTEGER, DIMENSION(nbi), INTENT(in) :: ind  !! Index vector 
     3135  REAL, DIMENSION(:), INTENT(in)      :: py   !! Vector containing the  
     3136                                              !! previous values of px 
     3137                                              !! Warning : due to memory  
     3138                                              !! optimization, we have 
     3139                                              !! generally SIZE(px) /= SIZE(py)   
     3140  INTEGER, INTENT(in)                 :: pwx  !! Used to calculate average value                              
     3141 
     3142  !! 0.3 Modified variables 
     3143 
     3144  REAL, DIMENSION(:), INTENT(inout)   :: px   !! Result 
     3145 
     3146  !! 0.4 Local variables 
     3147 
     3148  INTEGER :: ig                               !! Index 
     3149 
     3150!--------------------------------------------------------------------- 
     3151 
     3152  !! Perform operations only if the values of ind don't exceed the size of px  
     3153 
     3154  IF ( MAXVAL(ind) > SIZE(px) ) THEN 
     3155     CALL ipslerr(3,"moycum_index", & 
     3156          & "the index vector is out of range for px", & 
     3157          & "Indexation vector problem. We stop", " " ) 
     3158  END IF 
     3159 
     3160  IF (pwx /= 0) THEN 
     3161     IF      (opp == 'ave') THEN 
     3162        DO ig = 1,nbi 
     3163           px(ind(ig)) = (px(ind(ig))*pwx + py(ind(ig)))/REAL(pwx+1) 
     3164        END DO 
     3165     ELSE IF (opp == 't_sum') THEN 
     3166        DO ig = 1,nbi 
     3167           px(ind(ig)) = px(ind(ig)) + py(ind(ig)) 
     3168        END DO 
     3169     ELSE IF ( (opp == 'l_min').OR.(opp == 't_min') ) THEN 
     3170        DO ig = 1,nbi 
     3171           px(ind(ig)) = MIN(px(ind(ig)),py(ind(ig))) 
     3172        END DO 
     3173     ELSE IF ( (opp == 'l_max').OR.(opp == 't_max') ) THEN 
     3174        DO ig = 1,nbi 
     3175           px(ind(ig)) = MAX(px(ind(ig)),py(ind(ig))) 
     3176        END DO 
     3177     ELSE 
     3178        CALL ipslerr(3,"moycum_index",'Unknown time operation',opp,' ') 
     3179     END IF 
     3180  ELSE 
     3181    IF      (opp == 'l_min') THEN 
     3182       DO ig = 1,nbi 
     3183          px(ind(ig)) = MIN(px(ind(ig)),py(ind(ig))) 
     3184       END DO 
     3185    ELSE IF (opp == 'l_max') THEN 
     3186       DO ig = 1,nbi 
     3187          px(ind(ig)) = MAX(px(ind(ig)),py(ind(ig))) 
     3188       END DO 
     3189    ELSE 
     3190       DO ig = 1,nbi 
     3191          px(ind(ig)) = py(ind(ig)) 
     3192       END DO 
     3193    ENDIF 
     3194 END IF 
     3195 
     3196END SUBROUTINE moycum_index 
     3197 
     3198 
    31213199!----------------- 
    31223200END MODULE mathelp 
Note: See TracChangeset for help on using the changeset viewer.