-
Notifications
You must be signed in to change notification settings - Fork 1
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
1 parent
74a76cc
commit 05f615f
Showing
17 changed files
with
4,206 additions
and
1,276 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,39 @@ | ||
# 2 "asmcomp/loongarch64/CSE.ml" | ||
(**************************************************************************) | ||
(* *) | ||
(* OCaml *) | ||
(* *) | ||
(* yala <[email protected]> *) | ||
(* *) | ||
(* Copyright © 2008-2023 LOONGSON *) | ||
(* *) | ||
(* All rights reserved. This file is distributed under the terms of *) | ||
(* the GNU Lesser General Public License version 2.1, with the *) | ||
(* special exception on linking described in the file LICENSE. *) | ||
(* *) | ||
(**************************************************************************) | ||
|
||
(* CSE for the LoongArch *) | ||
|
||
open Arch | ||
open Mach | ||
open CSEgen | ||
|
||
class cse = object (_self) | ||
|
||
inherit cse_generic as super | ||
|
||
method! class_of_operation op = | ||
match op with | ||
| Ispecific(Imultaddf _ | Imultsubf _) -> Op_pure | ||
| _ -> super#class_of_operation op | ||
|
||
method! is_cheap_operation op = | ||
match op with | ||
| Iconst_int n -> n <= 0x7FFF_FFFFn && n >= -0x8000_0000n | ||
| _ -> false | ||
|
||
end | ||
|
||
let fundecl f = | ||
(new cse)#fundecl f |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,13 @@ | ||
# Supported platforms | ||
|
||
LoongArch in 64-bit mode | ||
|
||
Debian architecture name: `loongarch64` | ||
|
||
# Reference documents | ||
|
||
* Instruction set specification: | ||
- https://loongson.github.io/LoongArch-Documentation/LoongArch-Vol1-EN.html | ||
|
||
* ELF ABI specification: | ||
- https://loongson.github.io/LoongArch-Documentation/LoongArch-ELF-ABI-EN.html |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,94 @@ | ||
# 2 "asmcomp/loongarch64/arch.ml" | ||
(**************************************************************************) | ||
(* *) | ||
(* OCaml *) | ||
(* *) | ||
(* Nicolas Ojeda Bar <[email protected]> *) | ||
(* *) | ||
(* Copyright 2016 Institut National de Recherche en Informatique et *) | ||
(* en Automatique. *) | ||
(* *) | ||
(* All rights reserved. This file is distributed under the terms of *) | ||
(* the GNU Lesser General Public License version 2.1, with the *) | ||
(* special exception on linking described in the file LICENSE. *) | ||
(* *) | ||
(**************************************************************************) | ||
|
||
(* Specific operations for the Loongarch processor *) | ||
|
||
open Format | ||
|
||
(* Machine-specific command-line options *) | ||
|
||
let command_line_options = [] | ||
|
||
(* Specific operations *) | ||
|
||
type specific_operation = | ||
| Imultaddf of bool (* multiply, optionally negate, and add *) | ||
| Imultsubf of bool (* multiply, optionally negate, and subtract *) | ||
| Isqrtf (* floating-point square root *) | ||
|
||
(* Addressing modes *) | ||
|
||
type addressing_mode = | ||
| Iindexed of int (* reg + displ *) | ||
|
||
let is_immediate n = | ||
(n <= 0x7FF) && (n >= -0x800) | ||
|
||
(* Sizes, endianness *) | ||
|
||
let big_endian = false | ||
|
||
let size_addr = 8 | ||
let size_int = size_addr | ||
let size_float = 8 | ||
|
||
let allow_unaligned_access = false | ||
|
||
(* Behavior of division *) | ||
|
||
let division_crashes_on_overflow = false | ||
|
||
(* Operations on addressing modes *) | ||
|
||
let identity_addressing = Iindexed 0 | ||
|
||
let offset_addressing addr delta = | ||
match addr with | ||
| Iindexed n -> Iindexed(n + delta) | ||
|
||
(* Printing operations and addressing modes *) | ||
|
||
let print_addressing printreg addr ppf arg = | ||
match addr with | ||
| Iindexed n -> | ||
let idx = if n <> 0 then Printf.sprintf " + %i" n else "" in | ||
fprintf ppf "%a%s" printreg arg.(0) idx | ||
|
||
let print_specific_operation printreg op ppf arg = | ||
match op with | ||
| Imultaddf false -> | ||
fprintf ppf "%a *f %a +f %a" | ||
printreg arg.(0) printreg arg.(1) printreg arg.(2) | ||
| Imultaddf true -> | ||
fprintf ppf "-f (%a *f %a +f %a)" | ||
printreg arg.(0) printreg arg.(1) printreg arg.(2) | ||
| Imultsubf false -> | ||
fprintf ppf "%a *f %a -f %a" | ||
printreg arg.(0) printreg arg.(1) printreg arg.(2) | ||
| Imultsubf true -> | ||
fprintf ppf "-f (%a *f %a -f %a)" | ||
printreg arg.(0) printreg arg.(1) printreg arg.(2) | ||
| Isqrtf -> | ||
fprintf ppf "sqrtf %a" | ||
printreg arg.(0) | ||
|
||
(* Specific operations that are pure *) | ||
|
||
let operation_is_pure _ = true | ||
|
||
(* Specific operations that can raise *) | ||
|
||
let operation_can_raise _ = false |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,75 @@ | ||
# 2 "asmcomp/loongarch64/arch.mli" | ||
(**************************************************************************) | ||
(* *) | ||
(* OCaml *) | ||
(* *) | ||
(* Nicolas Ojeda Bar <[email protected]> *) | ||
(* *) | ||
(* Copyright 2016 Institut National de Recherche en Informatique et *) | ||
(* en Automatique. *) | ||
(* *) | ||
(* All rights reserved. This file is distributed under the terms of *) | ||
(* the GNU Lesser General Public License version 2.1, with the *) | ||
(* special exception on linking described in the file LICENSE. *) | ||
(* *) | ||
(**************************************************************************) | ||
|
||
(* Specific operations for the Loongarch processor *) | ||
|
||
(* Machine-specific command-line options *) | ||
|
||
val command_line_options : (string * Arg.spec * string) list | ||
|
||
(* Specific operations *) | ||
|
||
type specific_operation = | ||
| Imultaddf of bool (* multiply, optionally negate, and add *) | ||
| Imultsubf of bool (* multiply, optionally negate, and subtract *) | ||
| Isqrtf (* floating-point square root *) | ||
|
||
(* Addressing modes *) | ||
|
||
type addressing_mode = | ||
| Iindexed of int (* reg + displ *) | ||
|
||
val is_immediate : int -> bool | ||
|
||
(* Sizes, endianness *) | ||
|
||
val big_endian : bool | ||
|
||
val size_addr : int | ||
|
||
val size_int : int | ||
|
||
val size_float : int | ||
|
||
val allow_unaligned_access : bool | ||
|
||
(* Behavior of division *) | ||
|
||
val division_crashes_on_overflow : bool | ||
|
||
(* Operations on addressing modes *) | ||
|
||
val identity_addressing : addressing_mode | ||
|
||
val offset_addressing : addressing_mode -> int -> addressing_mode | ||
|
||
(* Printing operations and addressing modes *) | ||
|
||
val print_addressing : | ||
(Format.formatter -> 'a -> unit) -> addressing_mode -> | ||
Format.formatter -> 'a array -> unit | ||
|
||
val print_specific_operation : | ||
(Format.formatter -> 'a -> unit) -> specific_operation -> | ||
Format.formatter -> 'a array -> unit | ||
|
||
(* Specific operations that are pure *) | ||
|
||
val operation_is_pure : specific_operation -> bool | ||
|
||
(* Specific operations that can raise *) | ||
|
||
val operation_can_raise : specific_operation -> bool |
Oops, something went wrong.