FIGURE 7. 1

Syntax details of a type declaration.

 

 

FIGURE 7. 2

Input-Output mapping of an inverter in qit logic value system.

 

USE WORK.basic_utilities.ALL;

-- From PACKAGE USE : qit

ENTITY inv_q IS

GENERIC (tplh : TIME := 5 NS; tphl : TIME := 3 NS);

PORT (i1 : IN qit; o1 : OUT qit);

END inv_q;

--

ARCHITECTURE double_delay OF inv_q IS

BEGIN

o1 <= '1' AFTER tplh WHEN i1 = '0' ELSE

'0' AFTER tphl WHEN i1 = '1' OR i1 = 'Z' ELSE

'X' AFTER tplh;

END double_delay;

 

 

 

FIGURE 7. 3

VHDL description of an inverter in qit logic value system.

 

 

 

 

FIGURE 7. 4

Syntax details of a conditional signal assignment.

 

 

 

FIGURE 7. 5

Input-Output mapping of a NAND gate in qit logic value system.

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE : qit

ENTITY nand2_q IS

GENERIC (tplh : TIME := 7 NS; tphl : TIME := 5 NS);

PORT (i1, i2 : IN qit; o1 : OUT qit);

END nand2_q;

--

ARCHITECTURE double_delay OF nand2_q IS

BEGIN

o1 <= '1' AFTER tplh WHEN i1 = '0' OR i2 = '0' ELSE

'0' AFTER tphl WHEN (i1 = '1' AND i2 = '1') OR

(i1 = '1' AND i2 = 'Z') OR

(i1 = 'Z' AND i2 = '1') OR

(i1 = 'Z' AND i2 = 'Z') ELSE

'X' AFTER tplh; -- Can Use: UNAFFECTED;

END double_delay;

 

FIGURE 7. 6

VHDL description of a NAND gate in qit logic value system.

 

 

 

FIGURE 7. 7

Composition aspect of an inverter with RC timing.

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit

ENTITY inv_rc IS

GENERIC (c_load : REAL := 0.066E-12); -- Farads

PORT (i1 : IN qit; o1 : OUT qit);

CONSTANT rpu : REAL := 25000.0; -- Ohms

CONSTANT rpd : REAL := 15000.0; -- Ohms

END inv_rc;

--

ARCHITECTURE double_delay OF inv_rc IS

CONSTANT tplh : TIME := INTEGER ( rpu * c_load * 1.0E15) * 3 FS;

CONSTANT tphl : TIME := INTEGER ( rpd * c_load * 1.0E15) * 3 FS;

BEGIN

o1 <= '1' AFTER tplh WHEN i1 = '0' ELSE

'0' AFTER tphl WHEN i1 = '1' OR i1 = 'Z' ELSE

'X' AFTER tplh;

END double_delay;

 

 

FIGURE 7. 8

An inverter model with RC timing parameters.

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

TYPE capacitance IS RANGE 0 TO 1E16

UNITS

ffr; -- Femto Farads (base unit)

pfr = 1000 ffr;

nfr = 1000 pfr;

ufr = 1000 nfr;

mfr = 1000 ufr;

far = 1000 mfr;

kfr = 1000 far;

END UNITS;

 

 

FIGURE 7. 9

Type definition for defining the capacitance physical type.

 

TYPE resistance IS RANGE 0 TO 1E16

UNITS

l_o; -- Milli-Ohms (base unit)

ohms = 1000 l_o;

k_o = 1000 ohms;

m_o = 1000 k_o;

g_o = 1000 m_o;

END UNITS;

 

FIGURE 7. 10

Type definition for defining the resistance physical type.

 

 

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, resistance, capacitance

ENTITY inv_rc IS

GENERIC (c_load : capacitance := 66 ffr);

PORT (i1 : IN qit; o1 : OUT qit);

CONSTANT rpu : resistance := 25000 ohms;

CONSTANT rpd : resistance := 15000 ohms;

END inv_rc;

--

ARCHITECTURE double_delay OF inv_rc IS

CONSTANT tplh : TIME := (rpu / 1 l_o) * (c_load / 1 ffr) * 3 FS / 1000;

CONSTANT tphl : TIME := (rpd / 1 l_o) * (c_load / 1 ffr) * 3 FS / 1000;

BEGIN

o1 <= '1' AFTER tplh WHEN i1 = '0' ELSE

'0' AFTER tphl WHEN i1 = '1' OR i1 = 'Z' ELSE

'X' AFTER tplh;

END double_delay;

 

FIGURE 7. 11

Using resistance and capacitance physical types in the description of an inverter.

 

 

TYPE qit_nibble IS ARRAY ( 3 DOWNTO 0 ) OF qit;

TYPE qit_byte IS ARRAY ( 7 DOWNTO 0 ) OF qit;

TYPE qit_word IS ARRAY ( 15 DOWNTO 0 ) OF qit;

TYPE qit_4by8 IS ARRAY ( 3 DOWNTO 0, 0 TO 7 ) OF qit;

TYPE qit_nibble_by_8 IS ARRAY ( 0 TO 7 ) OF qit_nibble;

 

 

 

 

FIGURE 7. 12

Declaring array types.

 

 

 

FIGURE 7. 13

Syntax details of an array type declaration.

 

 

 

SIGNAL sq1 : qit;

SIGNAL sq4 : qit_nibble;

SIGNAL sq8 : qit_byte;

SIGNAL sq16 : qit_word;

SIGNAL sq_4_8 : qit_4by_8;

SIGNAL sq_nibble_8 : qit_nibble_by_8;

(a)

sq8 <= sq16 (11 DOWNTO 4); -- middle 8 bit slice of sq16 to sq8;

sq16 (15 DOWNTO 12) <= sq4; -- sq4 into left 4 bit slice of sq16;

sq1 <= sq_4_8 (0, 7); -- lower right bit of sq_4_8 into sq1;

sq4 <= sq_nibble_8 (2); -- third nibble (number 2) of sq_nibble_8 into sq4;

sq1 <= sq_nibble_8(2)(3); -- nibble 2, bit 3 of sq_nibble_8 into sq1;

sq8 <= sq8(0) & sq8 (7 DOWNTO 1); -- right rotate sq8;

sq4 <= sq8(2) & sq8(3) & sq8(4) & sq8(5); -- reversing sq8 into sq4;

sq4 <= (sq8(2), sq8(3), sq8(4), sq8(5)); -- reversing sq8 into sq4;

(sq4(0), sq4(1), sq4(2), sq4(3)) <= sq8 (5 DOWNTO 2);-- reversing sq8 into sq4;

(b)

 

FIGURE 7. 14

Various forms of signal declarations and signal assignments based on signal declarations of Figure 7.12, (a) signal declarations, (b) valid signal assignments.

 

 

 

 

 

FIGURE 7. 15

Referencing bits of a vector; reversing bits of sq8 and assigning them to sq4.

 

 

 

SIGNAL sq_4_8 : qit_4by8 :=

(

( '0', '0', '1', '1', 'Z', 'Z', 'X', 'X' ),

( 'X', 'X', '0', '0', '1', '1', 'Z', 'Z' ),

( 'Z', 'Z', 'X', 'X', '0', '0', '1', '1' ),

( '1', '1', 'Z', 'Z', 'X', 'X', '0', '0' )

);

SIGNAL sq_4_8 : qit_4by8 := (OTHERS => "11000000");

SIGNAL sq_4_8 : qit_4by8 := (OTHERS => (OTHERS => ‘Z’));

SIGNAL sq_4_8 : qit_4by8 := (OTHERS => (0 TO 1 => ‘1’, OTHERS =>’0’));

 

FIGURE 7. 16

Initializing a two dimensional array.

 

 

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, qit_2d

ENTITY nand2_q IS

GENERIC (tplh : TIME := 7 NS; tphl : TIME := 5 NS);

PORT (i1, i2 : IN qit; o1 : OUT qit);

END nand2_q;

--

ARCHITECTURE average_delay OF nand2_q IS

CONSTANT qit_nand2_table : qit_2d := (

('1','1','1','1'),

('1','0','0','X'),

('1','0','0','X'),

('1','X','X','X'));

BEGIN

o1 <= qit_nand2_table (i1, i2) AFTER (tplh + tphl) / 2;

END average_delay;

 

FIGURE 7. 17

Using qit enumeration type for the discrete range of a two-dimensional array.

 

 

 

 

 

 

FIGURE 7. 18

Syntax details of an unconstrained array declaration.

PROCEDURE apply_data (

SIGNAL target : OUT BIT_VECTOR;

CONSTANT values : IN integer_vector; CONSTANT period : IN TIME) IS

VARIABLE buf : BIT_VECTOR (target'RANGE);

BEGIN

FOR i IN values'RANGE LOOP

int2bin (values(i), buf);

target <= TRANSPORT buf AFTER i * period;

END LOOP;

END apply_data;

 

FIGURE 7. 19

A generic version of the apply_data procedure.

 

 

 

ENTITY n_bit_comparator IS

PORT (a, b : IN BIT_VECTOR; gt, eq, lt : IN BIT;

a_gt_b, a_eq_b, a_lt_b : OUT BIT);

END n_bit_comparator;

--

ARCHITECTURE structural OF n_bit_comparator IS

COMPONENT comp1

PORT (a, b, gt, eq, lt : IN BIT; a_gt_b, a_eq_b, a_lt_b : OUT BIT);

END COMPONENT;

FOR ALL : comp1 USE ENTITY WORK.bit_comparator (functional);

CONSTANT n : INTEGER := a'LENGTH;

SIGNAL im : BIT_VECTOR ( 0 TO (n-1)*3-1);

BEGIN

c_all: FOR i IN 0 TO n-1 GENERATE

l: IF i = 0 GENERATE

least: comp1 PORT MAP (a(i), b(i), gt, eq, lt, im(0), im(1), im(2) );

END GENERATE;

m: IF i = n-1 GENERATE

most: comp1 PORT MAP

(a(i), b(i), im(i*3-3), im(i*3-2), im(i*3-1), a_gt_b, a_eq_b, a_lt_b);

END GENERATE;

r: IF i > 0 AND i < n-1 GENERATE

rest: comp1 PORT MAP

(a(i), b(i), im(i*3-3), im(i*3-2), im(i*3-1), im(i*3+0), im(i*3+1), im(i*3+2) );

END GENERATE;

END GENERATE;

END structural;

 

FIGURE 7. 20

An n-bit comparator, wiring n number of one-bit comparators.

 

 

 

 

ENTITY n_bit_comparator_test_bench IS

END n_bit_comparator_test_bench ;

--

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: apply_data which uses integer_vector

ARCHITECTURE procedural OF n_bit_comparator_test_bench IS

COMPONENT comp_n PORT (a, b : IN bit_vector;

gt, eq, lt : IN BIT;

a_gt_b, a_eq_b, a_lt_b : OUT BIT);

END COMPONENT;

FOR a1 : comp_n USE ENTITY WORK.n_bit_comparator(structural);

SIGNAL a, b : BIT_VECTOR (5 DOWNTO 0);

SIGNAL eql, lss, gtr : BIT;

SIGNAL vdd : BIT := '1';

SIGNAL gnd : BIT := '0';

BEGIN

a1: comp_n PORT MAP (a, b, gnd, vdd, gnd, gtr, eql, lss);

apply_data (a, 00&15&57&17, 500 NS);

apply_data (b, 00&43&14&45&11&21&44&11, 500 NS);

END procedural;

 

FIGURE 7. 21

Using generic apply_data procedure for testing n_bit_comparator.

 

 

 

 

 

PROCEDURE assign_bits (

SIGNAL s : OUT BIT; file_name : IN STRING; period : IN TIME) IS

VARIABLE char : CHARACTER;

VARIABLE current : TIME := 0 NS;

FILE input_value_file : logic_data;

BEGIN

FILE_OPEN (input_value_file, file_name, READ_MODE);

WHILE NOT ENDFILE (input_value_file) LOOP

READ (input_value_file, char);

IF char = '0' OR char = '1' THEN

current := current + period;

IF char = '0' THEN

s <= TRANSPORT '0' AFTER current;

ELSIF char = '1' THEN

s <= TRANSPORT '1' AFTER current;

END IF;

END IF;

END LOOP;

END assign_bits;

 

FIGURE 7. 22

A procedure for reading characters from a file and assigning them to a BIT type.

 

 

 FIGURE 7. 23

Shift operators.

 

 

FIGURE 7. 24

Application of shift operators.

 

 

 

0

1

Z

X

0

0

1

1

X

1

1

1

1

1

Z

1

1

1

1

X

X

1

1

X

 

0

1

Z

X

0

0

1

1

X

1

1

1

1

1

Z

1

1

1

1

X

X

1

1

X

 

 

0

0

1

1

Z

1

X

X

 

 

 

 

 

FIGURE 7. 25

Tables for the basic logic functions in the qit four value logic system, (a) AND function, (b) OR function, (c) NOT function.

 

TYPE qit IS ('0', '1', 'Z', 'X');

TYPE qit_2d IS ARRAY (qit, qit) OF qit;

TYPE qit_1d IS ARRAY (qit) OF qit;

--

FUNCTION "AND" (a, b : qit) RETURN qit;

FUNCTION "OR" (a, b : qit) RETURN qit;

FUNCTION "NOT" (a : qit) RETURN qit;

(a)

 

 

FUNCTION "AND" (a, b : qit) RETURN qit IS

CONSTANT qit_and_table : qit_2d := (

('0','0','0','0'),

('0','1','1','X'),

('0','1','1','X'),

('0','X','X','X'));

BEGIN

RETURN qit_and_table (a, b);

END "AND";

FUNCTION "OR" (a, b : qit) RETURN qit IS

CONSTANT qit_or_table : qit_2d := (

('0','1','1','X'),

('1','1','1','1'),

('1','1','1','1'),

('X','1','1','X'));

BEGIN

RETURN qit_or_table (a, b);

END "OR";

FUNCTION "NOT" (a : qit) RETURN qit IS

CONSTANT qit_not_table : qit_1d := ('1','0','0','X');

BEGIN

RETURN qit_not_table (a);

END "NOT";

(b)

 

FIGURE 7. 26

Overloading basic logical functions for the qit four value logic system, (a) function declarations and other necessary declarations, (b) definition of functions.

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, "NOT"

ENTITY inv_q IS

GENERIC (tplh : TIME := 5 NS; tphl : TIME := 3 NS);

PORT (i1 : IN qit; o1 : OUT qit);

END inv_q;

--

ARCHITECTURE average_delay OF inv_q IS

BEGIN

o1 <= NOT i1 AFTER (tplh + tphl) / 2;

END average_delay;

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, "AND"

ENTITY nand2_q IS

GENERIC (tplh : TIME := 6 NS; tphl : TIME := 4 NS);

PORT (i1, i2 : IN qit; o1 : OUT qit);

END nand2_q;

--

ARCHITECTURE average_delay OF nand2_q IS

BEGIN

o1 <= NOT ( i1 AND i2 ) AFTER (tplh + tphl) / 2;

END average_delay;

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, "AND"

ENTITY nand3_q IS

GENERIC (tplh : TIME := 7 NS; tphl : TIME := 5 NS);

PORT (i1, i2, i3 : IN qit; o1 : OUT qit);

END nand3_q;

--

ARCHITECTURE average_delay OF nand3_q IS

BEGIN

o1 <= NOT ( i1 AND i2 AND i3) AFTER (tplh + tphl) / 2;

END average_delay;

 

FIGURE 7. 27

Basic gates in the qit logic value system using overloaded AND and OR operators.

 

 

FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME;

(a)

 

 

FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME IS

BEGIN

RETURN ( ( a / 1 l_o) * ( b / 1 ffr ) * 1 FS ) / 1000;

END "*";

(b)

 

FIGURE 7. 28

Overloading the multiplication operator for returning TIME when multiplying resistance and capacitance physical types, (a) function declaration, (b) the "*" subprogram body.

 

 

 

 

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, capacitance, resistance, "*"

ENTITY inv_rc IS

GENERIC (c_load : capacitance := 66 ffr);

PORT (i1 : IN qit; o1 : OUT qit);

CONSTANT rpu : resistance := 25 k_o;

CONSTANT rpd : resistance := 15 k_o;

END inv_rc;

--

ARCHITECTURE double_delay OF inv_rc IS

CONSTANT tplh : TIME := rpu * c_load * 3;

CONSTANT tphl : TIME := rpd * c_load * 3;

BEGIN

o1 <= '1' AFTER tplh WHEN i1 = '0' ELSE

'0' AFTER tphl WHEN i1 = '1' OR i1 = 'Z' ELSE

'X' AFTER tplh;

END double_delay;

 

FIGURE 7. 29

Using the overloaded multilplication operator in the double_delay architecture of inv_rc.

TYPE qit IS ('0', '1', 'Z', 'X');

TYPE logic_data IS FILE OF CHARACTER;

PROCEDURE assign_bits (

SIGNAL s : OUT qit; file_name : IN STRING; period : IN TIME);

(a)

 

PROCEDURE assign_bits (

SIGNAL s : OUT qit; file_name : IN STRING; period : IN TIME) IS

VARIABLE char : CHARACTER;

VARIABLE current : TIME := 0 NS;

FILE input_value_file : logic_data;

BEGIN

FILE_OPEN (input_value_file, file_name, READ_MODE);

WHILE NOT ENDFILE (input_value_file) LOOP

READ (input_value_file, char);

current := current + period;

CASE char IS

WHEN '0' => s <= TRANSPORT '0' AFTER current;

WHEN '1' => s <= TRANSPORT '1' AFTER current;

WHEN 'Z' | 'z' => s <= TRANSPORT 'Z' AFTER current;

WHEN 'X' | 'x' => s <= TRANSPORT 'X' AFTER current;

WHEN OTHERS => current := current - period;

END CASE;

END LOOP;

END assign_bits;

(b)

 

FIGURE 7. 30

Overloading the assign_bits procedure for accepting and producing qit data, (a) procedure declaration and other necessary declarations, (b) the subprogram body.

 

 

 

FIGURE 7. 31

Syntax details of a sequential case statement.

 

 

 

 

 

USE WORK.basic_utilities.ALL;

-- FROM PACKAGE USE: qit, capacitance, resistance, assign_bits (Fig 7.30)

ENTITY tester IS

END tester;

--

ARCHITECTURE input_output OF tester IS

COMPONENT inv

GENERIC (c_load : capacitance := 11 ffr);

PORT (i1 : IN qit; o1 : OUT qit);

END COMPONENT;

FOR ALL : inv USE ENTITY WORK.inv_rc(double_delay);

SIGNAL a, z : qit;

BEGIN

assign_bits (a, "data.qit", 500 NS);

i1 : inv PORT MAP (a, z);

END input_output;

 

FIGURE 7. 32

Calling the overloaded assign_bits for testing an inverter.

 

TYPE opcode IS (sta, lda, add, sub, and, nop, jmp, jsr);

TYPE mode IS RANGE 0 TO 3;

TYPE address IS BIT_VECTOR (10 DOWNTO 0);

(a)

 

TYPE instruction_format IS RECORD

opc : opcode;

mde : mode;

adr : address;

END RECORD;

(b)

 

SIGNAL instr : instruction_format := (nop, 0, "00000000000");

(c)

 

instr.opc <= lda;

instr.mde <= 2;

instr.adr <= "00011110000";

(d)

 

instr <= (adr => (OTHERS => ‘1’), mde => 2, opc => sub)

(e)

 

FIGURE 7. 33

Record Type, (a) three fields of an instruction, (b) declaration of instruction format, (c) A signal of record type, (d) referencing fields of a record type signal, (e) record aggragate.

 

(a)

ALIAS page :

BIT_VECTOR (2 DOWNTO 0) IS instr.adr (10 DOWNTO 8);

ALIAS offset :

BIT_VECTOR (7 DOWNTO 0) IS instr.adr (7 DOWNTO 0);

 

(b)

page <= "001";

offset <= X"F1";

(c)

 

 

FIGURE 7. 34

Alias declaration, (a) page and offset addresses, (b) alias declaration for the page and offset parts of the address, (c) assignments to page and offset parts of address.

 

 

 

 

 

 

 

(a)

TYPE node;

TYPE pointer IS ACCESS node;

TYPE node IS RECORD

data : INTEGER;

link : pointer;

END RECORD;

(b)

FIGURE 7. 35

Linked list, (a) graphical representation, (b) definition in VHDL.

 

 

 

PROCEDURE lineup (VARIABLE head : INOUT pointer; int : integer_vector) IS

VARIABLE t1 : pointer;

BEGIN

-- Insert data in the linked list

head := NEW node;

t1 := head;

FOR i IN int'RANGE LOOP

t1.data := int(i);

IF i = int'RIGHT THEN

t1.link := NULL;

ELSE

t1.link := NEW node;

t1 := t1.link;

END IF;

END LOOP;

END lineup;

 

FIGURE 7. 36

Creating a linked list and entering data into it.

 

PROCEDURE remove (VARIABLE head : INOUT pointer; v : IN INTEGER) IS

VARIABLE t1, t2 : pointer;

BEGIN

-- Remove node following that with value v

t1 := head;

WHILE t1 /= NULL LOOP

IF t1.data = v THEN

t2 := t1.link;

t1.link := t2.link;

DEALLOCATE (t2);

END IF;

t1 := t1.link;

END LOOP;

END remove;

 

FIGURE 7. 37

Removing an item from a linked list.

PROCEDURE clear (VARIABLE head : INOUT pointer) IS

VARIABLE t1, t2 : pointer;

BEGIN

-- Free all the linked list

t1 := head;

head := NULL;

WHILE t1 /= NULL LOOP

t2 := t1;

t1 := t1.link;

DEALLOCATE (t2);

END LOOP;

END clear;

END ll_utilities;

 

FIGURE 7. 38

Freeing a linked list.

PACKAGE ll_utilities IS

TYPE node;

TYPE pointer IS ACCESS node;

TYPE node IS RECORD

data : INTEGER;

link : pointer;

END RECORD;

TYPE integer_vector IS ARRAY (INTEGER RANGE <>) OF INTEGER;

PROCEDURE lineup (VARIABLE head : INOUT pointer; int : integer_vector);

PROCEDURE remove (VARIABLE head : INOUT pointer; v : IN INTEGER);

PROCEDURE clear (VARIABLE head : INOUT pointer);

END ll_utilities;

--

PACKAGE BODY ll_utilities IS

PROCEDURE lineup (VARIABLE head : INOUT pointer; int : integer_vector) IS

VARIABLE t1 : pointer;

BEGIN

-- Insert data in the linked list

head := NEW node;

t1 := head;

FOR i IN int'RANGE LOOP

t1.data := int(i);

IF i = int'RIGHT THEN

t1.link := NULL;

ELSE

t1.link := NEW node;

t1 := t1.link;

END IF;

END LOOP;

END lineup;

--

PROCEDURE remove (VARIABLE head : INOUT pointer; v : IN INTEGER) IS

VARIABLE t1, t2 : pointer;

BEGIN

-- Remove node following that with value v

t1 := head;

WHILE t1 /= NULL LOOP

IF t1.data = v THEN

t2 := t1.link;

t1.link := t2.link;

DEALLOCATE (t2);

END IF;

t1 := t1.link;

END LOOP;

END remove;

--

PROCEDURE clear (VARIABLE head : INOUT pointer) IS

VARIABLE t1, t2 : pointer;

BEGIN

-- Free all the linked list

t1 := head;

head := NULL;

WHILE t1 /= NULL LOOP

t2 := t1;

t1 := t1.link;

DEALLOCATE (t2);

END LOOP;

END clear;

END ll_utilities;

 

FIGURE 7. 39

Linked list utilities.

 

 

  

FIGURE 7. 40

std_logic subtypes.

 

 

 

Attribute

 

Description

Example

Result

‘LEFT

Left bound

sq_4_8’LEFT(1)

3

‘RIGHT

Right bound

sq_4_8’RIGHT

sq_4_8’RIGHT(2)

0

7

‘HIGH

Upper bound

sq_4_8’HIGH(2)

7

‘LOW

Lower bound

sq_4_8’LOW(2)

0

‘RANGE

Range

sq_4_8’RANGE(2)

sq_4_8’RANGE(1)

0 TO 7

3 DOWNTO 0

‘REVERSE_RANGE

Reverse range

sq_4_8’REVERSE_RANGE(2)

sq_4_8’REVERSE_RANGE(1)

7 DOWNTO 0

0 TO 3

‘LENGTH

Length

sq_4_8’LENGTH

4

‘ASCENDING

TRUE

If Ascending

sq_4_8’ASCENDING(2)

sq_4_8’ASCENDING(1)

TRUE

FALSE

 

FIGURE 7. 41

Predefined Array Attributes. The Type of sq_4_8 Is qit_4by8 of Figure 7.12.

 

 

 

 

 

Attribute

 

Description

Example

Result

‘BASE

Base of type

rit’BASE

qit

‘LEFT

Left bound of type

or subtype

rit’LEFT

qit’LEFT

‘0’

‘0’

‘RIGHT

Right bound of type

or subtype

rit’RIGHT

qit’RIGHT

‘Z’

‘X’

‘HIGH

Upper bound of type

or subtype

INTEGER’HIGH

rit’HIGH

Large

‘Z’

‘LOW

Lower bound of type

or subtype

POSITIVE’LOW

qit’LOW

1

‘0’

‘POS(V)

Position of value V

in base of type.

qit’POS(‘Z’)

rit’POS(‘X’)

2

3

‘VAL(P)

Value at Position P

in base of type.

qit’VAL(3)

rit’VAL(3)

‘X’

‘X’

‘SUCC(V)

Value, after value

V in base of type.

rit’SUCC(‘Z’)

‘X’

‘PRED(V)

Value, before value

V in base of type.

rit’PRED(‘1’)

‘0’

‘LEFTOF(V)

Value, left of value

V in base of type.

rit’LEFTOF(‘1’)

rit’LEFTOF(‘0’)

‘0’

Error

‘RIGHTOF(V)

Value, right of value

V in base of type.

rit’RIGHTOF(‘1’)

rit’RIGHTOF(‘Z’)

‘Z’

‘X’

‘ASCENDING

TRUE if range is ascending

qit’ASCENDING

qqit’ASCENDING

TRUE

TRUE

‘IMAGE (V)

Converts value

V of type to string.

qit’IMAGE(‘Z’)

qqit’IMAGE(qZ)

"’Z’"

"qZ"

‘VALUE(S)

Converts string

S to value of type.

qqit’VALUE("qZ")

qZ

FIGURE 7. 42

Predefined type attributes. The type of qit and rit are enumeration types.

Attribute

T/E

Example

Kind

Type

Attribute description for the specified example

‘DELAYED

-

s1’DELAYED (5 NS)

SIGNAL

As s1

A copy of s1, but delayed by 5 NS. If no parameter or 0, delayed by delta. Equivalent to TRANSPORT delay of s1.

‘STABLE

EV

s1’STABLE (5 NS)

SIGNAL

BOOLEAN

A signal that is TRUE if s1 has not changed in the last 5 NS. If no parameter or 0, the resulting signal is TRUE if s1 has not changed in the current simulation time.

‘EVENT

EV

s1’EVENT

VALUE

BOOLEAN

In a simulation cycle, if s1 changes, this attribute becomes TRUE.

‘LAST_EVENT

EV

s1’LAST_VALUE

VALUE

TIME

The amount of time since the last value change on s1. If s1’EVENT is TRUE, the value of s1’LAST_VALUE is 0.

‘LAST_VALUE

EV

s1’LAST_VALUE

VALUE

As s1

The value of s1 before the most recent event occurred on this signal.

‘QUIET

TR

s1’QUIET (5 NS)

SIGNAL

BOOLEAN

A signal that ir TRUE if no transaction has been placed on s1 in the last 5 NS. If no parameter or 0, the current simulation cycle is assumed.

‘ACTIVE

TR

s1’ACTIVE

VALUE

BOOLEAN

If s1 has had a transaction in the current simulation cycle, s1’ACTIVE will be TRUE for this simulation cycle, for delta time.

‘LAST_ACTIVE

TR

s1’LAST_ACTIVE

VALUE

TIME

The amount of time since the last transaction occurred on s1. If s1’ACTIVE is TRUE, s1’LAST_ACTIVE is 0.

‘TRANSACTION

TR

s1’TRANACTION

SIGNAL

BIT

A signal that toggles each time a transaction occurs on s1. Initial value of this attribute is not defined.

‘DRIVING

-

s1’DRIVING

VALUE

BOOLEAN

If s1is being driven in a process, s1’DRIVING is TRUE in the same process.

‘DRIVING_VALUE

-

s1’DRIVING_VALUE

VALUE

As s1

The driving value of s1 from within the process this attribute is being applied.

 

 

FIGURE 7. 43

Predefined signal attributes. Signal s is assumed to be of type BIT.

 

 

FIGURE 7. 44

Results of signal attributes when applied to the BIT type signal, s1.

 

 

 

ENTITY brief_d_flip_flop IS

PORT (d, c : IN BIT; q : OUT BIT);

END brief_d_flip_flop;

--

ARCHITECTURE falling_edge OF brief_d_flip_flop IS

SIGNAL tmp : BIT;

BEGIN

tmp <= d WHEN (c = '0' AND NOT c'STABLE) ELSE tmp;

q <= tmp AFTER 8 NS;

END falling_edge;

 

FIGURE 7. 45

A simple falling edge Flip-Flop using signal attributes.

 

 

 

ENTITY brief_t_flip_flop IS

PORT (t : IN BIT; q : OUT BIT);

END brief_t_flip_flop;

--

ARCHITECTURE toggle OF brief_t_flip_flop IS

SIGNAL tmp : BIT;

BEGIN

tmp <= NOT tmp WHEN (

(t = '0' AND NOT t'STABLE) AND (t'DELAYED'STABLE(20 NS))

) ELSE tmp;

q <= tmp AFTER 8 NS;

END toggle;

 

 

 

 

FIGURE 7. 46

A simple toggle Flip-Flop using signal attributes.

 

ENTITY nand2 IS

PORT (i1, i2 : IN BIT; o1 : OUT BIT);

END ENTITY;

--

ARCHITECTURE single_delay OF nand2 IS

SIGNAL simple : STRING (1 TO nand2'SIMPLE_NAME'LENGTH) := (OTHERS => '.');

SIGNAL path : STRING (1 TO nand2'PATH_NAME'LENGTH) := (OTHERS => '.');

SIGNAL instance : STRING (1 TO nand2'INSTANCE_NAME'LENGTH) := (OTHERS => '.');

BEGIN

o1 <= i1 NAND i2 AFTER 3 NS;

simple <= nand2'SIMPLE_NAME;

instance <= nand2'INSTANCE_NAME;

path <= nand2'PATH_NAME;

END single_delay;

--

ENTITY xoring IS

PORT (i1, i2 : IN BIT; o1 : OUT BIT);

END ENTITY;

--

ARCHITECTURE gate_level OF xoring IS

SIGNAL a, b, c : BIT;

BEGIN

u1 : ENTITY WORK.nand2 PORT MAP (i1, i2, a);

u2 : ENTITY WORK.nand2 PORT MAP (i1, a, b);

u3 : ENTITY WORK.nand2 PORT MAP (a, i2, c);

u4 : ENTITY WORK.nand2 PORT MAP (b, c, o1);

END gate_level;

 

 

FIGURE 7. 47

Simple, path, and instance attributes.

 

 

 

FIGURE 7. 48

Simple, path, and instance strings.

 

 

 

PACKAGE utility_attributes IS

TYPE timing IS RECORD

rise, fall : TIME;

END RECORD;

ATTRIBUTE delay : timing;

ATTRIBUTE sub_dir : STRING;

END utility_attributes;

--

USE WORK.utility_attributes.ALL;

-- FROM PACKAGE USE: delay, sub_dir

ENTITY brief_d_flip_flop IS

PORT (d, c : IN BIT; q : OUT BIT);

ATTRIBUTE sub_dir OF brief_d_flip_flop : ENTITY IS "/user/vhdl";

ATTRIBUTE delay OF q : SIGNAL IS (8 NS, 10 NS);

END brief_d_flip_flop;

--

ARCHITECTURE attributed_falling_edge OF brief_d_flip_flop IS

SIGNAL tmp : BIT;

BEGIN

tmp <= d WHEN ( c= '0' AND NOT c'STABLE ) ELSE tmp;

q <= '1' AFTER q'delay.rise WHEN tmp = '1' ELSE

'0' AFTER q'delay.fall;

END attributed_falling_edge;

 

FIGURE 7. 49

Associating attributes to entities and signals

 

PACKAGE basic_utilities IS

TYPE qit IS ('0', '1', 'Z', 'X');

TYPE qit_2d IS ARRAY (qit, qit) OF qit;

TYPE qit_1d IS ARRAY (qit) OF qit;

TYPE qit_vector IS ARRAY (NATURAL RANGE <>) OF qit;

SUBTYPE rit IS qit RANGE '0' TO 'Z';

TYPE rit_vector IS ARRAY (NATURAL RANGE <>) OF rit;

TYPE integer_vector IS ARRAY (NATURAL RANGE <>) OF INTEGER;

TYPE logic_data IS FILE OF CHARACTER;

TYPE capacitance IS RANGE 0 TO 1E16

UNITS

ffr; -- Femto Farads (base unit)

pfr = 1000 ffr;

nfr = 1000 pfr;

ufr = 1000 nfr;

mfr = 1000 ufr;

far = 1000 mfr;

kfr = 1000 far;

END UNITS;

TYPE resistance IS RANGE 0 TO 1E16

UNITS

l_o; -- Milli-Ohms (base unit)

ohms = 1000 l_o;

k_o = 1000 ohms;

m_o = 1000 k_o;

g_o = 1000 m_o;

END UNITS;

FUNCTION fgl (w, x, gl : BIT) RETURN BIT;

FUNCTION feq (w, x, eq : BIT) RETURN BIT;

FUNCTION to_integer (bin : BIT_VECTOR) RETURN INTEGER;

PROCEDURE bin2int (bin : IN BIT_VECTOR; int : OUT INTEGER);

PROCEDURE int2bin (int : IN INTEGER; bin : OUT BIT_VECTOR);

PROCEDURE apply_data ( SIGNAL target : OUT BIT_VECTOR;

CONSTANT values : IN integer_vector; CONSTANT period : IN TIME);

PROCEDURE assign_bits ( SIGNAL s : OUT BIT; file_name : IN STRING; period : IN TIME);

PROCEDURE assign_bits ( SIGNAL s : OUT qit; file_name : IN STRING; period : IN TIME);

FUNCTION "AND" (a, b : qit) RETURN qit;

FUNCTION "OR" (a, b : qit) RETURN qit;

FUNCTION "NOT" (a : qit) RETURN qit;

FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME;

END basic_utilities;

PACKAGE BODY basic_utilities IS

FUNCTION "AND" (a, b : qit) RETURN qit IS

CONSTANT qit_and_table : qit_2d := (

('0','0','0','0'),

('0','1','1','X'),

('0','1','1','X'),

('0','X','X','X'));

BEGIN

RETURN qit_and_table (a, b);

END "AND";

FUNCTION "OR" (a, b : qit) RETURN qit IS

CONSTANT qit_or_table : qit_2d := (

('0','1','1','X'),

('1','1','1','1'),

('1','1','1','1'),

('X','1','1','X'));

BEGIN

RETURN qit_or_table (a, b);

END "OR";

FUNCTION "NOT" (a : qit) RETURN qit IS

CONSTANT qit_not_table : qit_1d := ('1','0','0','X');

BEGIN

RETURN qit_not_table (a);

END "NOT";

FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME IS

BEGIN

RETURN ( ( a / 1 l_o) * ( b / 1 ffr ) * 1 FS ) / 1000;

END "*";

FUNCTION fgl (w, x, gl : BIT) RETURN BIT IS

BEGIN

RETURN (w AND gl) OR (NOT x AND gl) OR (w AND NOT x);

END fgl;

FUNCTION feq (w, x, eq : BIT) RETURN BIT IS

BEGIN

RETURN (w AND x AND eq) OR (NOT w AND NOT x AND eq);

END feq;

FUNCTION to_integer (bin : BIT_VECTOR) IS VARIABLE result: INTEGER; BEGIN result := 0; FOR i IN bin'RANGE LOOP IF bin(i) = '1' THEN result := result + 2**i;

END IF;

END LOOP;

RETURN result;

END;

PROCEDURE bin2int (bin : IN BIT_VECTOR; int : OUT INTEGER) IS

VARIABLE result: INTEGER;

BEGIN

result := 0;

FOR i IN bin'RANGE LOOP

IF bin(i) = '1' THEN result := result + 2**i;

END IF;

END LOOP;

int := result;

END bin2int;

PROCEDURE int2bin (int : IN INTEGER; bin : OUT BIT_VECTOR) IS

VARIABLE tmp : INTEGER;

BEGIN

tmp := int;

FOR i IN 0 TO (bin'LENGTH - 1) LOOP

IF (tmp MOD 2 = 1) THEN bin (i) := '1';

ELSE bin (i) := '0';

END IF;

tmp := tmp / 2;

END LOOP;

END int2bin;

PROCEDURE apply_data ( SIGNAL target : OUT BIT_VECTOR;

CONSTANT values : IN integer_vector; CONSTANT period : IN TIME)

IS

VARIABLE buf : BIT_VECTOR (target'RANGE);

BEGIN

FOR i IN values'RANGE LOOP

int2bin (values(i), buf);

target <= TRANSPORT buf AFTER i * period;

END LOOP;

END apply_data;®BB¯

PROCEDURE assign_bits (

SIGNAL s : OUT BIT; file_name : IN STRING; period : IN TIME)

IS

VARIABLE char : CHARACTER;

VARIABLE current : TIME := 0 NS;

FILE input_value_file : logic_data;

BEGIN

FILE_OPEN (input_value_file, file_name, READ_MODE);

WHILE NOT ENDFILE (input_value_file) LOOP

READ (input_value_file, char);

IF char = '0' OR char = '1' THEN

current := current + period;

IF char = '0' THEN

s <= TRANSPORT '0' AFTER current;

ELSIF char = '1' THEN

s <= TRANSPORT '1' AFTER current;

END IF;

END IF;

END LOOP;

END assign_bits;

PROCEDURE assign_bits (

SIGNAL s : OUT qit; file_name : IN STRING; period : IN TIME)

IS

VARIABLE char : CHARACTER;

VARIABLE current : TIME := 0 NS;

FILE input_value_file : logic_data;

BEGIN

FILE_OPEN (input_value_file, file_name, READ_MODE);

WHILE NOT ENDFILE (input_value_file) LOOP

READ (input_value_file, char);

current := current + period;

CASE char IS

WHEN '0' => s <= TRANSPORT '0' AFTER current;

WHEN '1' => s <= TRANSPORT '1' AFTER current;

WHEN 'Z' | 'z' => s <= TRANSPORT 'Z' AFTER current;

WHEN 'X' | 'x' => s <= TRANSPORT 'X' AFTER current;

WHEN OTHERS => current := current - period;

END CASE;

END LOOP;

END assign_bits;

END basic_utilities;

FIGURE 7. 50

Present form of the basic_utilities package