Quantcast
Channel: Intel® Software - Intel® Advisor
Viewing all 178 articles
Browse latest View live

Parallelization (where and how to start?!)

$
0
0

Dear All,

I analyzed my code using adviser recently and this is a snapshot of the code performance. I am including the portion of the code which causes tremendous slow down here. Can someone give me a couple of hints and examples to start correcting the code?! 

adviser analysis screenshot!

 

 

 

 

 

Source code : 

2473            !$OMP PARALLEL default(none) &    36.706s    11.29%            
2474            !$OMP private(i,j,n,k,kk)    & !! indice for Do loop                    
2475            !$OMP private(p11,p12,p13,p14,p21,p22,p23,p24) &                    
2476            !$OMP private(p31,p32,p33,p34,p41,p42,p43,p44) &                    
2477            !$OMP private(c11,c12,c13,c14,c21,c22,c23,c24) &                    
2478            !$OMP private(c31,c32,c33,c34,c41,c42,c43,c44) &                    
2479            !$OMP private(cs11,cs12,cs13,cs14,ci21,ci22,ci23,ci24) &                    
2480            !$OMP private(cl31,cl32,cl33,cl34,ce41,ce42,ce43,ce44) &                    
2481            !$OMP private(PHIC051,PHIC052,PHIC053,PHIC054)         &                    
2482            !$OMP private(PSI11,PSI12,PSI13,PSI14)                 &                    
2483            !$OMP private(APK1,APK2,APK3,APK4)                     &                            
2484            !$OMP private(ph,pdx,pdy,pc,pd,ome_nkk,ome_kkk)  &                    
2485            !$OMP private(pxxk,pxxkk,pxxp)                   &                       
2486            !$OMP private(del_psum1,result,result1,TIME)     &                            
2487            !$OMP private(ick,msn,nop,pkk,psum1,psum22,ptot) &                    
2488            !$OMP private(pxxary,pxxn)                       &                                   
2489            !$OMP shared(csn_s,dt,dx,epsgb,epsk,epsl,epss,gc3s,gc6s5,gcu_l) &                    
2490            !$OMP shared(gcu_s,gsn_l,gsn_s,l0l,l0s,l1l,l1s,l2l,ml,ms,omegb) &                    
2491            !$OMP shared(omek,omel,omes)                      &                                 
2492            !$OMP shared(weight,eptime,eptime1,freq,zi,ei,kb) &                                
2493            !$OMP shared(ZEKT,EKT,EPQ)                        &                     
2494            !$OMP shared(am,ck,cn,dfk,eps,eps_kkk,eps_nkk,fk,fn) &                    
2495            !$OMP shared(ome,pa,pb)                              &                    
2496            !$OMP shared(CS05I,CS05J,CE05I,CE05J,CI05I,CI05J,CL05I,CL05J) &  !! Input outside from parallel zone                    
2497            !$OMP shared(SUMIMC,NNN,NNN1,aa)                         &       !! Input outside from parallel zone                    
2498            !$OMP shared(ce,ci,cl,cs,DDDI,DDDJ,PHI05I,PHI05J,SSSI,SSSJ) &    !! Input outside from parallel zone                    
2499            !$OMP shared(APV1,APV2,APV3,APV4,APV11,APV21,APV31,APV41)   &                    
2500            !$OMP shared(c1,phi1,c2,phi2,psi,Exc,Eyc,Ex,Ey)                     
2501            !$OMP Do                    
2502                        
2503            DO I=0, IG, 1            0.961s    0.19%    
2504                DO J=0, JG, 1                    
2505                        
2506                    !***** CALCULATE NEXT PHI VALUE *****                    
2507                    NOP=0                    
2508                        
2509                    DO N=1,NPP    0.072s    0.02%    0.472s    0.09%    
2510                        IF (PHI1(N,I,J).GT.0.0) THEN    0.032s    0.01%            
2511                            MSN(N)=1                    
2512                            PXXARY(N)=(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1) &    0.040s    0.01%            Divisions
2513                            +PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)    0.042s    0.01%            
2514                                            
2515                        ELSEIF (PHI1(N,I,J).EQ.0.0.AND.PHI1(N,I-1,J).GT.0.0) THEN    0.146s    0.04%    0.961s    0.19%    
2516                            MSN(N)=1                    
2517                            PXXARY(N)=(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1) &                    
2518                            +PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)                    
2519                                            
2520                        ELSEIF (PHI1(N,I,J).EQ.0.0.AND.PHI1(N,I,J-1).GT.0.0) THEN    0.070s    0.02%            
2521                            MSN(N)=1                    
2522                            PXXARY(N)=(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1) &                    
2523                            +PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)    0.008s    0.00%            
2524                                            
2525                        ELSEIF (PHI1(N,I,J).EQ.0.0.AND.PHI1(N,I+1,J).GT.0.0) THEN    0.034s    0.01%            
2526                            MSN(N)=1                    
2527                            PXXARY(N)=(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1) &                    
2528                            +PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)                    
2529                                            
2530                        ELSEIF (PHI1(N,I,J).EQ.0.0.AND.PHI1(N,I,J+1).GT.0.0) THEN    0.070s    0.02%            
2531                            MSN(N)=1                    
2532                            PXXARY(N)=(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1) &                    
2533                            +PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)                    
2534                        ELSE                    
2535                            MSN(N)=0                    
2536                            PXXARY(N)=0.0    0.030s    0.01%            
2537                        ENDIF                    
2538                        
2539                        PHI2(N,I,J)=PHI1(N,I,J) ! only phi in interface region will be updated.    0.118s    0.04%            
2540                        NOP=NOP+MSN(N)          ! number of coexisting phases at a grid (i,j).    0.108s    0.03%            Type Conversions
2541                    END DO                    
2542                                        
2543                    !********************************************************************************                    

2545                        

2546    108             IF(NOP.GE.2) THEN                    
2547                        ICK=0                    
2548                        
2549                        DO N=1, NPP                    
2550                            IF(MSN(N).EQ.1) THEN    0.062s    0.02%    0.110s    0.02%    
2551                                PXXN=PXXARY(N)  !(PHI1(N,I+1,J)+PHI1(N,I-1,J)+PHI1(N,I,J+1)+PHI1(N,I,J-1)-4.0*PHI1(N,I,J))/(DX*DX)    0.060s    0.02%            
2552                        
2553                                IF(N.EQ.1) THEN                    
2554                                    CN = CS(I,J)                    
2555                                    FN = FS(CN)    0.024s    0.01%            
2556                                ELSEIF(N.EQ.NPP) THEN                    
2557                                    CN = CL(I,J)                    
2558                                    FN = FL(CN)                    
2559                                ELSEIF(N.GE.NPPK.AND.N.LT.NPP) THEN                    
2560                                    CN = CI(I,J)    0.032s    0.01%            
2561                                    FN = FI(CN)    0.064s    0.02%            
2562                                ELSE                    
2563                                    CN = CE(I,J)    0.012s    0.00%            
2564                                    FN = FE(CN)    0.054s    0.02%            
2565                                ENDIF                    
2566                        
2567                                PTOT = 0.0    18.852s    5.80%            
2568                        
2569                                DO K=1, NPP                    
2570                                    IF(K.NE.N.AND.MSN(K).EQ.1) THEN    1.304s    0.40%    173.496s    34.85%    
2571                                        PXXK=PXXARY(K)   !(PHI1(K,I+1,J)+PHI1(K,I-1,J)+PHI1(K,I,J+1)+PHI1(K,I,J-1)-4.0*PHI1(K,I,J))/(DX*DX)      0.148s    0.05%            
2572                                        PXXP=PXXK-PXXN    0.092s    0.03%            
2573                                   
2574                                        IF(K.EQ.1) THEN    0.430s    0.13%            
2575                                            CK = CS(I,J)                    
2576                                            FK = FS(CK)    0.080s    0.02%            Divisions
2577                                            DFK = DFS(CK)    0.034s    0.01%            Divisions
2578                                        ELSEIF(K.EQ.NPP) THEN                    
2579                                            CK = CL(I,J)    0.038s    0.01%            
2580                                            FK = FL(CK)    0.209s    0.06%            Divisions
2581                                            DFK = DFL(CK)    0.130s    0.04%            Divisions
2582                                        ELSEIF(K.GE.NPPK.AND.K.LT.NPP) THEN                    
2583                                            CK = CI(I,J)    0.164s    0.05%            
2584                                            FK = FI(CK)    0.826s    0.25%            Divisions
2585                                            DFK = DFI(CK)    0.431s    0.13%            Divisions
2586                                        ELSE                    
2587                                            CK = CE(I,J)    0.195s    0.06%            
2588                                            FK = FE(CK)    0.554s    0.17%            Divisions
2589                                            DFK = DFE(CK)    0.372s    0.11%            Divisions
2590                                        ENDIF                    
2591                                          
2592                                        IF((N.EQ.NPP).OR.(K.EQ.NPP)) THEN    0.080s    0.02%            
2593                                            EPS(I,J)=EPSL    0.022s    0.01%            
2594                                            OME(I,J)=OMEL    0.008s    0.00%            
2595                                            AM(I,J)=ML                    
2596                                        ELSEIF((N.EQ.1).OR.(K.EQ.1)) THEN                    
2597                                            EPS(I,J)=EPSS    0.008s    0.00%            
2598                                            OME(I,J)=OMES    0.010s    0.00%            
2599                                            AM(I,J)=MS    0.008s    0.00%            
2600                                        elseif(((n.ge.2.and.n.lt.nppk).and.(k.ge.nppk.and.k.lt.npp-1)).or. &    0.350s    0.11%            
2601                                        ((k.ge.2.and.k.lt.nppk).and.(n.ge.nppk.and.n.lt.npp-1))) then    0.030s    0.01%            
2602                                            EPS(I,J)=EPSK    0.172s    0.05%            
2603                                            OME(I,J)=OMEK    0.242s    0.07%            
2604                                            AM(I,J)=MS    0.186s    0.06%            
2605                                        elseif(((n.ge.2.and.n.lt.nppk).and.(k.ge.nppk.and.k.lt.npp-1)).or. &    0.060s    0.02%            
2606                                        ((k.ge.2.and.k.lt.nppk).and.(n.ge.nppk.and.n.lt.npp-1))) then    0.010s    0.00%            
2607                                            EPS(I,J)=EPSK                    
2608                                            OME(I,J)=OMEK                    
2609                                            AM(I,J)=MS                    
2610                                        elseif((n.ge.2.and.n.lt.nppk).or.(k.ge.2.and.k.lt.nppk)) then    0.012s    0.00%            
2611                                            EPS(I,J)=EPSK                    
2612                                            OME(I,J)=OMEK                    
2613                                            AM(I,J)=MS                    
2614                                        ELSE                    
2615                                            EPS(I,J)=EPSGB    0.199s    0.06%            
2616                                            OME(I,J)=OMEGB    0.028s    0.01%            
2617                                            AM(I,J)=MS    0.030s    0.01%            
2618                                        ENDIF                    
2619                                        
2620                                        PKK=0.0    0.028s    0.01%            
2621                                        DO KK=1, NPP    0.016s    0.00%            
2622                                            IF(KK.NE.N.AND.KK.NE.K.AND.MSN(KK).EQ.1.AND.KK.NE.NPP) THEN    14.918s    4.59%    163.803s    32.90%    
2623                                                PXXKK=(PHI1(KK,I+1,J)+PHI1(KK,I-1,J)+PHI1(KK,I,J+1) &    19.070s    5.87%            Divisions
2624                                                +PHI1(KK,I,J-1)-4.*PHI1(KK,I,J))/(DX*DX)      ! Laplacian phi    11.133s    3.42%            
2625                                                IF(N.EQ.NPP) THEN    0.737s    0.23%            
2626                                                    OME_NKK=OMEL    0.266s    0.08%            
2627                                                    EPS_NKK=EPSL    0.472s    0.15%            
2628                                                ELSEIF(N.EQ.1) THEN                    
2629                                                    OME_NKK=OMES    0.430s    0.13%            
2630                                                    EPS_NKK=EPSS    0.250s    0.08%            
2631                                                ELSEIF(N.EQ.NPP-1) THEN                    
2632                                                    OME_NKK=OMEGB    34.930s    10.74%            
2633                                                    EPS_NKK=EPSGB    4.891s    1.50%            
2634                                                ELSEIF(N.GE.NPPK.AND.N.LT.NPP-1) THEN                    
2635                                                    OME_NKK=OMEGB                    
2636                                                    EPS_NKK=EPSGB                    
2637                                                ELSE                    
2638                                                    OME_NKK=OMEGB                    
2639                                                    EPS_NKK=EPSGB                    
2640                                                ENDIF                    
2641                        
2642                                                IF(K.EQ.NPP) THEN    0.865s    0.27%            
2643                                                    OME_KKK=OMEL    0.036s    0.01%            
2644                                                    EPS_KKK=EPSL    0.908s    0.28%            
2645                                                ELSEIF(K.EQ.1) THEN                    
2646                                                    OME_KKK=OMES    0.008s    0.00%            
2647                                                    EPS_KKK=EPSS    0.448s    0.14%            
2648                                                ELSEIF(K.EQ.NPP-1) THEN                    
2649                                                    OME_KKK=OMEGB    1.208s    0.37%            
2650                                                    EPS_KKK=EPSGB    39.524s    12.16%            
2651                                                ELSEIF(K.GE.NPPK.AND.K.LT.NPP-1) THEN                    
2652                                                    OME_KKK=OMEGB                    
2653                                                    EPS_KKK=EPSGB                    
2654                                                ELSE                    
2655                                                    OME_KKK=OMEGB                    
2656                                                    EPS_KKK=EPSGB                    
2657                                                ENDIF                    
2658                        
2659                                                PKK=PKK+0.5*(EPS_NKK**2.-EPS_KKK**2.)*PXXKK &    7.826s    2.41%            
2660                                                +(OME_NKK-OME_KKK)*PHI1(KK,I,J)    4.963s    1.53%            
2661                                            ENDIF                    
2662                                        ENDDO    21.098s    6.49%            
2663                                       
2664                                        PA(I,J)=0.5*(EPS(I,J)**2.0)*PXXP                       ! Epsilon term    0.240s    0.07%            
2665                                        PB(I,J)=OME(I,J)*(PHI1(K,I,J)-PHI1(N,I,J))             ! Omega term    0.482s    0.15%            
2666                        
2667                                        PH=1.0                    
2668                                        PC=PH*(FN-FK-(CN-CK)*DFK)                              ! Free energy term    0.414s    0.13%            
2669                        
2670                                        PDX=(8.0*(PSI(I+1,J)-PSI(I-1,J))-(PSI(I+2,J)-PSI(I-2,J)))/(12.*DX)                    
2671                                        PDY=(8.0*(PSI(I,J+1)-PSI(I,J-1))-(PSI(I,J+2)-PSI(I,J-2)))/(12.*DX)                    
2672                        
2673                                        !PD=sigmac(i,j)*sqrt(PDX**2.+PDY**2.)/freq                    
2674                                        PD=sqrt((SSSI(I,J)*PDX)**2.+(SSSJ(I,J)*PDY)**2.)/freq*EPTIME*0.0                    
2675                        
2676                                        ! PTOT=PTOT-AM*DT*(PA+PB+PC+PD+PKK)                      ! Summation value                    
2677                                       
2678                                        PTOT(I,J)=PTOT(I,J)-AM(I,J)*DT*(PA(I,J)+PB(I,J)+PC+PD+PKK)               ! summation value    1.736s    0.53%            
2679                                       
2680                                    ENDIF                    
2681                                ENDDO    0.706s    0.22%            
2682                                             
2683                                PHI2(N,I,J)=PHI1(N,I,J)+(2.0/NOP)*PTOT(I,J)   ! phi value at the next time step    0.092s    0.03%            Divisions; Type Conversions
2684                                 
2685                                IF(PHI2(N,I,J).GT.1.0) THEN    0.019s    0.01%            
2686                                    PHI2(N,I,J)=1.0                    
2687                                    ICK=1                    
2688                                    EXIT                    
2689                                ELSEIF(PHI2(N,I,J).LT.0.0) THEN                    
2690                                    PHI2(N,I,J)=0.0                    
2691                                    ICK=2                    
2692                                    EXIT                    
2693                                ENDIF                    
2694                                                    
2695                                !********** CHECKING FOR NaN  ***********                    
2696                                        
2697                                !IF (ieee_is_nan(C1(I,J)) THEN                    
2698                                result1=(PHI2(N,I,J))                    
2699                                IF (ISNAN(result1))THEN    0.050s    0.02%            
2700                                    WRITE(*,*)'********** NaN value in PHI PDE!! ************'                    
2701                                    WRITE(*,*) '# of coexisting phases at this point is:',NOP                    
2702                                    WRITE(*,*) 'I,J,N,NNN,PHI2(N,I,J)'                    
2703                                    WRITE(*,*) I,J,N,NNN,result1                    
2704                                    WRITE(*,*)                    
2705                                    WRITE(*,*) 'CS(I,J),CI(I,J),CE(I,J),CL(I,J)'                    
2706                                    WRITE(*,*) CS(I,J),CI(I,J),CE(I,J),CL(I,J)                    
2707                                    WRITE(*,*)                    
2708                                    WRITE(*,*) 'PB contents: PHI1(K,I,J),PHI1(N,I,J)'                    
2709                                    WRITE(*,"(4F12.2)") PHI1(K,I,J),PHI1(N,I,J)                    
2710                                    WRITE(*,*)                    
2711                                    WRITE(*,*) 'CL(I,J),FL(CK),DFL(CK)'                    
2712                                    WRITE(*,*) CL(I,J),FL(CK),DFL(CK)                    
2713                                    WRITE(*,*)                    
2714                                    WRITE(*,*) 'CS(I,J),FS(CK),DFS(CK)'                    
2715                                    WRITE(*,*) CS(I,J),FS(CK),DFS(CK)                    
2716                                    WRITE(*,*)                    
2717                                    WRITE(*,*) 'CI(I,J),FI(CK),DFI(CK)'                    
2718                                    WRITE(*,*) CI(I,J),FI(CK),DFI(CK)                    
2719                                    WRITE(*,*) '********** NaN value in Field equation! ************'                    
2720                                    pause                    
2721                        
2722                                ENDIF                    
2723                        
2724                            ENDIF                    
2725                            
2726                        ENDDO    0.048s    0.01%            
2727                                                                  
2729                        IF(ICK.EQ.1) THEN                    
2730                            DO K=1,NPP    0.020s    0.01%    0.008s    0.00%    
2731                                IF(K.NE.N) PHI2(K,I,J)=0.0                    
2732                            END DO                    
2733                        ELSEIF(ICK.EQ.2) THEN    ! recalculate phi2 after phi2(N,I,J)=0 and msn(N)=0 (hopefully assuming phi1(N,I,J)=0)                    
2734                            MSN(N)=0                    
2735                            IF(NOP.EQ.2) THEN    0.008s    0.00%            
2736                                DO K=1,NPP            0.012s    0.00%    
2737                                    IF(MSN(K).EQ.1) PHI2(K,I,J)=1.0    0.012s    0.00%            
2738                                END DO                    
2739                            ELSEIF(NOP.GT.2) THEN                    
2740                                NOP=NOP-1                    
2741                                GOTO 108                    
2742                            ENDIF                    
2743                        ENDIF                    
2744                        
2745                        !*****                                       
2749                        PSUM1=0.0    0.012s    0.00%            Unpacks
2750                        DO N=1,NPP            0.012s    0.00%    
2751                            PSUM1=PSUM1+PHI2(N,I,J)    0.012s    0.00%            
2752                        END DO                    
2753                        IF(PSUM1.NE.1.0) THEN                    
2754                            DEL_PSUM1=1.0-PSUM1                    
2755                        
2756                            psum22=0.0                    
2757                            do n=1,npp            0.034s    0.01%    
2758                                if(msn(n).eq.1) then    0.018s    0.01%            
2759                                    psum22=psum22+0.5-dabs(phi2(n,i,j)-0.5)    0.016s    0.00%            
2760                                endif                    
2761                            enddo                    
2762                            DO N=1, NPP                    
2763                                IF(MSN(N).EQ.1) THEN    0.012s    0.00%    0.048s    0.01%    
2764                                    PHI2(N,I,J)=PHI2(N,I,J)+DEL_PSUM1  &    0.024s    0.01%            
2765                                    *(0.5-dabs(phi2(n,i,j)-0.5))/(psum22) !!/DFLOAT(NOP) !!*PHI2(N,I,J)/PSUM1  !!!    0.012s    0.00%            Divisions
2766                                ENDIF                    
2767                            END DO                    
2768                        ENDIF                    
2769                        
2770                    ENDIF                    
2771                        
2773                    ! PHI_i                    
2774                    P11  = PHI05I(1,I,J)    !H(PHI05I(1,I,J))       ! (I+1/2,J)    0.042s    0.01%            
2775                    P12  = PHI05I(1,I-1,J)  !H(PHI05I(1,I-1,J))     ! (I-1/2,J)    0.030s    0.01%            
2776                    P13  = PHI05J(1,I,J)    !H(PHI05J(1,I,J))       ! (I,J+1/2)                    
2777                    P14  = PHI05J(1,I,J-1)  !H(PHI05J(1,I,J-1))     ! (I,J-1/2)                    
2778                        
2779                    P41  = PHI05I(4,I,J)    !H(PHI05I(4,I,J))       ! (I+1/2,J)                    
2780                    P42  = PHI05I(4,I-1,J)  !H(PHI05I(4,I-1,J))     ! (I-1/2,J)                    
2781                    P43  = PHI05J(4,I,J)    !H(PHI05J(4,I,J))       ! (I,J+1/2)    0.008s    0.00%            
2782                    P44  = PHI05J(4,I,J-1)  !H(PHI05J(4,I,J-1))     ! (I,J-1/2)                    
2783                                 
2784                    P21  = PHI05I(2,I,J)    !H(PHI05I(2,I,J))       ! (I+1/2,J)    0.008s    0.00%            
2785                    P22  = PHI05I(2,I-1,J)  !H(PHI05I(2,I-1,J))     ! (I-1/2,J)    0.008s    0.00%            
2786                    P23  = PHI05J(2,I,J)    !H(PHI05J(2,I,J))       ! (I,J+1/2)                    
2787                    P24  = PHI05J(2,I,J-1)  !H(PHI05J(2,I,J-1))     ! (I,J-1/2)                    
2788                                            
2789                    P31  = PHI05I(3,I,J)    !H(PHI05I(3,I,J))       ! (I+1/2,J)    0.012s    0.00%            
2790                    P32  = PHI05I(3,I-1,J)  !H(PHI05I(3,I-1,J))     ! (I-1/2,J)                    
2791                    P33  = PHI05J(3,I,J)    !H(PHI05J(3,I,J))       ! (I,J+1/2)                    
2792                    P34  = PHI05J(3,I,J-1)  !H(PHI05J(3,I,J-1))     ! (I,J-1/2)    0.008s    0.00%            
2793                        
2794                    !! dC_i                    
2795                    C11 = CS(I+1,J)-CS(I,J);                    
2796                    C12 = CS(I,J)-CS(I-1,J);                    
2797                    C13 = CS(I,J+1)-CS(I,J);                    
2798                    C14 = CS(I,J)-CS(I,J-1);                    
2799                        
2800                    C41 = CE(I+1,J)-CE(I,J);                    
2801                    C42 = CE(I,J)-CE(I-1,J);                    
2802                    C43 = CE(I,J+1)-CE(I,J);                    
2803                    C44 = CE(I,J)-CE(I,J-1);                    
2804                        
2805                    C21 = CI(I+1,J)-CI(I,J);                    
2806                    C22 = CI(I,J)-CI(I-1,J)    0.012s    0.00%            
2807                    C23 = CI(I,J+1)-CI(I,J);                    
2808                    C24 = CI(I,J)-CI(I,J-1)                    
2809                        
2810                    C31 = CL(I+1,J)-CL(I,J);                    
2811                    C32 = CL(I,J)-CL(I-1,J)                    
2812                    C33 = CL(I,J+1)-CL(I,J);                    
2813                    C34 = CL(I,J)-CL(I,J-1)                    
2814                        
2815                    CS11 = CS05I(I,J); CS12 = CS05I(I-1,J)                    
2816                    CS13 = CS05J(I,J); CS14 = CS05J(I,J-1)                    
2817                        
2818                    CE41 = CE05I(I,J); CE42 = CE05I(I-1,J)                    
2819                    CE43 = CE05J(I,J); CE44 = CE05J(I,J-1)                    
2820                        
2821                    CI21 = CI05I(I,J); CI22 = CI05I(I-1,J)                    
2822                    CI23 = CI05J(I,J); CI24 = CI05J(I,J-1)                    
2823                        
2824                    CL31 = CL05I(I,J); CL32 = CL05I(I-1,J)                    
2825                    CL33 = CL05J(I,J); CL34 = CL05J(I,J-1)                    
2826                                        
2827                    ! PHI_i*C_i                    
2828                    PHIC051=P11*CS11+P21*CI21+P31*CL31+P41*CE41                    
2829                    PHIC052=P12*CS12+P22*CI22+P32*CL32+P42*CE42                    
2830                    PHIC053=P13*CS13+P23*CI23+P33*CL33+P43*CE43    0.008s    0.00%            
2831                    PHIC054=P14*CS14+P24*CI24+P34*CL34+P44*CE44    0.028s    0.01%            
2832                                        
2833                    ! dPSI                    
2834                    PSI11 = PSI(I+1,J)-PSI(I,J);    PSI12 = PSI(I,J)-PSI(I-1,J)                    
2835                    PSI13 = PSI(I,J+1)-PSI(I,J);     PSI14 = PSI(I,J)-PSI(I,J-1)                                                              
2836                        
2837                    APK1 = DDDI(I,J)  *(P11*C11+P21*C21+P31*C31+P41*C41     &                                  
2838                    -ZEKT(I,J)*PHIC051*PSI11)                            0.010s    0.00%            
2840                                 
2841                    APK2 = DDDI(I-1,J)*(P12*C12+P22*C22+P32*C32+P42*C42  &    0.024s    0.01%            
2842                    -ZEKT(I,J)*PHIC052*PSI12)                                            
2844                            
2845                    APK3 = DDDJ(I,J)  *(P13*C13+P23*C23+P33*C33+P43*C43  &                    
2846                    -zekt(I,J)*PHIC053*PSI13)                                          
2848                            
2849                    APK4 = DDDJ(I,J-1)*(P14*C14+P24*C24+P34*C34+P44*C44  &    0.020s    0.01%            
2850                    -ZEKT(I,J)*PHIC054*PSI14)                                            
2852                                        
2853                    C2(I,J) = C1(I,J)+DT*(APK1-APK2+APK3-APK4)/(DX*DX)    0.044s    0.01%            Divisions
2854                                        
2855                    !! ****** CHECKING FOR STRANGE OR NaN values *****                    
2856                    IF(C2(I,J).GE.1.0) THEN                    
2857                        WRITE(*,*) 'TIME:',TIME                    
2858                        WRITE(*,*) 'NNN,I,J, C1(I,J),C2(I,J)'                    
2859                        WRITE(*,*) NNN,I,J, C1(I,J),C2(I,J), 'C2 VALUE IS STRANGE'                    
2860                        C2(I,J)=(C2(I+1,J)+C2(I-1,J)+C2(I,J-1)+C2(I,J+1))/4                    
2861                                            
2862                        IF(PHI1(NPP,I,J).GE.0.85) C2(I,J) = 0.97                    
2863                                            
2864                        !C2(I,J) = C1(I,J)                    
2865                        !STOP                    
2866                        
2867                    ELSEIF(C2(I,J).LE.0.0) THEN                    
2868                        WRITE(*,*) 'TIME:',TIME                    
2869                        WRITE(*,*) 'NNN,I,J, C1(I,J),C2(I,J)'                    
2870                        WRITE(*,*) NNN,I,J, C1(I,J),C2(I,J), 'C2 VALUE IS STRANGE'                    
2871                        C2(I,J)=(C2(I+1,J)+C2(I-1,J)+C2(I,J-1)+C2(I,J+1))/4                    
2872                                            
2873                        IF(PHI1(NPP,I,J).GE.0.85) C2(I,J) = 0.97                    
2874                                           
2875                        !C2(I,J) = C1(I,J)                    
2876                        !STOP                    
2877                        
2878                    ENDIF                    
2879                                        
2880                    !********** CHECKING FOR NaN @ C Equation ***********                    
2881                    !IF (ieee_is_nan(C1(I,J)) THEN                    
2882                    result=(C2(I,J))                    
2883                    IF (ISNAN(result))THEN                    
2884                        WRITE(*,*) '!********** Found NaN @ C Equation *****************'                    
2885                        WRITE(*,*) 'TIME:',TIME                    
2886                        WRITE(*,*) 'I,J,NNN,result'                    
2887                        WRITE(*,*) I,J,NNN,result                    
2888                        WRITE(*,*) 'DT,DX,APK1,APK2,APK3,APK4'                    
2889                        WRITE(*,*) DT,DX,APK1,APK2,APK3,APK4                    
2890                        WRITE(*,*)                    
2891                        WRITE(*,*) 'DDDI(I,J),P11,C11,P21,C21,P31,C31,P41,C41'                    
2892                        WRITE(*,*) DDDI(I,J),P11,C11,P21,C21,P31,C31,P41,C41                    
2893                        WRITE(*,*)                    
2894                        WRITE(*,*) 'P13,C13,P23,C23,P33,C33,P43,C43'                    
2895                        WRITE(*,*) P13,C13,P23,C23,P33,C33,P43,C43                    
2896                        WRITE(*,*)                    
2897                        WRITE(*,*) 'P12,C12,P22,C22,P32,C32,P42,C42'                    
2898                        WRITE(*,*) P12,C12,P22,C22,P32,C32,P42,C42                    
2899                        WRITE(*,*)                    
2900                        WRITE(*,*) 'P14,C14,P24,C24,P34,C34,P44,C44'                    
2901                        WRITE(*,*) P14,C14,P24,C24,P34,C34,P44,C44                    
2902                        WRITE(*,*)                    
2903                        WRITE(*,*) 'PHIC051,PHIC052,PHIC053,PHIC054'                    
2904                        WRITE(*,*) PHIC051,PHIC052,PHIC053,PHIC054                    
2905                        WRITE(*,*)                    
2906                        WRITE(*,*) 'PSI11,PSI12,PSI13,PSI14'                    
2907                        WRITE(*,*) PSI11,PSI12,PSI13,PSI14                    
2908                        WRITE(*,*)                    
2909                        WRITE(*,*) 'PSI(I+1,J),PSI(I,J),PSI(I,J),PSI(I-1,J)'                    
2910                        WRITE(*,*) PSI(I+1,J),PSI(I,J),PSI(I,J),PSI(I-1,J)                    
2911                        WRITE(*,*)                     
2912                        WRITE(*,*) 'DDDI(I,J)  *(P11*C11+P21*C21+P31*C31+P41*C41'                    
2913                        WRITE(*,*) DDDI(I,J)  *(P11*C11+P21*C21+P31*C31+P41*C41)                    
2914                        WRITE(*,*) '!**************************************************'                    
2915                        
2916                        STOP                    
2917                    ENDIF                    
2918                                        
2919                ENDDO                    
2920            ENDDO                    

 

 

 


Advisor trip count file corrupted, no flops/roofline available.

$
0
0

Hi,

I use Advisor Update 2 (build 501009) installed via a Parallel Studio XE license. I was able to analyse provided examples and my own codes.

Now I have a code, fixed format Fortran compiled with ifort 17.0.2 20170213 using mpif90 after sourcing the compilervars.csh intel64 , mpivars.csh and advixe-vars.csh.

When I run, the collection log states the tripcount file is corrupted. Advisor then shows no roofline / flops data available and that I should recompile with -g, which I already do. Vtune has no problem reading performance counters and trip counts.

Regards,
Patrick

Thread Topic: 

Help Me

Join the Intel® Parallel Studio XE 2018 Beta program

$
0
0

 

We would like to invite you to participate in the Intel® Parallel Studio XE 2018 Beta program. In this beta test, you will gain early access to new features and analysis techniques. Try them out, tell us what you love and what to improve, so we can make our products better for you. 

Registration is easy. Complete the pre-beta survey, register, and download the beta software:

Intel® Parallel Studio XE 2018 Pre-Beta survey

The 2018 version brings together exciting new technologies along with improvements to Intel’s existing software development tools:

Modernize Code for Performance, Portability and Scalability on the Latest Intel® Platforms

  • Use fast Intel® Advanced Vector Extensions 512 (Intel®AVX-512) instructions on Intel® Xeon® and Intel®Xeon® Phi™ processors and coprocessors
  • Intel® Advisor - Roofline finds high impact, but under optimized loops
  • Intel® Distribution for Python* - Faster Python* applications
  • Stay up-to-date with the latest standards and IDE:
    • C++2017 draft parallelizes and vectorizes C++ easily using Parallel STL*
    • Full Fortran* 2008, Fortran 2015 draft
    • OpenMP* 5.0 draft, Microsoft Visual Studio* 2017
  • Accelerate MPI applications with Intel® Omni-Path Architecture

Flexibility for Your Needs

  • Application Snapshot - Quick answers:  Does my hybrid code need optimization?
  • Intel® VTune™ Amplifier – Profile private clouds with Docker* and Mesos* containers, Java* daemons

And much more…

For more details about this beta program, a FAQ, and What’s New, visit: Intel® Parallel Studio XE 2018 Beta page.As a highly-valued customer and beta tester, we welcome your feedback to our development teams via this program at our Online Service Center

no jit code was profiled when counting on flops

$
0
0

Hi, I'm using advisor to profile flops on knl on my application, My application use mkldnn as backend and it will generated jit code. After profiling, I found its flops is very small:~8GFlop, how ever , my application should use a lot of avx512 instructions. I found that flops of jit code(heaviest) is not count on. We should have omp.so, libmkldnn.so, dynamic code modules,. but advisor only shows omp.so, libmkldnn.so. Any help? THanks verymuch

Zone: 

Where should I put ANNOTATE_ITERATION_TASK?

$
0
0

I'm using Intel Advisor to analyze my parallel application. I have this code, which is the main loop of my program and where is spent most of the time:

       ANNOTATE_SITE_BEGIN(solve);
       for(size_t i=0; i<wrapperIndexes.size(); i++){
           const int r = wrapperIndexes[i].r;
           const int c = wrapperIndexes[i].c;
           const float val = localWrappers[wrapperIndexes[i].i].cur.at<float>(wrapperIndexes[i].r,wrapperIndexes[i].c);
           if ( (val > positiveThreshold && (isMax(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].high, r, c))) ||
                (val < negativeThreshold && (isMin(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].high, r, c))) )
              // either positive -> local max. or negative -> local min.
                ANNOTATE_ITERATION_TASK(localizeKeypoint);
                localizeKeypoint(r, c, localCurSigma[wrapperIndexes[i].i], localPixelDistances[wrapperIndexes[i].i], localWrappers[wrapperIndexes[i].i]);
       }
       ANNOTATE_SITE_END();

As you can see, `localizeKeypoint` is where most of the time the loop is spent (if you don't consider the `if` clause). I want to do a Suitability Report to estimate the gain from parallelizing the loop above. So I've written this:

       ANNOTATE_SITE_BEGIN(solve);
       for(size_t i=0; i<wrapperIndexes.size(); i++){
           const int r = wrapperIndexes[i].r;
           const int c = wrapperIndexes[i].c;
           const float val = localWrappers[wrapperIndexes[i].i].cur.at<float>(wrapperIndexes[i].r,wrapperIndexes[i].c);
           if ( (val > positiveThreshold && (isMax(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].high, r, c))) ||
                (val < negativeThreshold && (isMin(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].high, r, c))) )
              // either positive -> local max. or negative -> local min.
                ANNOTATE_ITERATION_TASK(localizeKeypoint);
                localizeKeypoint(r, c, localCurSigma[wrapperIndexes[i].i], localPixelDistances[wrapperIndexes[i].i], localWrappers[wrapperIndexes[i].i]);
       }
       ANNOTATE_SITE_END();

And the Suitability Report given an excellent 6.69x gain, as you can see here:

However, launching dependencies check, I got this problem message:
In particular see "Missing start task".

In addition, if I place `ANNOTATE_ITERATION_TASK` at the beggining of the loop, like this:

       ANNOTATE_SITE_BEGIN(solve);
       for(size_t i=0; i<wrapperIndexes.size(); i++){
            ANNOTATE_ITERATION_TASK(localizeKeypoint);
           const int r = wrapperIndexes[i].r;
           const int c = wrapperIndexes[i].c;
           const float val = localWrappers[wrapperIndexes[i].i].cur.at<float>(wrapperIndexes[i].r,wrapperIndexes[i].c);
           if ( (val > positiveThreshold && (isMax(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].high, r, c))) ||
                (val < negativeThreshold && (isMin(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].high, r, c))) )
              // either positive -> local max. or negative -> local min.
                localizeKeypoint(r, c, localCurSigma[wrapperIndexes[i].i], localPixelDistances[wrapperIndexes[i].i], localWrappers[wrapperIndexes[i].i]);
       }
       ANNOTATE_SITE_END();

    
The gain is horrible:

Am I doing something wrong?

Why Missing start task error is returned?

$
0
0

I have this code:

   ANNOTATE_SITE_BEGIN(solve);
   for(size_t i=0; i<wrapperIndexes.size(); i++){
       ANNOTATE_ITERATION_TASK(localizeKeypoint);
       const int r = wrapperIndexes[i].r;
       const int c = wrapperIndexes[i].c;
       const float val = localWrappers[wrapperIndexes[i].i].cur.at<float>(wrapperIndexes[i].r,wrapperIndexes[i].c);
       if ( (val > positiveThreshold && (isMax(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMax(val, localWrappers[wrapperIndexes[i].i].high, r, c))) ||
            (val < negativeThreshold && (isMin(val, localWrappers[wrapperIndexes[i].i].cur, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].low, r, c) && isMin(val, localWrappers[wrapperIndexes[i].i].high, r, c))) )
          // either positive -> local max. or negative -> local min.
            localizeKeypoint(r, c, localCurSigma[wrapperIndexes[i].i], localPixelDistances[wrapperIndexes[i].i], localWrappers[wrapperIndexes[i].i]);
   }
   ANNOTATE_SITE_END();

Which is compiled with icpc 2017 and compiler options:

 
INTEL_OPT=-O3 -simd -xCORE-AVX2 -parallel -qopenmp -fargument-noalias -ansi-alias -no-prec-div -fp-model fast=2
INTEL_PROFILE=-g -qopt-report=5 -Bdynamic -shared-intel -debug inline-debug-info -qopenmp-link dynamic -parallel-source-info=2 -ldl 

However, after running a dependency analysis, a "Missing start task" is returned:

Why this happens? 

I'm sorry, but I don't know how to attach the binary file of the application and the input image as argument, I hope that this is enough (please let me know otherwise).

Intel Advisor runs very slowly

$
0
0

I am running Intel Advisor 2017 in Visual Studio 2012. I've been able to work through the tutorial using the vec_samples example code.

However, in the code that I am actually working on, the Advisor takes a really long time to process the results of a run of a simple test harness.

This is the output from the Intel Advisor 2017 messages window:

Collection has been started.
Peak bandwidth measurement started.
Peak bandwidth measurement finished.
Collection has stopped. Application exit code:  0
Raw data has been loaded to the database, elapsed time is 0.003 seconds.
Finalizing the result took 18.101 seconds.
Collection time: 26s
Finalizing results
Finalizing the result
Clearing the database
The database has been cleared, elapsed time is 0.198 seconds.
Loading raw data to the database
Loading 'systemcollector-3664-steve-PC.sc' file
Loading '8532-1668.0.trace' file
Loading 'tripcounts_6176_0.tcs' file
Updating precomputed scalar metrics
Raw data has been loaded to the database, elapsed time is 2.395 seconds.
Processing profile metrics and debug information
Data transformations have been finished, elapsed time is 0.000 seconds.
Setting data model parameters
Resolving module symbols
Resolving information for `WS2_32.dll'
Resolving information for `MSVCR110.dll'
Resolving information for `ntmarta.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\WS2_32.dll'.
Resolving information for `ntdll.dll'
Resolving information for `GDI32.dll'
Resolving information for `MSVCR80.dll'
Resolving information for `IP2Lib64.dll'
Resolving information for `svml_dispmd.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\SYSTEM32\ntmarta.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\SYSTEM32\ntdll.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\GDI32.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\WinSxS\amd64_microsoft.vc80.crt_1fc8b3b9a1e18e3b_8.0.50727.8428_none_88dcdb0b2fb19957\MSVCR80.dll'.
Resolving information for `clr.dll'
Resolving information for `combase.dll'
Resolving information for `System.ni.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\SYSTEM32\combase.dll'.
Resolving information for `wminet_utils.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\assembly\NativeImages_v4.0.30319_64\System\9e5716401a8897f73f47ad27f58b8518\System.ni.dll'.
Resolving information for `mscorlib.ni.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\Microsoft.NET\Framework64\v4.0.30319\wminet_utils.dll'.
Resolving information for `mswsock.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\assembly\NativeImages_v4.0.30319_64\mscorlib\35a36d5faf5966eed2243f3d43f9f490\mscorlib.ni.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\mswsock.dll'.
Resolving information for `tpsstool.dll'
Warning: Cannot locate debugging symbols for file `C:\Program Files (x86)\IntelSWTools\Advisor 2017\bin64\tpsstool.dll'.
Resolving information for `KERNELBASE.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\KERNELBASE.dll'.
Resolving information for `AI2Interface.dll'
Resolving information for `clrjit.dll'
Resolving information for `mscoreei.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\Microsoft.NET\Framework64\v4.0.30319\mscoreei.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\Microsoft.NET\Framework64\v4.0.30319\clr.dll'.
Resolving information for `System.Management.ni.dll'
Resolving information for `RPCRT4.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\RPCRT4.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\assembly\NativeImages_v4.0.30319_64\System.Management\9f633e32d6de1c9d04fb2008f1e001bb\System.Management.ni.dll'.
Resolving information for dangling locations
Resolving information for `MSVCR120_CLR0400.dll'
Resolving information for `fastprox.dll'
Warning: Cannot locate debugging symbols for file `C:\Windows\SYSTEM32\MSVCR120_CLR0400.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\Microsoft.NET\Framework64\v4.0.30319\clrjit.dll'.
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\wbem\fastprox.dll'.
Resolving information for `RunUnitTestsAI2Interface.exe'
Resolving information for `KERNEL32.DLL'
Warning: Cannot locate debugging symbols for file `C:\Windows\system32\KERNEL32.DLL'.
Resolving bottom user stack information
Resolving thread name information
Resolving call target names for dynamic code
Symbol resolution has been finished, elapsed time is 51.205 seconds.
Processing profile metrics and debug information
Deferred data transformations have been finished, elapsed time is 5184.648 seconds.
Setting data model parameters
Data model parameters have been set, elapsed time is 0.345 seconds.
Precomputing frequently used data
Precomputing frequently used data
Updating precomputed scalar metrics
Precomputing frequently used data has been finished, elapsed time is 0.066 seconds.
Discarding redundant overtime data
Saving the result
Redundant overtime data has been discarded, elapsed time is 0.003 seconds.
Raw collector data has been discarded, elapsed time is 0.000 seconds.
Finalizing the result took 5376.563 seconds.
Preparing data for display of survey call tree
Resolving module symbols
Resolving bottom user stack information
Resolving thread name information
Resolving call target names for dynamic code
Precomputing frequently used data
Finalization time: 01:29:41s
Data collection processing end

 

There are a couple of steps that take 5000+ seconds.

Does anyone have any suggestions as to what is happening? Running the test again seems just as slow. Task manager shows VS running at 20% CPU.

Regards,

Steve

Isolating failure point

$
0
0

Previously I collected data on KNL system with Advisor XE (survey).  I want to change the input data set and rerun.  I also want to collect different data.   I am running this the same way - but it now fails to run.  I get a message like hthis:  advixe: Collection stopped.
advixe: Warning: The application returned a non-zero exit value.

Then more error messages.   

My run is something like this: mpirun -np 1 advixe-cl -collect survey -project-dir /<path>/RUNFILES/dirname /<path>/RUNFILES/FILES/Craft.exe  : -np 127 /path/RUNFILES/Craft.exe

 

Is there a flag I can add to trace what is going on with mpi and advisor xe?   If I understood why it was failing maybe I could modify something.  If I drop advixe and just enter:mpirun -np 1 /<path>/RUNFILES/FILES/Craft.exe  : -np 127 /path/RUNFILES/Craft.exe

the application runs just fine.   How do I trace what is happening so I can debug it?

 

 

Thread Topic: 

How-To

Update linux kernel breaks advisor 17 update 4

$
0
0

Hello,

We did an update of our RHEL kernel from (RHEL 6.8) kernel 2.6.32-642.6.2.el6.x86_64 to (RHEL 6.9) 2.6.32-696.3.2.el6.x86_64.

Using the last version of advisor update 4 

ewart@bbpviz2 ~]$ advixe-cl  --version
Intel(R) Advisor Command Line Tool
Copyright (C) 2009-2017 Intel Corporation. All rights reserved.
Intel(R) Advisor 2017 Update 4 (build 517067) Command Line Tool

 

We get the following error message on a hello word. 

[ewart@bbpviz036 learning_engine]$  advixe-cl -collect survey ./a.out 

Intel(R) Advisor Command Line Tool

Copyright (C) 2009-2017 Intel Corporation. All rights reserved.

advixe: Collection started. To stop the collection, either press CTRL-C or enter from another console window: advixe-cl -r /gpfs/bbp.cscs.ch/home/ewart/learning_engine/e000/hs001 -command stop.

advixe: Collection stopped.

advixe: Warning: The application returned a non-zero exit value.

advixe: Opening result 31 % Processing profile metrics and debug information   

advixe: Error: Error 0x4000002a (Database interface error) -- Cannot run data transformation `Add Fake Loop Data'.

advixe: Opening result 99 % done                                               

advixe: Opening result 100 % done                                              

advixe: Error: Data loading failed.

advixe: Error: Unknown error during finalization

 

 

Thread Topic: 

Bug Report

Recent Advisor problems may be caused by PIN

$
0
0

Lately, we have been getting many reports of problems with the analysis tools (Inspector, Advisor, and VTune Amplifier) caused by a problem with PIN, the tool they use to instrument software.

PIN problems can produce several types of error. One of the more common ones is
__bionic_open_tzdata_path: PIN_CRT_TZDATA not set!

If you believe you may be affected, please see this article for more information.

Intel Advisor

$
0
0

Hi,

This is my first post so I'll try to do my best to make the issue as clear as possible. I'm trying to use Intel Advisor 2017 for the first time to verify a quite simple Fortran code and I cannot get it to work. I follow the steps included in this tutorial https://software.intel.com/en-us/get-started-with-advisor-threading-advisor, and run the GUI using these lines of code:

cd /opt/intel

source advisor_2017/advixe-vars.sh

export PATH=/opt/intel/advisor_2017.1.1.486553/bin64:$PATH

cd /opt/intel/parallel_studio_xe_2017.1.043

./psxevars.sh

advixe-gui

Then I create a new project. The only thing that I change in "Project Properties" is the Application section, where I include the path to the compiled executable file. When I run the Survey analysis I get the following message: No data/Data loading failed/Error message: operation was succesful. In the Collection Log it says: Error 0x4000002a (Database interface error) -- Cannot run data transformation `Add fake loop data'. If I check what is going on in the terminal I get the following error message: path_to_application: error while loading shared libraries: libiomp5.so: cannot open shared object file: No such file or directory. I'm running this on Linux Centos 7.

Thank you for any kind of help

Best,

Andres

 

 

advice-cl hangs immediately after starting

$
0
0
I am running the vec_samples example in this release..../beta/parallel_studio_xe_2018_update1/advisor_2018.0.3.513243/
I execute the following...

advixe-cl -collect survey -project-dir ./advi -search-dir src:=./advi/vec_samples -- ./advi/vec_samples/vec_samples

It hangs right away, no top activity and no core activity.

I reran it using strace followed by command and it "seems" to get stuck here...
./advi/project_read_only.dflgadvixe", O_RDWR|O_CREAT|O_DSYNC, 0644) = 4
fcntl(4, F_SETLK, {type=F_WRLCK, whence=SEEK_SET, start=0, len=0}

when I kill it it dies like this

(removed control character)terminate called after throwing an instance of 'boost::exception_detail::clone_impl<boost::exception_detail::error_info_injector<boost::thread_resource_error> >'
  what():  boost thread: trying joining itself: Resource deadlock avoided
Process 186039 detached
 <detached ...>

 

 

Can Intel Advisor be used to assist with parallelism in Java applications?

$
0
0

Advisor supports C# which is basically just "Microsoft Java" so is it possible to use Advisor with Java programs?

Power Consumption for multiplying two 64 bit numbers

$
0
0

 

Can anyone help me to find the power consumed in an ( i7-6700 CPU@3.4 GHz, 4 cores, 8 logical processors) while multiplying two 64 bit numbers and adding two 64 bit numbers?

Is there any specific document/link where I can find that ?

Also what is the process to compute the number of clock cycles it takes for multiplying two 64 bit numbers?  I used rdtsc subroutine to get the time stamp before and after the multiplication, and then subtract them. Is it the correct way to do ? Please advise! 

Thanks 

 

DLL / No source code shown

$
0
0

Hi, we have a DLL project, which is used from an interpreter via an FFI. I compile the DLL with release options and added the /Zi and /DEBUG. So I get a .pdb file for the DLL. The DLL is compiled via a VS project using ICL. The sources are distributed over several directories, but of course, all are in the same VS project.

I pointed IA's symbol path to the PDB file. And I added the root where all our sources are.

I see this line: "Resolving information for `nlpp.dll'" which is our DLL two times. I checked the PDB file and see that the paths to our source files are all included and correct. But on the "Survey & Roofline" tab I see: modules without debug information nlpp.dll

So, how to track down where things don't fit or missing?

 


pin.exe The NTDLL!NtMapViewOfSection function jumps out of NTDLL

$
0
0

We are having a problem running Advisor, following advise found elsewhere we are trying to run this command to prove pin.exe works and getting the error below. Can anyone offer some assistance on how we go about resolving this. This is Parallel Studio XE 2018 on Windows 7 with VS2017.

thanks

pin.exe -- notepad

E: SYSCALL_INSPECTOR: The NTDLL!NtMapViewOfSection function jumps out of NTDLL, at 0x027480000. It may be hooked by a PIN-incompatible software instal
led on the system
A: Source\pin\base_w\ipc_server_windows.cpp: LEVEL_BASE::StartServer: 2216: assertion failed: res == TRUE

NO STACK TRACE AVAILABLE

Export survey page as a csv file

$
0
0

Hi,

​  From the Intel Advisor client, is it possible to export the survey page columns ( under the "Survey and Roofline" tab, where "function call sites and loops" are sorted by decreasing "self times") as a .csv file or some other text format? Being able to extract it as a .csv will enable me to use scripts to further explore this treasure trove of data efficiently. 
Thanks much in advance
Anirban

 

 

 

 

 

Intel support for OpenACC

$
0
0

The current computing landscape is spotted with a variety of computational architectures: multi-core CPUs, GPUs, many-core devices. DSPs, and FPGAs, just to name a few. It is now becoming commonplace to find not just one, but many of these different architectures within the same machine.

I was wondering if there is support for OpenACC on Intel GPU's?

I have used OpenACC on multi-core CPU's to parallelize my C++ application, and the results were very efficient

Roofline gives me a much higher performance then expected

$
0
0

Good morning,

I'm working on code optimisation. I run on  Broadwell E5-2650v4 CPUs Linux machines. I optimised the code so roofline model shows 284.38 GFLOPS of perfomance versus 35.94 GFLOPS of the previous version of optimisation. It is 7.9 times higher. However, elapsed time is only around 2 times difference. I'm not sure it is the sort of difference I should expect...I would expect that roofline model also shows me 2 times difference in performance...What there could be wrong?

I'm attaching two screenshots of roofline models built with Intel Advisor. 

Kind regards,

Sofya

 

AttachmentSize
Downloadapplication/rarroofLine.rar102.44 KB

advixe-cl How to report GFLOPs

$
0
0

I am running the Intel Advisor 2018 (build 523188) on Linux CentOS 7.4.

I am profiling a bunch of benchmarks (I want to plot them all in a single roofline plot) and I am using the command line tool (advixe-cl) to collect the survey, tripcounts and flops information for each benchmark.

However, I cannot find a way to report the measured flops (for each loop or function or even whole program) using the command line tool advixe-cl. The documentation I am looking at is found here https://software.intel.com/en-us/advisor-help-lin-command-line-interface-reference, but I think that it is not complete e.g. the option -flops-and-masks is not mentioned anywhere. Do you know if there is any way to report the measured flops via the command line interface?

Viewing all 178 articles
Browse latest View live


<script src="https://jsc.adskeeper.com/r/s/rssing.com.1596347.js" async> </script>