Skip to content

Commit

Permalink
Merge pull request #641 from ThePortlandGroup/nv_stage
Browse files Browse the repository at this point in the history
Pull 2018-12-17T19-02 Recent NVIDIA Changes
  • Loading branch information
sscalpone authored Dec 18, 2018
2 parents 0424a51 + 7689436 commit 87c7238
Show file tree
Hide file tree
Showing 45 changed files with 528 additions and 276 deletions.
7 changes: 1 addition & 6 deletions runtime/flang/fortDt.h
Original file line number Diff line number Diff line change
Expand Up @@ -303,14 +303,9 @@ typedef __INT_T dtype;

/*
* data type representing the number of elements passed to
* ENTF90(ALLOC04, alloc04), etc. * It's either a 64-bit type, or __INT_T
* which can be either a 64-bit or 32-bit type depending on DESC_I8
* ENTF90(ALLOC04, alloc04), etc.
*/

#if defined(TARGET_X8664)
#define __NELEM_T __INT8_T
#else
#define __NELEM_T __INT_T
#endif

#endif /*_PGHPF_TYPES_H_*/
7 changes: 2 additions & 5 deletions runtime/flang/gather_cmplx16.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -21,11 +21,8 @@

subroutine ftn_gather_cmplx16( ta, a, lda, alpha, buffer, bufrows, bufcols )
implicit none
#ifdef TARGET_X8664

integer*8 lda
#else
integer lda
#endif
complex*16 :: a( lda,* ), alpha
integer :: bufrows, bufcols
integer :: i, j, ndx, ndxsave
Expand Down
7 changes: 2 additions & 5 deletions runtime/flang/gather_cmplx8.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -21,11 +21,8 @@

subroutine ftn_gather_cmplx8( ta, a, lda, alpha, buffer, bufrows, bufcols )
implicit none
#ifdef TARGET_X8664

integer*8 lda
#else
integer lda
#endif
complex*8 :: a( lda,* ), alpha
integer :: bufrows, bufcols
integer :: i, j, ndx, ndxsave
Expand Down
7 changes: 2 additions & 5 deletions runtime/flang/gather_real4.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2011-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -20,11 +20,8 @@

subroutine ftn_gather_real4( a, lda, alpha, buffer, bufrows, bufcols )
implicit none
#ifdef TARGET_X8664

integer*8 lda
#else
integer lda
#endif
real*4 :: a( lda,* ), alpha
integer :: bufrows, bufcols
integer i, j, ndx, ndxsave
Expand Down
7 changes: 2 additions & 5 deletions runtime/flang/gather_real8.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2011-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -20,11 +20,8 @@

subroutine ftn_gather_real8( a, lda, alpha, buffer, bufrows, bufcols )
implicit none
#ifdef TARGET_X8664

integer*8 lda
#else
integer lda
#endif
real*8 :: a( lda,* ), alpha
integer :: bufrows, bufcols
integer i, j, ndx, ndxsave
Expand Down
5 changes: 0 additions & 5 deletions runtime/flang/iso_c_bind.F95
Original file line number Diff line number Diff line change
Expand Up @@ -153,11 +153,6 @@ module ISO_C_BINDING
interface operator (.ne.)
module procedure compare_ne_cfunptrs
end interface
#if defined TARGET_LINUX_X8664 || defined TARGET_LLVM_64
! added this to make the data-initializd module common block be at 32 bytes long
! maybe only needed for linux86-64
integer*8 :: __iso_bind_private_i = 11, __iso_bind_private_j = 23
#endif

contains
logical function compare_eq_cptrs(a,b)
Expand Down
4 changes: 0 additions & 4 deletions runtime/flang/miscsup_com.c
Original file line number Diff line number Diff line change
Expand Up @@ -4833,11 +4833,7 @@ ENTF90(SPACINGD, spacingd)(__REAL8_T *d)

#ifndef DESC_I8

#if defined(TARGET_X8664)
typedef __INT8_T SZ_T;
#else
typedef __INT4_T SZ_T;
#endif

#undef _MZERO
#define _MZERO(n, t) \
Expand Down
11 changes: 2 additions & 9 deletions runtime/flang/mvmul_cmplx16.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -19,22 +19,15 @@

subroutine ftn_mvmul_cmplx16( ta, tb, m, k, alpha, a, lda, b, beta, c )
implicit none
#ifdef TARGET_X8664

integer*8 :: m, k, lda
#else
integer :: m, k, lda
#endif
complex*16 :: alpha, beta
complex*16, dimension( lda, * ) :: a
complex*16, dimension( * ) :: b, c
integer :: ta, tb
! Local variables

#ifdef TARGET_X8664
integer*8 :: i, j, kk
#else
integer :: i, j, kk
#endif
complex*16 :: temp

! print *, "#### In mvmul ####"
Expand Down
11 changes: 2 additions & 9 deletions runtime/flang/mvmul_cmplx8.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -19,22 +19,15 @@

subroutine ftn_mvmul_cmplx8( ta, tb, m, k, alpha, a, lda, b, beta, c )
implicit none
#ifdef TARGET_X8664

integer*8 :: m, k, lda
#else
integer :: m, k, lda
#endif
complex*8 :: alpha, beta
complex*8, dimension( lda, * ) :: a
complex*8, dimension( * ) :: b, c
integer :: ta, tb
! Local variables

#ifdef TARGET_X8664
integer*8 :: i, j, kk
#else
integer :: i, j, kk
#endif
complex*8 :: temp

! print *, "#### In mvmul ####"
Expand Down
11 changes: 2 additions & 9 deletions runtime/flang/mvmul_real4.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -20,22 +20,15 @@

subroutine ftn_mvmul_real4( ta, m, k, alpha, a, lda, b, beta, c )
implicit none
#ifdef TARGET_X8664

integer*8 :: m, k, lda
#else
integer :: m, k, lda
#endif
real*4 :: alpha, beta
real*4, dimension( lda, * ) :: a
real*4, dimension( * ) :: b, c
integer :: ta
! Local variables

#ifdef TARGET_X8664
integer*8 :: i, j, kk
#else
integer :: i, j, kk
#endif
real*4 :: temp

if( ta .eq. 0 )then ! normally oriented a matrix
Expand Down
11 changes: 2 additions & 9 deletions runtime/flang/mvmul_real8.F95
Original file line number Diff line number Diff line change
@@ -1,5 +1,5 @@
!
! Copyright (c) 2017, NVIDIA CORPORATION. All rights reserved.
! Copyright (c) 2012-2018, NVIDIA CORPORATION. All rights reserved.
!
! Licensed under the Apache License, Version 2.0 (the "License");
! you may not use this file except in compliance with the License.
Expand All @@ -20,22 +20,15 @@

subroutine ftn_mvmul_real8( ta, m, k, alpha, a, lda, b, beta, c )
implicit none
#ifdef TARGET_X8664

integer*8 :: m, k, lda
#else
integer :: m, k, lda
#endif
real*8 :: alpha, beta
real*8, dimension( lda, * ) :: a
real*8, dimension( * ) :: b, c
integer :: ta
! Local variables

#ifdef TARGET_X8664
integer*8 :: i, j, kk
#else
integer :: i, j, kk
#endif
real*8 :: temp

if( ta .eq. 0 )then ! normally oriented a matrix
Expand Down
19 changes: 1 addition & 18 deletions runtime/flang/pgf90_mmul_cmplx16.h
Original file line number Diff line number Diff line change
Expand Up @@ -17,20 +17,15 @@
!
! Global variables
!
#ifdef TARGET_X8664
integer*8 :: mra, ncb, kab, lda, ldb, ldc
#else
integer :: mra, ncb, kab, lda, ldb, ldc
#endif
complex*16, dimension( lda, * )::a
complex*16, dimension( ldb, * )::b
complex*16, dimension( ldc, * )::c
complex*16 :: alpha, beta, one = 1.0
character*1 :: ca, cb
!
! local variables
!
#ifdef TARGET_X8664
!
integer*8 :: colsa, rowsa, rowsb, colsb
integer*8 :: i, j, jb, k, ak, bk, jend
integer*8 :: ar, ar_sav, ac, ac_sav, br, bc
Expand All @@ -41,18 +36,6 @@
integer*8 :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer*8 :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer*8 :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#else
integer :: colsa, rowsa, rowsb, colsb
integer :: i, j, jb, k, ak, bk, jend
integer :: ar, ar_sav, ac, ac_sav, br, bc
integer :: ndxa, ndxasav
integer :: ndxb, ndxbsav, ndxb0, ndxb1, ndxb2, ndxb3
integer :: colachunk, colachunks, colbchunk, colbchunks
integer :: rowchunk, rowchunks
integer :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#endif
integer :: ta, tb
complex*16 :: temp, temp0, temp1, temp2, temp3
real*8 :: temprr0, temprr1, temprr2, temprr3
Expand Down
19 changes: 1 addition & 18 deletions runtime/flang/pgf90_mmul_cmplx8.h
Original file line number Diff line number Diff line change
Expand Up @@ -17,20 +17,15 @@
!
! Global variables
!
#ifdef TARGET_X8664
integer*8 :: mra, ncb, kab, lda, ldb, ldc
#else
integer :: mra, ncb, kab, lda, ldb, ldc
#endif
complex*8, dimension( lda, * )::a
complex*8, dimension( ldb, * )::b
complex*8, dimension( ldc, * )::c
complex*8 :: alpha, beta, one = 1.0
character*1 :: ca, cb
!
! local variables
!
#ifdef TARGET_X8664
!
integer*8 :: colsa, rowsa, rowsb, colsb
integer*8 :: i, j, jb, k, ak, bk, jend
integer*8 :: ar, ar_sav, ac, ac_sav, br, bc
Expand All @@ -41,18 +36,6 @@
integer*8 :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer*8 :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer*8 :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#else
integer :: colsa, rowsa, rowsb, colsb
integer :: i, j, jb, k, ak, bk, jend
integer :: ar, ar_sav, ac, ac_sav, br, bc
integer :: ndxa, ndxasav
integer :: ndxb, ndxbsav, ndxb0, ndxb1, ndxb2, ndxb3
integer :: colachunk, colachunks, colbchunk, colbchunks
integer :: rowchunk, rowchunks
integer :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#endif
integer :: ta, tb
complex*8 :: temp, temp0, temp1, temp2, temp3
real*4 :: temprr0, temprr1, temprr2, temprr3
Expand Down
17 changes: 0 additions & 17 deletions runtime/flang/pgf90_mmul_real4.h
Original file line number Diff line number Diff line change
Expand Up @@ -21,11 +21,7 @@
!
! Global variables
!
#ifdef TARGET_X8664
integer*8 :: mra, ncb, kab, lda, ldb, ldc
#else
integer :: mra, ncb, kab, lda, ldb, ldc
#endif
real*4, dimension( lda, * )::a
real*4, dimension( ldb, * )::b
real*4, dimension( ldc, * )::c
Expand All @@ -34,7 +30,6 @@
!
! local variables
!
#ifdef TARGET_X8664
integer*8 :: colsa, rowsa, rowsb, colsb
integer*8 :: i, j, jb, k, ak, bk, jend
integer*8 :: ar, ar_sav, ac, ac_sav, br, bc
Expand All @@ -45,18 +40,6 @@
integer*8 :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer*8 :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer*8 :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#else
integer :: colsa, rowsa, rowsb, colsb
integer :: i, j, jb, k, ak, bk, jend
integer :: ar, ar_sav, ac, ac_sav, br, bc
integer :: ndxa, ndxasav
integer :: ndxb, ndxbsav, ndxb0, ndxb1, ndxb2, ndxb3
integer :: colachunk, colachunks, colbchunk, colbchunks
integer :: rowchunk, rowchunks
integer :: colsb_chunk, colsb_chunks, colsb_strt, colsb_end
integer :: colsa_chunk, colsa_chunks, colsa_strt, colsa_end
integer :: bufr, bufr_sav, bufca, bufca_sav, bufcb, bufcb_sav
#endif
real*4 :: temp, temp0, temp1, temp2, temp3
real*4 :: bufatemp, bufbtemp
real*8 :: time_start, time_end, ttime, all_time
Expand Down
Loading

0 comments on commit 87c7238

Please sign in to comment.