discrete_subtype_indication. But a range is not a type.
A range is an (implementation specific) data structure defining at least the following three members: red to blue is a valid range, a null range, etc. This might be trivial for integer and floating point
literals, because these literals are of type universal_integer or universal_real and are compatible to each other. The problem comes from enumeration, which create new
ordered sets, each with own position numbers. I'll deepen this point in a later paragraph.
H downto L or L to H syntax
'range and 'reverse_range attributes
<< and >> for ranges
range keyword is already reserved in VHDL and used in: type short is range -32768 to 32767;
type ratio is range 0.0 to 1.0;
type string is array(positive range <>) of character;
subtype positive is integer range 1 to integer'high;
digit0 : integer range 0 to 9;
'range and 'reverse_range are pre-defined attribute names, containing the string "range".
Currently, VHDL's EBNF knows "ranges" as: range :: = range_attribute_name, e.g. mySignal'range(2)
simple_expression direction simple_expression, e.g. 7 downto 0
index_subtype_definition, e.g. natural range <>
discrete_subtype_indication, e.g. std_logic_vector(RegisterIndex)
| Scalar Type | Ordered Type1 | Discrete Type | Numeric Types | Has Position Number | |
|---|---|---|---|---|---|
| integer type | yes | yes | yes | yes | yes |
| enumeration type | yes | yes | yes | no | yes |
| floating type | yes | yes | no | yes | no |
| physical type | yes | yes | no | yes | yes |
to and downto.
type direction is (to, downto);
type <name> is record lowerBound : <scalar_type>; upperBound : <scalar_type>; direction : direction; end record;
range_declaration rule. So a range becomes an named "object" like a VHDL constant or type. When a range becomes an object, its no longer an
language internal intermediate data structure, which can now be (re)used e.g. in slices or constraints, be passed around, be returned, or define operators and have attributes.
So to warm-up with ranges, let's play with ranges and their range arithmetic. The range declartion syntax is inspired by the type declaration syntax.
simple_range_expression as already
known from VHDL-200x.
architecture a of e is range r_lower is 15 downto 0; -- range R_lower is range 15 downto 0; -- too many range keywords in one VHDL line range r_upper is 16 to 31; range empty1 is null; -- creates a null range (for arithmetic completeness) range empty2 is 0 downto 1; -- results in a null range (current behavior) begin -- ...;
architecture a of e is subtype t_int3 is integer range 0 to 7; subtype t_slv_8 is std_logic_vector(7 downto 0); range LowerByteRange is t_slv_8'range; -- store a subtype's range constraint in a range range UpperByteRange is LowerByteRange << 8; -- move (both) range bounds by +8 => 15 downto 8 range WordRange is LowerByteRange * 4; -- expand range by 4, lower bound is not modified => 31 downto 0 range HalfWordRange is WordRange / 2; -- split the range in equal sized parts => 15 downto 0 range DoubleWordRange1 is WordRange & WordRange; -- combine two ranges => 63 downto 0 range DoubleWordRange2 is UpperByteRange & WordRange; -- combine two ranges => 39 downto 0 range NormalizedRange is UpperByteRange'normalized; -- the range is moved so the lower bound is zero => 7 downto 0 range ReverseRange is UpperByteRange'reversed; -- reverse direction => 8 to 15 constant Bytes : integer := WordRange / t_int3'range; -- divide two range lengths => 4 signal MySignal : std_logic_vector(WordRange); -- constrain a array with a range subtype MySubType is integer range WordRange; -- constrain a type to a subtype begin lowerByte <= MySignal(LowerByteRange); -- use a range in a slice end architecture;
function func generic (range LHS); parameter (input : std_logic_vector(LHS); range RHS) return std_logic_vector is begin return input(RHS); end architecture; -- example usage: signal Registers : std_logic_vector(15 downto 0); signal output : std_logic_vector(3 downto 0); function foo is new func generic map (LHS => Registers'range); ouput <= foo(Registers, output'range);
architecture a of e is
-- 16-bit registers filled with four 3-bit status fields (S) and one error bit (E)
signal Registers : std_logic_vector(15 downto 0); -- Format: SSSE SSSE SSSE SSSE
-- a generic extract function to demonstrate many capabilities of range objects
function Extract
generic (type T; range R_MAX);
parameter (input : T(R_MAX); range Slice)
return std_logic_vector is
variable result : T(Slice);
begin
result := input(Slice);
return result;
end function;
range AllBitsRange is 3 downto 0;
range StatusRange is 0 to 3;
range StatusBitsRange is 3 downto 1;
-- a normalized ranged is a to/downto range beginning at index 0
signal Status : array(natural StatusRange'reverse) of std_logic_vector(StatusBitsRange'normalized); -- (3 downto 0) of (2 downto 0)
function GetStatus is new Extract
generic map (T => Registers'type, R_Max => Registers'range);
begin
genLoop: for i in StatusRange generate
range CurrentStatusRange is StatusBitsRange'range << (i * AllBitsRange'length);
begin
Status(i) <= GetStatus(Registers, CurrentStatusRange);
end generate;
end architecture;
<expr> (to | downto) <expr> becomes a simple range expression and will construct a range.
'low -> returns the lower bound
'high -> returns the upper bound
'left -> returns the left bound
'right -> returns the right bound
'length -> returns the length
'direction -> returns the direction
'is_ascending -> returns true if range is ascending
'is_descending -> returns true if range is descending
'is_nullrange -> returns true if range is a null range / empty
'ascending -> returns a range with to direction
'descending -> returns a range with downto direction
'reverse -> reverses the direction
'normalize -> creates a zero-based range (lower bound is zero)
'image -> returns a string representation " to|downto "
"<<" -> move bounds up
">>" -> move bounds down
"+" -> extend upper bound
"-" -> shrink upper bound
"*" -> expand range
"/" -> split range
"/" -> range ratio
"&" -> combine ranges
"and" -> Intersection of two ranges
"or" -> Union of two ranges
"xor" -> Consecutive ranges
"=" -> Strict equality
"/=" -> Strict inequality
"?=" -> Matching equality
"?/=" -> Matching inequality
'range and 'reverse_range attribute return ranges.
range to incomplete_* and full_range_declartion as well as an interface_range_declaration
range_declaration to block_*, entity_*, package_*, package_body_*, process_*, subprogram_* and protected_type_body_declarative_item
simple_expression direction simple_expression with simple_range_expression
range_**_operator rules
complex_range_expression
+= means "add a further alternative"
entity_class +=
| range
incomplete_range_declaration ::=
range identifier ;
full_range_declartion ::=
range identifier is complex_range_expression;
interface_incomplete_range_declaration ::=
range identifier
interface_range_declaration ::=
interface_incomplete_range_declaration
interface_declaration +=
| interface_range_declaration
range_declartion ::=
full_range_declartion
block_declarative_item +=
| range_declartion
entity_declarative_item +=
| range_declartion
package_declarative_item +=
| range_declartion
package_body_declarative_item +=
| range_declartion
process_declarative_item +=
| range_declartion
subprogram_declarative_item +=
| range_declartion
protected_type_body_declarative_item +=
| range_declartion
simple_range_expression ::=
simple_expression direction simple_expression
range ::=
range_attribute_name
| complex_range_expression
range_adding_operator ::= adding_operator
range_move_operator ::= << | >>
range_multiplying_operator ::= * | /
range_set_operator ::= and | or
range_relational_operator ::= = | /= | ?= | ?/=
range_operator ::=
range_adding_operator
| range_move_operator
| range_multiplying_operator
| range_set_operator
complex_range_expression ::=
simple_range_expression
| complex_range_expression range_operator simple_expression
relation ::=
shift_expression [ relational_operator shift_expression ]
| complex_range_expression range_relational_operator complex_range_expression
direction type direction is (ascending, descending); -- to and downto cannot be used, because these are keywords
range_.
See also: extended user-defined attributes
function range_low(range R) return universal_integer is begin return <lower bound of R>; end function;
function range_high(range R) return universal_integer is begin return <upper bound of R>; end function;
function range_left(range R) return universal_integer is
begin
if R'is_ascending then
return R'low;
else
return R'high;
end if;
end function;
function range_right(range R) return universal_integer is
begin
if R'is_ascending then
return R'high;
else
return R'low;
end if;
end function;
function range_length(range R) return universal_integer is begin return R'high - R'low + 1; end function;
function range_direction(range R) return direction is begin return <direction of R as an enum member> end function;
function range_is_ascending(range R) return boolean is begin return (R'direction = ascending); end function;
function range_is_descending(range R) return boolean is begin return (R'direction = descending); end function;
function range_is_nullrange(range R) return boolean is begin return (R'length <= 0); end function;
function range_ascending(range R) return range is begin return R'low to R'high; end function;
function range_descending(range R) return range is begin return R'high downto R'low; end function;
function range_normalize(range R; zero : universal_integer := 0) return range is begin return R - (R'low - zero); end function;
function range_reverse(range R) return range is
begin
if R'is_ascending then
return R'high downto R'low;
else
return R'low to R'high;
end if;
end function;
function range_image(range R) return string is
begin
if R'is_ascending then
return R'base'image(R'high) & " downto " & R'base'image(R'low);
else
return R'base'image(R'low) & " to " & R'base'image(R'high);
end if;
end function;
+ and minus - can be used for range shifting, whereby
plus means a constant offset is added to both ranges and minus means a constant offset is subtracted. I would prefer to have a new set of generic shift operators (<<, >>)
for range operations. This might collide with external names syntax.
Every range is considered as a base range shifted by an offset. The lower bound of a base range is defined as zero. Every range can be converted to a base range by
applying 'normalize on it. The behavior of most of the following operators is defined as if an operation is performed on a base range and the offset is restored after each
operation. So most of the following operators effect only the upper bound, because the lower bound is zero by definition.
function "<<"(range R; offset : universal_integer) return range is
begin
if R'is_ascending then
return R'low + offset to R'high + offset;
else
return R'high + offset downto R'low + offset;
end if;
end function;
function ">>"(range R; offset : universal_integer) return range is
begin
if R'is_ascending then
return R'low - offset to R'high - offset;
else
return R'high - offset downto R'low - offset;
end if;
-- return R << (-offset); -- alternative implementation
end function;
function "+"(range R; offset : universal_integer) return range is
begin
if R'is_ascending then
return R'low to R'high + offset;
else
return R'high + offset downto R'low;
end if;
end function;
function "-"(range R; offset : universal_integer) return range is
begin
if R'is_ascending then
return R'low to R'high - offset;
else
return R'high - offset downto R'low;
end if;
-- return R + (-offset); -- alternative implementation
end function;
function "*"(range R; mult : natural) return range is
constant offset : universal_integer := R'length * (mult - 1);
begin
if R'is_ascending then
return R'low to R'high + offset;
else
return R'high + offset downto R'low;
end if;
-- return R + offset; -- alternative implementation
end function;
function "/"(range R; div : positive) return range is
constant length : natural := R'length / div;
begin
if R'is_ascending then
return R'low to R'low + length - 1;
else
return R'low + length - 1 downto R'low;
end if;
end function;
function "/"(range LHS; range RHS) return integer is begin assert (RHS'length > 0) report "RHS is an empty range." severity failure; assert ((LHS'length mod RHS'length) = 0) report "LHS is not a multiple of RHS" severity failure; return LHS'length / RHS'length; end function;
-- RHS LHS
function "&"(range LHS; range RHS) return range is
begin
if R'is_ascending then
return RHS'low to RHS'low + LHS'length;
else
return RHS'low + LHS'length downto RHS'low;
end if;
-- return RHS + LHS'length; -- alternative implementation
end function;
function "="(range LHS; range RHS) return boolean is
begin
return (LHS'direction = RHS'direction)
and (LHS'low = RHS'low)
and (LHS'high = RHS'high);
end function;
function "/="(range LHS; range RHS) return boolean is begin return not (LHS = RHS); end function;
function "?="(range LHS; range RHS) return boolean is
begin
return (LHS'direction = RHS'direction)
and (LHS'length = RHS'length);
end function;
function "?/="(range LHS; range RHS) return boolean is begin return not (LHS ?= RHS); end function;
function "and"(range LHS; range RHS) return range is
begin
if (LHS ?= RHS) then
return LHS;
elsif ((LHS'low <= RHS'high) and (LHS'high >= RHS'high) and (LHS'low >= RHS'low)) then
if LHS'is_ascending then
return LHS'low to RHS'high;
else
return RHS'high downto LHS'low;
end if
elsif ((RHS'low <= LHS'high) and (RHS'high >= LHS'high) and (RHS'low >= LHS'low)) then
if LHS'is_ascending then
return RHS'low to LHS'high;
else
return LHS'high downto RHS'low;
end if
else
return NullRange;
end if;
end function;
function "and"(range LHS; range RHS) return boolean is begin return not (LHS and RHS)'is_nullrange; end function;
function "or"(range LHS; range RHS) return range is
begin
if (LHS ?= RHS) then
return LHS;
elsif ((LHS'low <= RHS'high) and (LHS'high >= RHS'high) and (LHS'low >= RHS'low)) then
if LHS'is_ascending then
return RHS'low to LHS'high;
else
return LHS'high downto RHS'low;
end if
elsif ((RHS'low <= LHS'high) and (RHS'high >= LHS'high) and (RHS'low >= LHS'low)) then
if LHS'is_ascending then
return LHS'low to RHS'high;
else
return RHS'high downto LHS'low;
end if
else
return NullRange;
end if;
end function;
function "or"(range LHS; range RHS) return boolean is begin return not (LHS or RHS)'is_nullrange; end function;
function "xor"(range LHS; range RHS) return range is
begin
if ((LHS'low < RHS'low) and (LHS'high < RHS'low) and ((LHS'high + 1) = RHS'low)) then
if LHS'is_ascending then
return LHS'low to RHS'high;
else
return RHS'high downto LHS'low;
end if
elsif ((RHS'low < LHS'low) and (RHS'high < LHS'low) and ((RHS'high + 1) = LHS'low)) then
if LHS'is_ascending then
return RHS'low to LHS'high;
else
return LHS'high downto RHS'low;
end if
else
return NullRange;
end if;
end function;
function "xor"(range LHS; range RHS) return boolean is begin return not (LHS xor RHS)'is_nullrange; end function;
is is used to delimit the range's name from the complex_range_expression. The proposal prefers is over := because
a range is immutable.
'ascending, which returns a boolean value if a subtype's range is ascending. The proposal uses 'is_ascending to a) denote the boolean return
value, b) use a common naming scheme as in other languages and c) free the attribute 'ascending for a new purpose: 'ascending returns a range in ascending order. The
counter part 'descending returns a range in descending order.
VHDL has an attribute 'reverse_range to return a reversed range. The proposal uses 'reverse to spare the doubling of "range".
sla, sra, sll, srl. So
in my first draft I'll suggest plus (+) and minus (-) with the semantic of adding or subtracting an integer to/from both range bounds. Should VHDL get two new shift operators?
<Patrick Lehmann> Yes. </Patrick Lehmann>
0 downto 7), is it meaning full that a user can declare an empty range or is there
only one pre-defined empty range, which can be used for comparison? I cannot think of any range arithmetic, which incorporates empty ranges.
<Patrick Lehmann> Yes, for semantic completeness. </Patrick Lehmann>
R * 8 + 4 shall equal (R * 8) + 4, which should be equal to same priority to all range operators and left-associative.
&) be defined? &) is not symmetric/commutative: LHS & RHS / RHS & LHS=. How should concatenate be defined? Which side's lower bound and direction is used for the
resulting range?
and operator, which can return a range intersection (-> range) or
a intersection test result (-> boolean).
'range_type returns an implicitly declared record type for the corresponding scalar type:
'range_value returns a range instance of this implicit record type.
'range_value. A ranged can be stored in a constant or variable, by defining the
constant/variable of type subtype'range_type. As a range is stored in a normal VHDL object, it can be passed around. Further it's a normal -- but LRM-defined -- record and
operators can be applied to it.
The LRM needs further changes to allow these pre-defined implicit records in slices, constraints and loops as an equivalent to the currently used discrete_range.
type IntRange is range 0 to 15; type Realrange is range 0.0 downto 1.0; type Enum is (Item0, Item1, Item2, Item3);
subtype SmallInt is integer range -32768 to 32767; subtype Enum02 is Enum range Item0 to Item2;
type direction is (ascending, descending); -- to and downto cannot be used, because these are keywords type <unnamed> is record -- the record is unnamed / anonymous lowerBound : <scalar_type>; -- the bounds are not restricted to integers upperBound : <scalar_type>; direction : direction; end record;
'range_type. If a handle to the record type is required, it can be created with an alias
declaration. A record instance can be created by the attribute called 'range_value.
subtype R is integer range 0 to 7; alias integer_range is integer'range_type; alias R_range is R'range_type; -- LIEVEN: is this a different but closely related (record) type? constant RLHS : integer_range := R'range_value; -- get R's range => 0 to 7 constant RRHS : R'base'range_type := R'range_value; -- equivalent declaration LIEVEN: is this correct?
<expr> (to | downto) <expr> becomes a simple range expression and will construct a range.'range and 'reverse_range attribute will return ranges.direction type direction is (ascending, descending); -- to and downto cannot be used, because these are keywords
range_record per scalar type: type <unnamed> is record lowerBound : <scalar_type>; upperBound : <scalar_type>; direction : direction; end record;
'range_type.
alias integer_range is integer'range_type; alias index_range is integer_range; -- alternative name, because most indices are integers
function low(R : RANGE_RECORD) return RANGE_TYPE is begin return R.LowerBound; end function;
function high(R : RANGE_RECORD) return RANGE_TYPE is begin return R.UpperBound; end function;
function left(R : RANGE_RECORD) return RANGE_TYPE is
begin
if is_ascending(R) then
return R.LowerBound;
else
return R.UpperBound;
end if;
end function;
function right(R : RANGE_RECORD) return RANGE_TYPE is
begin
if is_ascending(R) then
return R.UpperBound;
else
return R.LowerBound;
end if;
end function;
function length(R : RANGE_RECORD) return INTEGER is begin return R.UpperBound - R.LowerBound + 1; end function;
function direction(R : RANGE_RECORD) return RANGE_DIRECTION is begin return R.Direction; end function;
function is_ascending(R : RANGE_RECORD) return BOOLEAN is begin return (R.Direction = ASCENDING); end function;
function is_descending(R : RANGE_RECORD) return BOOLEAN is begin return (R.Direction = DESCENDING); end function;
function is_nullrange(R : RANGE_RECORD) return BOOLEAN is begin return (length(R) <= 0); end function;
function ascending(R : RANGE_RECORD) return RANGE_RECORD is
begin
return (
LowerBound => R.LowerBound,
UpperBound => R.UpperBound,
Direction => ASCENDING
);
end function;
function descending(R : RANGE_RECORD) return RANGE_RECORD is
begin
return (
LowerBound => R.LowerBound,
UpperBound => R.UpperBound,
Direction => DESCENDING
);
end function;
function reverse(R : RANGE_RECORD) return RANGE_RECORD is
begin
if is_ascending(R) then
return descending(R);
else
return ascending(R);
end if;
end function;
function normalize(R : RANGE_RECORD) return RANGE_RECORD is begin return R srl length(R); end function;
function image(R : RANGE_RECORD) return STRING is
begin
if is_ascending(R) then
return INTEGER'image(R.LowerBound) & " to " & INTEGER'image(R.UpperBound);
else
return INTEGER'image(R.UpperBound) & " downto " & INTEGER'image(R.LowerBound);
end if;
end function;
function range_move_up
generic (type T is scalar_type);
parameter (R : T'range_type; offset : T) return T'range_type is
begin
return (
lowerBound => R.lowerBound + offset,
upperBound => R.upperBound + offset,
direction => R.direction
);
end function;
-- example for an implicit operator creation for integer
function "<<" is new range_move_up generic map(T => integer);
function range_move_down
generic (type T is scalar_type);
parameter (R : T'range_type; offset : T) return T'range_type is
begin
return (
lowerBound => R.lowerBound - offset,
upperBound => R.upperBound - offset,
direction => R.direction
);
-- return R << (-offset); -- alternative implementation
end function;
-- example for an implicit operator creation for integer
function ">>" is new range_move_down generic map(T => integer);
function range_increase
generic (type T is scalar_type);
parameter (R : T'range_type; offset : T) return T'range_type is
begin
return (
lowerBound => R.lowerBound,
upperBound => R.upperBound + offset,
direction => R.direction
);
end function;
-- example for an implicit operator creation for integer
function "+" is new range_increase generic map(T => integer);
function range_decrease
generic (type T is scalar_type);
parameter (R : T'range_type; offset : T) return T'range_type is
begin
return (
lowerBound => R.lowerBound,
upperBound => R.upperBound - offset,
direction => R.direction
);
-- return R + (-offset); -- alternative implementation
end function;
-- example for an implicit operator creation for integer
function "-" is new range_decrease generic map(T => integer);
function range_expand
generic (type T is scalar_type);
parameter (R : T'range_type; mult : natural) return T'range_type is
constant offset : integer := (R.upperBound - R.lowerBound + 1) * (mult - 1);
begin
return (
lowerBound => R.lowerBound,
upperBound => R.upperBound + offset,
direction => R.direction
);
-- return R + offset; -- alternative implementation
end function;
-- example for an implicit operator creation for integer
function "*" is new range_expand generic map(T => integer);
function range_split
generic (type T is scalar_type);
parameter (R : T'range_type; div : positive) return T'range_type is
begin
constant length : natural := (R.upperBound - R.lowerBound + 1) / div;
begin
return (
lowerBound => R.lowerBound,
upperBound => R.lowerBound + length - 1,
direction => R.direction
);
end function;
-- example for an implicit operator creation for integer
function "/" is new range_split generic map(T => integer);
function range_div generic (type T is scalar_type); parameter (LHS : T'range_type; RHS : T'range_type) return T'range_type is begin return (LHS.upperBound - LHS.lowerBound + 1) / (RHS.upperBound - RHS.lowerBound + 1); end function; -- example for an implicit operator creation for integer function "/" is new range_div generic map(T => integer);
function range_concat
generic (type T is scalar_type);
parameter (LHS : T'range_type; RHS : T'range_type) return T'range_type is
constant length : natural := (LHS.upperBound - LHS.lowerBound + 1);
begin
return (
lowerBound => RHS.lowerBound,
upperBound => RHS.upperBound + length,
direction => RHS.direction
);
-- return RHS + length; -- alternative implementation
end function;
-- example for an implicit operator creation for integer
function "&" is new range_concat generic map(T => integer);
function "="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
return LHS.direction = RHS.direction and
LHS.lowerBound = RHS.lowerBound and
LHS.upperBound = RHS.upperBound;
end function;
function "/="(LHS : integer'range_type; RHS : integer'range_type) return boolean is begin return not (LHS = RHS); end function;
function "?="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
return LHS.direction = RHS.direction and
(LHS.upperBound - LHS.lowerBound) = (RHS.upperBound - RHS.lowerBound);
end function;
function "?/="(LHS : integer'range_type; RHS : integer'range_type) return boolean is begin return not (LHS ?= RHS); end function;
function "and"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD is
begin
if (LHS ?= RHS) then
return LHS;
elsif ((LHS.LowerBound <= RHS.UpperBound) and (LHS.UpperBound >= RHS.UpperBound) and (LHS.LowerBound >= RHS.LowerBound)) then
return (LHS.LowerBound, RHS.UpperBound, LHS.Direction);
elsif ((RHS.LowerBound <= LHS.UpperBound) and (RHS.UpperBound >= LHS.UpperBound) and (RHS.LowerBound >= LHS.LowerBound)) then
return (RHS.LowerBound, LHS.UpperBound, LHS.Direction);
else
return (
LowerBound => 0,
UpperBound => 0,
Direction => NULL_RANGE
);
end if;
end function;
function "and"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN is begin return not is_nullrange(LHS or RHS); end function;
function "or"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD is
begin
if (LHS ?= RHS) then
return LHS;
elsif ((LHS.LowerBound <= RHS.UpperBound) and (LHS.UpperBound >= RHS.UpperBound) and (LHS.LowerBound >= RHS.LowerBound)) then
return (RHS.LowerBound, LHS.UpperBound, LHS.Direction);
elsif ((RHS.LowerBound <= LHS.UpperBound) and (RHS.UpperBound >= LHS.UpperBound) and (RHS.LowerBound >= LHS.LowerBound)) then
return (LHS.LowerBound, RHS.UpperBound, LHS.Direction);
else
return (
LowerBound => 0,
UpperBound => 0,
Direction => NULL_RANGE
);
end if;
end function;
function "or"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN is begin return not is_nullrange(LHS or RHS); end function;
function "xor"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD is
begin
if ((LHS.LowerBound < RHS.LowerBound) and (LHS.UpperBound < RHS.LowerBound) and ((LHS.UpperBound + 1) = RHS.LowerBound)) then
return (LHS.LowerBound, RHS.UpperBound, LHS.Direction);
elsif ((RHS.LowerBound < LHS.LowerBound) and (RHS.UpperBound < LHS.LowerBound) and ((RHS.UpperBound + 1) = LHS.LowerBound)) then
return (RHS.LowerBound, LHS.UpperBound, LHS.Direction);
else
return (
LowerBound => 0,
UpperBound => 0,
Direction => NULL_RANGE
);
end if;
end function;
function "xor"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN is begin return not is_nullrange(LHS xor RHS); end function;
'range_value by replaced with 'range? range_record in slices. So if every slice excepts a range_record, then 'range could always return a range_record
instance (range_value). This in turn allows us to replace 'range_value with 'range.
direction is created in library std.
range is made available to the user. The implementation dependent internal data structure of a range can be created at any place, be passed around and be manipulated.
7 downto 0 serves as a range constructor.
'range and 'reverse_range return a range.
RangePackage can be downloaded: 'range and 'reverse_range should return the implicit range Record -> big change.
signal reg_interface : array(natural range 255 downto 0) of std_logic_vector(31 downto 0);
type Myrange is record
RegID : natural;
Rng : range;
end record;
type MyRange_Vector is array(natural range <>) of MyRange;
function overall_range(RV : MyRange_Vector) return range is
variable length : natural := 0;
begin
for i in RV'range loop
length = length + RV(i).Rng'length;
end loop;
return length - 1 downto 0;
end function;
constant capability_flags : MyRange_Vector := (
0 => (0, 17 downto 4),
1 => (25, 8 downto 0),
2 => (97, 31 downto 8)
);
function extract(regs : std_logic_vector of std_logic_vector; positions : MyRange_Vector) return std_logic_vector is
variable capabilities : std_logic_vector(overall_range(positions));
variable offset : natural := 0;
begin
for i in positions'range loop
capabilities(RV(i).Rng'normalized + offset) := regs(RV(i).RegID)(RV(i).Rng);
end loop;
return capabilities;
end function;
signal capabilities : std_logic_vector(overall_range(positions));
capabilities <= extract(reg_interface, capability_flags)
entity enc_8b10b is
port (
DataIn : in std_logic_vector; -- must be a multiple of 8, otherwise the next line fails
CharIsK : in std_logic_vector(DataIn'range / 8); -- require one K bit per input byte
DataOut : out std_logic_vector((DataIn'range / 4) & DataIn'range) -- emit 2 additional bits per byte (10 bits per 8 bit byte)
);
end entity;
subtype X01Z is resolved std_ulogic range 'X' to 'Z';
subtype my_range_jt is natural range 10 downto 0;
subtype my_vector_vt is std_logic_vector(my_range_jst);
subtype my_signed_svt is signed(my_range_jst);
subtype my_unsigned_uvt is unsigned(my_range_jst);
{10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} with position numbers 10 down to 0
subtype my_range1_jt is natural range 9 downto 7;
-- defines a set {9, 8, 7}
subtype my_range2_jt is my_range1_jt >> 2;
-- produces a set {7, 6, 5}
subtype my_range3_jt is my_range1_jt << 1;
-- produces a set {10, 9, 8}
subtype my_range4_jt is my_range1_jt << 2;
-- generates an error
range function "<<"
generic(type L)
parameter(R : integer)
is
constant lo_pos : universal_integer := L'pos(L'low);
constant hi_pos : universal_integer := L'pos(L'high);
begin
if L'ascending then
return subtype L'base range L'base'val(lo_pos - R) to L'base'val(hi_pos - R);
else
return subtype L'base range L'base'val(hi_pos + R) downto L'base'val(lo_pos + R);
end if
end range function
range function "<<"
generic(type R)
parameter(L : integer)
is
begin
return subtype R << L;
end range function
| my_range | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} | |
| Operation | Definition | Return Subtype |
|---|---|---|
| my_range >> 2 | shift right | {8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| 2 >> my_range | ditto | {8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| 2 << my_range | shift left | {12, 11 10, 9 8, 7, 6, 5, 4, 3, 2} |
| my_range << 2 | ditto | {12, 11 10, 9 8, 7, 6, 5, 4, 3, 2} |
| my_range >+ 2 | add to right bound | {10, 9, 8, 7, 6, 5, 4, 3, 2} |
| my_range +> 2 | ditto | {10, 9, 8, 7, 6, 5, 4, 3, 2} |
| my_range <+ 2 | add to left bound | {12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range +< 2 | ditto | {12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range >+< 2 | add to both bounds | {12, 11 10, 9 8, 7, 6, 5, 4, 3, 2} |
| my_range <+> 2 | ditto | {12, 11 10, 9 8, 7, 6, 5, 4, 3, 2} |
| my_range >- 2 | subtract from right bound | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| my_range -> 2 | ditto | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| my_range <- 2 | subtract from left bound | {8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range -< 2 | ditto | {8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range >-< 2 | subtract from both bounds | {8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| my_range <-> 2 | ditto | {8, 7, 6, 5, 4, 3, 2, 1, 0, -1, -2} |
| my_range >* 2 | multiply right bound | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range *> 2 | ditto | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range <* 2 | multiply left bound | {20, 19, 18, 17, 16, 15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range *< 2 | ditto | {20, 19, 18, 17, 16, 15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| (my_range >+ 2) >*< 2 | multiply both bounds | {20, 19, 18, 17, 16, 15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4} |
| (my_range >+ 2) <*> 2 | ditto | {20, 19, 18, 17, 16, 15, 14, 13, 12, 11, 10, 9, 8, 7, 6, 5, 4} |
| my_range >/ 2 | divide right bound | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range /> 2 | ditto | {5, 4, 3, 2, 1, 0} |
| my_range </ 2 | divide right bound | {10, 9, 8, 7, 6, 5, 4, 3, 2, 1, 0} |
| my_range /< 2 | ditto | {5, 4, 3, 2, 1, 0} |
| (my_range >+ 2) >/< 2 | divide both bounds | {5, 4, 3, 2, 1} |
| (my_range >+ 2) </> 2 | ditto | {5, 4, 3, 2, 1} |