nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
! OpenACC Runtime Library Definitions.
|
|
|
|
|
2020-01-01 12:51:42 +01:00
|
|
|
! Copyright (C) 2014-2020 Free Software Foundation, Inc.
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
|
|
|
! Contributed by Tobias Burnus <burnus@net-b.de>
|
|
|
|
! and Mentor Embedded.
|
|
|
|
|
|
|
|
! This file is part of the GNU Offloading and Multi Processing Library
|
|
|
|
! (libgomp).
|
|
|
|
|
|
|
|
! Libgomp is free software; you can redistribute it and/or modify it
|
|
|
|
! under the terms of the GNU General Public License as published by
|
|
|
|
! the Free Software Foundation; either version 3, or (at your option)
|
|
|
|
! any later version.
|
|
|
|
|
|
|
|
! Libgomp is distributed in the hope that it will be useful, but WITHOUT ANY
|
|
|
|
! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS
|
|
|
|
! FOR A PARTICULAR PURPOSE. See the GNU General Public License for
|
|
|
|
! more details.
|
|
|
|
|
|
|
|
! Under Section 7 of GPL version 3, you are granted additional
|
|
|
|
! permissions described in the GCC Runtime Library Exception, version
|
|
|
|
! 3.1, as published by the Free Software Foundation.
|
|
|
|
|
|
|
|
! You should have received a copy of the GNU General Public License and
|
|
|
|
! a copy of the GCC Runtime Library Exception along with this program;
|
|
|
|
! see the files COPYING3 and COPYING.RUNTIME respectively. If not, see
|
|
|
|
! <http://www.gnu.org/licenses/>.
|
|
|
|
|
|
|
|
! Wrapper functions will be built from openacc.f90. We use a separate file
|
|
|
|
! here, because for using ../../openacc.f90, implementations are required for
|
|
|
|
! all the functions that it wraps, which we currently don't provide, so linking
|
|
|
|
! would fail.
|
|
|
|
|
|
|
|
module openacc_kinds
|
|
|
|
use iso_fortran_env, only: int32
|
|
|
|
implicit none
|
|
|
|
|
2019-12-17 12:19:32 +01:00
|
|
|
public
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
private :: int32
|
|
|
|
|
2019-12-17 12:19:32 +01:00
|
|
|
! When adding items, also update 'public' setting in 'module openacc' below.
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
2019-12-17 12:19:32 +01:00
|
|
|
integer, parameter :: acc_device_kind = int32
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
|
|
|
! Keep in sync with include/gomp-constants.h.
|
|
|
|
integer (acc_device_kind), parameter :: acc_device_none = 0
|
|
|
|
integer (acc_device_kind), parameter :: acc_device_default = 1
|
|
|
|
integer (acc_device_kind), parameter :: acc_device_host = 2
|
|
|
|
! integer (acc_device_kind), parameter :: acc_device_host_nonshm = 3 removed.
|
|
|
|
integer (acc_device_kind), parameter :: acc_device_not_host = 4
|
|
|
|
integer (acc_device_kind), parameter :: acc_device_nvidia = 5
|
2020-01-17 15:46:59 +01:00
|
|
|
integer (acc_device_kind), parameter :: acc_device_radeon = 8
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
2019-12-17 12:19:32 +01:00
|
|
|
end module openacc_kinds
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
|
|
|
module openacc_internal
|
|
|
|
use openacc_kinds
|
|
|
|
implicit none
|
|
|
|
|
|
|
|
interface
|
|
|
|
function acc_on_device_h (d)
|
|
|
|
import
|
|
|
|
integer (acc_device_kind) d
|
|
|
|
logical acc_on_device_h
|
|
|
|
end function
|
|
|
|
end interface
|
|
|
|
|
|
|
|
interface
|
|
|
|
function acc_on_device_l (d) &
|
|
|
|
bind (C, name = "acc_on_device")
|
|
|
|
use iso_c_binding, only: c_int
|
|
|
|
integer (c_int) :: acc_on_device_l
|
|
|
|
integer (c_int), value :: d
|
|
|
|
end function
|
|
|
|
end interface
|
2019-12-17 12:19:32 +01:00
|
|
|
end module openacc_internal
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
|
|
|
|
module openacc
|
|
|
|
use openacc_kinds
|
|
|
|
use openacc_internal
|
|
|
|
implicit none
|
|
|
|
|
2019-12-17 12:19:32 +01:00
|
|
|
private
|
|
|
|
|
|
|
|
! From openacc_kinds
|
|
|
|
public :: acc_device_kind
|
|
|
|
public :: acc_device_none, acc_device_default, acc_device_host
|
2020-01-17 15:46:59 +01:00
|
|
|
public :: acc_device_not_host, acc_device_nvidia, acc_device_radeon
|
2019-12-17 12:19:32 +01:00
|
|
|
|
nvptx offloading linking
gcc/
* config/nvptx/mkoffload.c (Kind, Vis): Remove enums.
(Token, Stmt): Remove structs.
(decls, vars, fns): Remove variables.
(alloc_comment, append_stmt, is_keyword): Remove macros.
(tokenize, write_token, write_tokens, alloc_stmt, rev_stmts)
(write_stmt, write_stmts, parse_insn, parse_list_nosemi)
(parse_init, parse_file): Remove functions.
(read_file): Accept a pointer to a length and store into it.
(process): Don't try to parse the input file, just write it out as
a string, but looking for maps. Also write out the length.
(main): Don't use "-S" to compile PTX code.
libgomp/
* oacc-ptx.h: Remove file, moving its content into...
* config/nvptx/fortran.c: ... here...
* config/nvptx/oacc-init.c: ..., here...
* config/nvptx/oacc-parallel.c: ..., and here.
* config/nvptx/openacc.f90: New file.
* plugin/plugin-nvptx.c: Don't include "oacc-ptx.h".
(link_ptx): Don't link in predefined bits of PTX code.
Co-Authored-By: Bernd Schmidt <bernds@codesourcery.com>
From-SVN: r228418
2015-10-02 21:43:41 +02:00
|
|
|
public :: acc_on_device
|
|
|
|
|
|
|
|
interface acc_on_device
|
|
|
|
procedure :: acc_on_device_h
|
|
|
|
end interface
|
|
|
|
|
|
|
|
end module openacc
|
|
|
|
|
|
|
|
function acc_on_device_h (d)
|
|
|
|
use openacc_internal, only: acc_on_device_l
|
|
|
|
use openacc_kinds
|
|
|
|
integer (acc_device_kind) d
|
|
|
|
logical acc_on_device_h
|
|
|
|
if (acc_on_device_l (d) .eq. 1) then
|
|
|
|
acc_on_device_h = .TRUE.
|
|
|
|
else
|
|
|
|
acc_on_device_h = .FALSE.
|
|
|
|
end if
|
|
|
|
end function
|