Extended Ranges

Proposal Editing Information

Table of Content

Summary

VHDL has a concept of ranges for either defining ranges on ordered sets (integer ranges, floating point number ranges, ranges on enumerated types) or defining slices to get a sub-set of a composite type (array).

These ranges cannot be:

  • manipulated (moved/shifted by an offset, expanded, shrinked, combined/concatenated),
  • reversed, normalized,
  • compared (equal, inequal, left-of, right-of, smaller, bigger, ...),
  • queried for range properties (e.g. is_ascending, direction, length),
  • passed as an argument to a subprogram (procedure, function, operator), or
  • returned as a result from a function or (extended) user defined attribute.
This proposal addresses all these missing features, by
  • splitting ranges from subtype constraints,
  • introducing ranges as an immutable "object", which can be passed round,
  • defining operators on ranges to create a range arithmetic, and
  • defining attributes to ease the handling of ranges.

While developing a first solution, which could be summarized as "ranges as a new VHDL entity class" (Idea 1), I found some limitations in VHDL, which might imply too heavy LRM changes to fulfill all requirements. So I had a talk with Lieven Lemiengre, who offered another view to the topic, which could be summarized as "Ranges as an LRM pre-defined record" (Idea 2). This view solved many of my issues, but has some drawbacks, too. So this proposal will show two ideas, presenting advantages and disadvantages for both ideas and giving a starting point for a discussion in an upcoming IEEE meeting.

Finally, if my initial Idea 1 seems to be too pioneering, then there might be a hybrid solution...

Related and/or Competing Proposals:

RangeOperations - Allow static operations on "ranges".

  • Author: Stewart Cobb
  • VHDL Version: VHDL-93
  • Issue Number: IR-2072
  • Status: Forwarded
  • VASG-ISAC Analysis & Rationale: Some of the problems that the author mentions can be solved by using aliases to normalize ranges and directions of array objects. However, this proposal goes farther and permits some form of arithmetic on ranges.

Aliases and Subtypes as Ranges

Many discussions begin at or end up in a sentence like:
  • "Ranges can be emulated with subtypes.", or
  • "Many presented use cases can be worked around with aliases."
I agree that aliases and/or subtypes are a -- in my eyes -- dirty workaround to emulate ranges, because each constrained subtype of a scalar type has a range. Furthermore a subtype can be used as a 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:
  • a direction,
  • a lower, and
  • an upper bound.
  • reference to an ordered set 1
A (sub-)type is more than a range. It defines:
  • a range (if constrained),
  • attributes for itself,
  • attributes for its instances, and
  • (default) operators for its instances.

1As Andy Jones pointed out in an IEEE reflector discussion, VHDL ranges need to be linked to an ordered set, otherwise a compiler can not know if for example 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.

General Requirements

Starting from an ideal world, this is a list of requirements, which shall be solved.
  • Mandatory:
    • ranges are created by the existing H downto L or L to H syntax
    • ranges are returned by the 'range and 'reverse_range attributes
    • ranges can be used in subtype declarations to constrain types
    • ranges can be used in slices
    • ranges can be used in choices
    • ranges can be passed into subprograms
      • as generic parameters
      • as formal parameters
    • ranges are immutable "objects" (they behave like constants)
    • ranges can be manipulated (the "manipulated" object is a new instance, because a range is immutable)
    • new shift/move operators << and >> for ranges
    • ranges can be reversed and normalized
    • ranges can be compared to each other
      • equality
    • properties of ranges can be queried
    • ranges can be aliased
  • Optional:
    • ranges can be returned from functions and attributes
    • ranges can be elements in composite types (e.g. to define multi-slices)
    • ranges are mutable (change the mandatory property of immutable ranges to mutable)

Current Situation - Ranges and Slices in VHDL

The range keyword is already reserved in VHDL and used in:
  • type declaration:
    • 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 declarations:
    • subtype positive is integer range 1 to integer'high;
  • type marks (e.g. in a record declaration):
    • digit0 : integer range 0 to 9;
Additionally, 'range and 'reverse_range are pre-defined attribute names, containing the string "range".

Currently, VHDL's EBNF knows "ranges" as:

These ranges can be used in:
  • slices,
  • range constraints,
  • choices, or
  • for loops (including generate loops)

Definitions

VHDL Type System
  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

1All relational operators are predefined.

Direction
A direction is an enumeration (enumerated type in VHDL) of 2 values: to and downto.
type direction is (to, downto);
Range
A range is an implementation specific data structure defining 3 members: 1) a lower bound, 2) an upper bound, and 3) a direction. The bounds are not limited to integer or floating point literals. Every scalar values is allowed. It can be expressed in (VHDL) pseudo code as a record:
type <name> is record
  Left : <scalar_type>;
  Right : <scalar_type>;
  direction  : direction;
end record;

Proposal - Idea 1

A range should be a member in VHDL's entity class list and it should be a VHDL "object" with its own 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.

Examples

EX01 - Simple Example 01
The following example declares two ranges: One in ascending (to) and one in descending (downto) order. This simple example uses a 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
  -- ...;

EX02 - Simple Example 02
The following lines show arithmetic on ranges. Some ranges are created from attribute return values.

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;

EX03 - Simple Example 03
This example shows a range in a generic list as well as in a formal parameter list.

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);

EX04 - Complex Example 04
This complex example combines many aspects from the previous examples into one big example.

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;

This is an example to demonstrate what's possible with ranges and range arithmetic. It's not an example of short and compact VHDL code!

Detailed Requirements

  1. Ranges can be declared in any declarative region:
    • entity declarative region
    • architecture declarative region
    • package and package body
    • process statement
    • block statement
    • generate statement
    • protected type body
    • subprogram declarative region
  2. The existing syntax <expr> (to | downto) <expr> becomes a simple range expression and will construct a range.
  3. Ranges can be used as:
    • constraints,
    • slices
    • choices, or
    • loop-ranges as in the current usage.
  4. Ranges define attributes to query range properties:
    • '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 "
  5. Ranges can be manipulated in complex range expressions by range arithmetic:
    • "<<" -> move bounds up
    • ">>" -> move bounds down
    • "+" -> extend upper bound
    • "-" -> shrink upper bound
    • "*" -> expand range
    • "/" -> split range
    • "/" -> range ratio
    • "&" -> combine ranges
  6. Ranges can implement set arithmetic:
    • "and" -> Intersection of two ranges
    • "or" -> Union of two ranges
    • "xor" -> Consecutive ranges
  7. Ranges can be compared for (in-)equality:
    • "=" -> Strict equality
    • "/=" -> Strict inequality
    • "?=" -> Matching equality
    • "?/=" -> Matching inequality
  8. The existing 'range and 'reverse_range attribute return ranges.
  9. Ranges can be passed in generic lists:
    • package generic lists
    • entity / component generic lists:
    • subprogram generic lists
  10. Ranges can be passed in formal lists to subprograms:
    • functions
    • procedures
    • operators
  11. Ranges can be returned by functions and attributes.

Proposal - Idea 2

The internal range data structure of a subtype should be accessible to the VHDL user through two new pre-defined attributes for any scalar type.
  • 'range_type returns an implicitly declared record type for the corresponding scalar type:
  • 'range_value returns a range instance of this implicit record type.
Ranges are expressed as subtypes and can be "converted" to the corresponding record with '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.

State-of-the-Art

Ranges can be expressed as (new) scalar types like:
type IntRange  is range 0 to 15;
type Realrange is range 0.0 downto 1.0;
type Enum is (Item0, Item1, Item2, Item3);

Every scalar type can be constrained by a range in a subtype declaration:

subtype SmallInt is integer range -32768 to 32767;
subtype Enum02   is Enum    range Item0  to Item2;

(Sub-)Types can be passed as type generics in _generic_=_interface_list=.

Implicit range Record:

Scalar types declare an implicit record (range_record), which represents a range as a triple: from, to, dir. The VHDL record prototype looks as follows:
type direction is (ascending, descending);    -- to and downto cannot be used, because these are keywords

type <unnamed> is record                -- the record is unnamed / anonymous
  Left : <scalar_type>;           -- the bounds are not restricted to integers
  Right : <scalar_type>;
  direction  : direction;
end record;

The implicit record type of every scalar type can be accessed by an attribute called '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?

Detailed Requirements

  1. Ranges can be declared in any declarative region:
    • same as in idea 1
  2. The existing syntax <expr> (to | downto) <expr> becomes a simple range expression and will construct a range.
  3. Ranges can be used as:
    • constraints,
    • slices, or
    • loop-ranges as in the current usage.
  4. Ranges can be manipulated in complex range expressions by range arithmetic:
    • same as in idea 1
  5. Ranges can be compared:
    • same as in idea 1
  6. Ranges define attributes to query range properties:
    • ='low= -> returns the lower bound
    • ='high= -> returns the upper bound
    • ='left= -> returns the left bound
    • ='right= -> returns the right bound
    • ='length= -> returns 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= -> reverse the direction
    • ='normalize= -> create a zero-based range (lower bound is zero)
    • ='image= -> returns a string representation
  7. The existing 'range and 'reverse_range attribute will return ranges.
  8. Ranges can be passed in generic lists:
    • same as in idea 1
  9. Ranges can be passed in formal lists to subprograms:
    • same as in idea 1
  10. Ranges can be returned by functions and attributes.

LIEVEN: Filling the next sections with content might enable stroked lines.

Additions to STANDARD:

New Enumerated Type: direction

type direction is (ascending, descending);    -- to and downto cannot be used, because these are keywords

One implicit declared range_record per scalar type:

type <unnamed> is record
  Left : <scalar_type>;
  Right : <scalar_type>;
  direction  : direction;
end record;

Useful extensions if a user works with 'range_type.

alias integer_range is integer'range_type;
alias index_range   is integer_range;    -- alternative name, because most indices are integers

Attributes on Ranges

Currently, no attributes are proposed to query range properties. Some are accessible through the record itself, but most should be implemented in normal functions. (Extended user-defined attributes) might be a solution to map these functions to the range records.

Functions for Ranges

Lower Boundary

function low(R : RANGE_RECORD) return RANGE_TYPE is
begin
  return R.Left;
end function;

Upper Boundary

function high(R : RANGE_RECORD) return RANGE_TYPE is
begin
  return R.Right;
end function;

Left Boundary

function left(R : RANGE_RECORD) return RANGE_TYPE is
begin
  if is_ascending(R) then
    return R.Left;
  else
    return R.Right;
  end if;
end function;

Right Boundary

function right(R : RANGE_RECORD) return RANGE_TYPE is
begin
  if is_ascending(R) then
    return R.Right;
  else
    return R.Left;
  end if;
end function;

Length

function length(R : RANGE_RECORD) return INTEGER is
begin
  return R.Right - R.Left + 1;
end function;

Direction

function direction(R : RANGE_RECORD) return RANGE_DIRECTION is
begin
  return R.Direction;
end function;

Range is ascending

function is_ascending(R : RANGE_RECORD) return BOOLEAN  is
begin
  return (R.Direction = ASCENDING);
end function;

Range is descending

function is_descending(R : RANGE_RECORD) return BOOLEAN  is
begin
  return (R.Direction = DESCENDING);
end function;

Range is a null range

function is_nullrange(R : RANGE_RECORD) return BOOLEAN  is
begin
  return (length(R) <= 0);
end function;

Returns an ascending range

function ascending(R : RANGE_RECORD) return RANGE_RECORD is
begin
  return (
    Left =>  R.Left,
    Right =>  R.Right,
    Direction =>  ASCENDING
  );
end function;

Returns a descending range

function descending(R : RANGE_RECORD) return RANGE_RECORD is
begin
  return (
    Left =>  R.Left,
    Right =>  R.Right,
    Direction =>  DESCENDING
  );
end function;

Returns a reversed range

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;

Returns a normalized range

function normalize(R : RANGE_RECORD) return RANGE_RECORD is
begin
  return R srl length(R);
end function;

Returns a string representation

function image(R : RANGE_RECORD) return STRING is
begin
  if is_ascending(R) then
    return INTEGER'image(R.Left) & " to "     & INTEGER'image(R.Right);
  else
    return INTEGER'image(R.Right) & " downto " & INTEGER'image(R.Left);
  end if;
end function;

Operators on Ranges

"<<" - Move a range up

function range_move_up
  generic   (type T is scalar_type);
  parameter (R : T'range_type; offset : T) return T'range_type is
begin
  return (
    Left => R.Left + offset,
    Right => R.Right + offset,
    direction =>  R.direction
  );
end function;

-- example for an implicit operator creation for integer
function "<<" is new range_move_up generic map(T => integer);

">>" - Move a range down

function range_move_down
  generic   (type T is scalar_type);
  parameter (R : T'range_type; offset : T) return T'range_type is
begin
  return (
    Left => R.Left - offset,
    Right => R.Right - 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);

"+" - Increase the upper bound

function range_increase
  generic   (type T is scalar_type);
  parameter (R : T'range_type; offset : T) return T'range_type is
begin
  return (
    Left => R.Left,
    Right => R.Right + offset,
    direction =>  R.direction
  );
end function;

-- example for an implicit operator creation for integer
function "+" is new range_increase generic map(T => integer);

"-" - Decrease the upper bound

function range_decrease
  generic   (type T is scalar_type);
  parameter (R : T'range_type; offset : T) return T'range_type is
begin
  return (
    Left => R.Left,
    Right => R.Right - 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);

"*" - Expand a range

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.Right - R.Left + 1) * (mult - 1);
begin
  return (
    Left => R.Left,
    Right => R.Right + 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);

"/" - Split a range

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.Right - R.Left + 1) / div;
begin
  return (
    Left => R.Left,
    Right => R.Left + length - 1,
    direction =>  R.direction
  );
end function;

-- example for an implicit operator creation for integer
function "/" is new range_split generic map(T => integer);

"/" - Divide ranges to get the multiple of each other

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.Right - LHS.Left + 1) / (RHS.Right - RHS.Left + 1);
end function;

-- example for an implicit operator creation for integer
function "/" is new range_div generic map(T => integer);

"&" - Combine two ranges

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.Right - LHS.Left + 1);
begin
  return (
    Left => RHS.Left,
    Right => RHS.Right + 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);

This operator is not commutative, because only one range's direction can be preserved.

Relational Operations on Ranges

"=" - Strict equality

TODO: needs upgrade
function "="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
  return LHS.direction  = RHS.direction and
         LHS.Left = RHS.Left and
         LHS.Right = RHS.Right;
end function;

"/=" - Strict inequality

TODO: needs upgrade
function "/="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
  return not (LHS = RHS);
end function;

"?=" - Matching equality

TODO: needs upgrade
function "?="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
  return LHS.direction  = RHS.direction and
         (LHS.Right - LHS.Left) = (RHS.Right - RHS.Left);
end function;

"?/=" - Matching inequality

TODO: needs upgrade
function "?/="(LHS : integer'range_type; RHS : integer'range_type) return boolean is
begin
  return not (LHS ?= RHS);
end function;

Set Operations on Ranges

"and" - Intersection
function "and"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD  is
begin
  if (LHS ?= RHS) then
    return LHS;
  elsif ((LHS.Left <= RHS.Right) and (LHS.Right >= RHS.Right) and (LHS.Left >= RHS.Left)) then
    return (LHS.Left, RHS.Right, LHS.Direction);
  elsif ((RHS.Left <= LHS.Right) and (RHS.Right >= LHS.Right) and (RHS.Left >= LHS.Left)) then
    return (RHS.Left, LHS.Right, LHS.Direction);
  else
    return (
      Left => 0,
      Right => 0,
      Direction  => NULL_RANGE
    );
  end if;
end function;

This operator is not commutative, because only range's direction can be preserved.

"and" - Is one range a subrange of the other?
function "and"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN  is
begin
  return not  is_nullrange(LHS or RHS);
end function;

This operator is not commutative, because only range's direction can be preserved.

"or" - Union
function "or"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD  is
begin
  if (LHS ?= RHS) then
    return LHS;
  elsif ((LHS.Left <= RHS.Right) and (LHS.Right >= RHS.Right) and (LHS.Left >= RHS.Left)) then
    return (RHS.Left, LHS.Right, LHS.Direction);
  elsif ((RHS.Left <= LHS.Right) and (RHS.Right >= LHS.Right) and (RHS.Left >= LHS.Left)) then
    return (LHS.Left, RHS.Right, LHS.Direction);
  else
    return (
      Left => 0,
      Right => 0,
      Direction  => NULL_RANGE
    );
  end if;
end function;

This operator is not commutative, because only range's direction can be preserved.

"or" - Are both ranges overlapping?
function "or"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN  is
begin
  return not  is_nullrange(LHS or RHS);
end function;

This operator is not commutative, because only range's direction can be preserved.

"xor" - Consecutive Ranges
function "xor"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return RANGE_RECORD  is
begin
  if ((LHS.Left < RHS.Left) and (LHS.Right < RHS.Left) and ((LHS.Right + 1) = RHS.Left)) then
    return (LHS.Left, RHS.Right, LHS.Direction);
  elsif ((RHS.Left < LHS.Left) and (RHS.Right < LHS.Left) and ((RHS.Right + 1) = LHS.Left)) then
    return (RHS.Left, LHS.Right, LHS.Direction);
  else
    return (
      Left => 0,
      Right => 0,
      Direction  => NULL_RANGE
    );
  end if;
end function;

This operator is not commutative, because only range's direction can be preserved.

"xor" - Are both ranges consecutive?
function "xor"(LHS : RANGE_RECORD; RHS : RANGE_RECORD) return BOOLEAN  is
begin
  return not  is_nullrange(LHS xor RHS);
end function;

This operator is not commutative, because only range's direction can be preserved.

Open Questions (unsolved or for discussion)

Q51 - Can 'range_value by replaced with 'range?

This proposal requests a special LRM rule, which allows a 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.

Q52 - Is it possible to define attributes on ranges?

Additional Examples

Composites of Ranges

Imagine a communication controller for a user-defined protocol in a System-on-a-Chip, which offers a register interface. After several redesign cycles over the past 5 years, the configuration values are scattered over multiple register addresses. This happens if a designer didn't implement enough reserved bits or the projected design lifetime was exceeded. However, the configuration values as a sequence of config bits can be described as a array or record of ranges, which need to be accessed to gather the complete configuration value.

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)

Constrained ports without generic parameters.

This example requires All Interface Lists Can Be Ordered. In 8b/10b encoding, every byte has an additional CharIsK bit, to distinguish data characters from K character and commas. Such encoders can be described for 1, 2, 4, or 8 bytes.
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;

General Comments

Arguments FOR

Arguments AGAINST

Supporters

-- Patrick Lehmann - 2016-07-19

-- Brent Hayhoe - 2016-07-21

Add your signature here to indicate your support for the proposal

I Attachment Action Size Date Who Comment
Unknown file formatvhdl char_range.pkg.vhdl manage 0.2 K 2016-08-15 - 11:36 PatrickLehmann Package to define a scalar type (enum) for the Ranges package.
Unknown file formatps1 compile.ps1 manage 1.9 K 2016-08-15 - 11:38 PatrickLehmann Compile script for Windows (PowerShell)
Unknown file formatvhdl ghdl_char.vhdl manage 8.8 K 2016-08-15 - 11:37 PatrickLehmann GHDL Testbench for enum ranges.
Unknown file formatvhdl ghdl_integer.vhdl manage 58.0 K 2016-08-15 - 11:37 PatrickLehmann GHDL Testbench for integer ranges.
Unknown file formatvhdl integer_range.pkg.vhdl manage 0.1 K 2016-08-15 - 11:36 PatrickLehmann Package to define a scalar type (integer) for the Ranges package.
Unknown file formatvhdl ranges.pkg.vhdl manage 18.5 K 2016-08-15 - 11:32 PatrickLehmann Implements an (integer) range as a record. Defines property functions and operators on ranges.
Topic revision: r16 - 2020-02-17 - 15:34:30 - JimLewis
 
Copyright © 2008-2025 by the contributing authors. All material on this collaboration platform is the property of the contributing authors.
Ideas, requests, problems regarding TWiki? Send feedback