Presentation is loading. Please wait.

Presentation is loading. Please wait.

Utilities for High Level Description

Similar presentations


Presentation on theme: "Utilities for High Level Description"— Presentation transcript:

1 Utilities for High Level Description
Instructors: Fu-Chiung Cheng (鄭福炯) Associate Professor Computer Science & Engineering Tatung University

2 Outline Type declaration and usage Operators Attributes

3 Type declaration and usage
VHDL is a strongly typed language Type declarations must be used for definition of objects. Operations in VHDL are defined for specific types of operands Basic operators are defined to perform operations on operands General Classes of types: Scalar, composite and file types

4 Enumeration type The basic scalar type is enumeration
Types of STANDARD package of std BIT is an enumeration of ‘0’ and ‘1’ BOOLEAN is an enumeration of FALSE and TRUE CHARACTER: 0~255 Enumeration type TYPE qit IS ('0', '1', 'Z', 'X');

5 Enumeration type Declaration
Declare 4-value qit type

6 Input-Output mapping of an inverter for qit type
in Out == === 0  1 1  0 Z  0 X  X

7 Inverter Declaration USE WORK.basic_utilities.ALL; -- see appendix A
-- 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; -- conditional signal assignment END double_delay;

8 Conditional signal assignment

9 Unaffected Keyword Ex1 Z <= a AFTER 5 NS WHEN d = ’1’ ELSE
UNAFFECTED WHEN e = ’1’ ELSE –Z unchanged b AFTER 5 NS WHEN f = ’1’ ELSE c AFTER 5 NS; Ex2 o1 <= a WHEN cond =’1’ ELSE o1; or o1 <= a WHEN cond =’1’ ELSE UNAFFECTED;

10 Input-Output mapping of a NAND gate in qit logic value system
assume 1 for high impedance

11 VHDL for NAND gate USE WORK.basic_utilities.ALL; -- 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;

12 Inverter with RC timing
Timing depends on the R and C values Exponential timing is 3RC Need floating point numbers

13 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 := ; -- Ohms CONSTANT rpd : REAL := ; -- Ohms END inv_rc; ARCHITECTURE double_delay OF inv_rc IS -- Delay values are calculated based on R and C 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;

14 Type definition for defining the capacitance physical type
TYPE capacitance IS RANGE 0 TO 1E16 UNITS ffr; -- Femto Farads (must have a base unit) pfr = 1000 ffr; nfr = 1000 pfr; ufr = 1000 nfr; mfr = 1000 ufr; far = 1000 mfr; kfr = 1000 far; END UNITS;

15 Type definition for defining the resistance 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;

16 USE WORK.basic_utilities.ALL; -- USE: qit, resistance, capacitance
ENTITY inv_rc IS GENERIC (c_load : capacitance := 66 ffr); PORT (i1 : IN qit; o1 : OUT qit); CONSTANT rpu : resistance := ohms; CONSTANT rpd : resistance := 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;

17 Array Declarations Multidimensional arrays are allowed in VHDL
Array elements must be of the same type Arrays are indexed Arrays can be unbounded Arrays may be ascending or descending

18 Array Declaration 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;

19 Type Declaration

20 Signal Declaration Objects of array type may be initialized when declared If explicit initialization is missing, all elements are initialized to left-most of array element aggregate operation, association by position or association by name SIGNAL sq8 : qit_byte := "ZZZZZZZZ"; SIGNAL sq8 : qit_byte := (‘Z’, ‘Z’, ‘Z’, ‘Z’, ‘1’, ‘1’, ‘1’, ‘1’); SIGNAL sq8 : qit_byte := (5 => ‘Z’, OTHERS => ‘1’); SIGNAL sq8 : qit_byte := (1 DOWN TO 0 => ‘Z’, OTHERS => ‘1’); SIGNAL sq8 : qit_byte := (1 DOWN TO 0 => ‘Z’, 3 TO 4 => ‘X’, OTHERS => ‘1’);

21 Signal declarations and signal assignments
Arrays may be sliced and used on RHS or LHS Aggregate may be used on RHS and LHS Aggregate may concatenate any length or slice size Examples:

22 Signal declarations 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;

23 Signal assignments 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 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;

24 Signal assignments

25 Signal declarations 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 => “ ”); Row 0  Row 1  Row 2  Row 3  SIGNAL sq_4_8 : qit_4by8 := (OTHERS => (0 TO 1 => ‘1’, OTHERS =>’0’)); // same as previous

26 Signal declarations Row 1  X111111X Row 2  X111111X Row 3  XXXXXXXX
SIGNAL sq_4_8 : qit_4by8 := (OTHERS => (OTHERS => ‘Z’)); -- all Z signals sq_4_8 <= ( 3 => (OTHERS => ‘X’), 0 => (OTHERS => ‘X’), OTHERS => (0 => ‘X’, 7 => ‘X’, OTHERS =>’1’); Row 0  XXXXXXXX Row 1  X111111X Row 2  X111111X Row 3  XXXXXXXX

27 Non-integer indexing In most language, array indexing is done only with integer VHDL allows the use of any type indication for index definition of arrays. Example use type as index TYPE qit_2d IS ARRAY (qit, qit) OF qit; Two dimension array of qit elements Index: 0,1,Z,X

28 Non-integer indexing ?? Not a NAND function
CONSTANT qit_nand2_table : qit_2d := ( ‘0’ => (OTHERS => ‘1’), ‘X’ => (‘0’ => ‘1’, OTHERS => ‘X’), OTHERS => (‘0’ => ‘1’, ‘X’ => ‘1’, OTHERS =>’0’)); Row 0  1111 Row 1  1001 Row Z  1001 Row X  1XXX ?? Not a NAND function OTHERS => (‘0’ => ‘1’, ‘X’ => ‘X’, OTHERS =>’0’))

29 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','X','X','X')); BEGIN o1 <= qit_nand2_table (i1, i2) AFTER (tplh + tphl) / 2; END average_delay;

30 Unconstrained Arrays VHDL allow unconstrained arrays.
Useful for developing generic descriptions or designs Example BIT_VECTOR in STANDARD package TYPE BIT_VECTOR IS ARRAY (NATURAL RANGE <>) OF BIT; Range: NATURAL == 0 to the largest allowable integer

31 Unconstrained Arrays Other Examples STRING in STANDARD package
TYPE STRING IS ARRAY (POSITIVE RANGE <>) OF CHARACTER; User defined TYPE integer_vector IS ARRAY (NATURAL RANGE <>) OF INTEGER Cannot have unconstrained array of an unconstrained array;

32 Unconstrained Arrays

33 Unconstrained Arrays for Generic Design
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;

34 Unconstrained Arrays for Generic Design
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 -- next page END structural;

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

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

37 File Type VHDL allows File IO. Specifying file: File type declaration
File Declaration TYPE logic_data IS FILE OF CHARACTER; FILE input_logic_value_file1: logic_data; An explicit OPEN statement must be used for opening

38 File Type File Declaration Can open a file in
FILE input_logic_value_file2: logic_data IS “input.dat”; FILE input_logic_value_file3: logic_data OPEN READ_MODE IS “input.dat”; Can open a file in READ_MODE, WRITE_MODE or APPEND_MODE

39 File Type Declare a logical file, open later (see next page)
FILE output_logic_value_file1: logic_data; Declare a logical file and open with the specified mode FILE output_logic_value_file2: logic_data OPEN WRITE_MODE IS “input.dat”;

40 File Type: Open files An explicit OPEN is needed if file is not implicitly opened FILE_OPEN (input_logic_value_file, “input.dat”, READ_MODE); -- READ_MODE is default and may be dropped FILE_OPEN (output_logic_value_file, “output.dat”, WRITE_MODE); FILE_OPEN(parameter_of_FILE_OPEN_STATUS, output_logic_value_file, “output.dat”, WRITE_MODE); -- Extra parameter can be included Return values of FILE OPEN STATUS: TYPE FILE_OPEN_STATUS IS (OPEN_OK, STATUS_ERROR, NAME_ERROR, MODE_ERROR)

41 File Type: Close files To close a file, use its logical name
FILE_CLOSE (input_logic_value_file); FILE_CLOSE (output_logic_value_file);

42 File Type: Read and Write files
VHDL provides three operations for the file type: READ example: READ (input_value_file, char); WRITE example: WRITE (output_value_file, char); ENDFILE example: ENDFILE (input_value_file) READ and WRITE are procedure calls ENDFILE is a function call

43 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 LOOP; END assign_bits; -- assign_bits (a_signal, "unix_file.bit", 1500 NS); calling this procedure

44 File IO (another way) Declare in an architecture: Call the procedure:
FILE input_value_file: logic_data IS “my_file.bit”; Call the procedure: read_from_file (SIGNAL target : OUT BIT, this_file : IN FILE);

45 VHDL Operators Type and operators are related issues
Operators operate on the operands of give type Operators: Logical operators:AND,OR,NAND,NOR,XOR,NOT Relational operators: =,/=,<,<=,>,>= Shift operators Arithmetic operators: +,-,x,/,sign +-,MOD,REM,ABS Aggregate operators

46 VHDL Logical Operators
Logical operators: AND,OR,NAND,NOR,XOR,NOT Examples: x <= a XNOR b; x_vector <= a_vector AND b_vector; -- bitwise AND x <= “XOR” (a, b); x_vector <= “AND” (a_vector, b_vector); String representing operator symbols can be used as function names for performing the same function as the operator

47 VHDL Relational Operators
Examples: a_boolean <= i1 > i2; b_boolean <= i1 /= i2; -- a_bit_vector=“00011” and b_bit_vector=“00100” a_bit_vector < b_bit_vector -- returns TRUE -- for qit: ‘0’ is less than ‘1’, and ‘X’ is larger all the rest -- qit = {0,1,Z,X} -- for BIT: ‘1’ is greater than ‘0’ -- bit = {0,1}

48 VHDL Shift Operators Shift operators Syntax:
operand SHIFT_OPERATOR number_of_shifts

49 VHDL Shift Operators Shift operators for BIT or BOOLEAN
Logical Shift Right (Left) operation Shifts an array to right, Drops the right(left)-most element Fill the left(right) side with a fill value (left-most enumeration element) left-most enumeration element BIT and qit: 0

50 VHDL Shift Operators Arithmetic Shift Right (Left) operation
Shifts an array to right, Drops the right(left)-most element Fill the left(right) side with left(right)-most element

51 VHDL Shift Operators Examples
qit = 0,1,Z,X

52 VHDL Arithmetic Operators
Operators: +, -, *, /, MOD, REM, **, ABS Examples: a + b “+” (a, b) a_int MOD b_int -- both integers a_int REM b_int -- returns remainder of absolute value division

53 VHDL Aggregate Operators
Operators: & and () Examples: a & b (a, b) (a,b) <= a2; (a,b) <= “10”); (a,b) <= (‘1’,’0’);

54 Function and Procedure overloading
In VHDL, function or procedure with the same name and different types of parameters or results are distinguished with each other A name used by more than one function or procedure is said to be overloaded. Overloading is a useful mechanism for using the same name for functions or procedures that perform the same operation on data of different types.

55 Function and Procedure overloading
Overloading “AND”, “OR” and “NOT” Declare the following in a package 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;

56 Function and Procedure overloading
Define these functions in package body FUNCTION "AND" (a, b : qit) RETURN qit is …. END “AND”; FUNCTION "OR" (a, b : qit) RETURN qit is END “OR”; FUNCTION "NOT" (a : qit) RETURN qit is END “NOT”;

57 FUNCTION "AND" (a, b : qit) RETURN qit IS
CONSTANT qit_and_table : qit_2d := ( ('0','0','0','0'), ('0','1','1','X'), ('0','X','X','X')); BEGIN RETURN qit_and_table (a, b); END "AND";

58 FUNCTION "OR" (a, b : qit) RETURN qit IS
CONSTANT qit_or_table : qit_2d := ( ('0','1','1','X'), ('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'); RETURN qit_not_table (a); END "NOT";

59 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 o1 <= NOT ( i1 AND i2 ) AFTER (tplh + tphl) / 2;

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

61 Operator Overloading Overloading multiplication operator for returning TIME = resistance * capacitance In the declaration: FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME; In a package body: FUNCTION "*" (a : resistance; b : capacitance) RETURN TIME IS BEGIN RETURN ( ( a / 1 l_o) * ( b / 1 ffr ) * 1 FS ) / 1000; END "*";

62 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; first * (resistance * capacitance) second * ??

63 Overloading assign_bits
Overloading the assign_bits procedure for accepting and producing qit data Package head: 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); Package body: Implement assign_bits

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

65 USE WORK.basic_utilities.ALL;
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;

66 Subtypes Subtypes are used for compatibility
SUBTYPE compatible_nibble_bits IS BIT_VECTOR ( 3 DOWNTO 0); compatible_nibble_bits is compatible with BIT_VECTOR TYPE nibble_bits IS ARRAY ( 3 DOWNTO 0 ) OF BIT; nibble_bits is not compatible with BIT_VECTOR Conversion is required for not compatible types Base type of a subtype is the original type

67 Subtypes rit and bin are fully compatible with qit
SUBTYPE rit IS qit RANGE '0' TO 'Z'; SUBTYPE bin IS qit RANGE '0' TO '1';

68 Record Type Arrays are composite type who elements are all the same type Records are also of composite class, but they can consist of elements with different types. Example: instruction set opcode mode address 3 bits 3 bits 11 bits

69 16-bit instruction set 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); TYPE instruction_format IS RECORD opc : opcode; mde : mode; adr : address; END RECORD;

70 16-bit instruction set Declare nop instruction set Assignments:
SIGNAL instr : instruction_format := (nop, 0, " "); Assignments: instr.opc <= lda; instr.mde <= 2; instr.adr <= " "; Record aggregate instr <= (adr => (OTHERS => ‘1’), mde => 2, opc => sub)

71 Alias Declaration An indexed part of a object or a slice of the object can be given alternative names by using an alias declaration. The declaration can be used for signals, variables, or constants. Example: alias c_flag : BIT is flag_register(3) alias v_flag : BIT is flag_register(2) alias n_flag : BIT is flag_register(1) alias z_flag : BIT is flag_register(0)

72 Alias Declaration opcode mode page offset 3 bits 3 bits 3 bits 8 bits
address (11 bits) = page (3 bits) + offset (8 bits) Example: 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); Assignment: page <= "001"; offset <= X"F1"; opcode mode page offset 3 bits 3 bits 3 bits 8 bits

73 Linked-list Declaration
Linked list see Fig 7.35 on page 245 A node has a integer data and a pointer TYPE node; TYPE pointer IS ACCESS node; TYPE node IS RECORD data : INTEGER; link : pointer; END RECORD;

74 Linked-list Declaration
Declaration of head as the head of a linked list to be created: VARIABLE head : pointer := NULL; Assigning the first node to head. head := NEW node; Linking the next node: head.link := NEW node;

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

76 Call Lineup procedure Declare mem:
VARIABLE mem, cache : pointer := NULL; Inserting integers into the mem linked list: lineup (mem, (25, 12, 17, 18, 19, 20));

77 Remove an item from the list
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;

78 Free all items from the 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); -- All nodes must be deallocated END LOOP; END clear; END ll_utilities;

79 Linked-list Package See Fig 7.39 on page 248

80 Global Objects A signal declared in a package can be written to or read by all VHDL bodies Because of concurrency in VHDL, conflicts and indeterminancy may be caused with shared or global variables A shared variable declared in a package is accessible to all bodies that use the package

81 Global Objects Example
SHARED VARIABLE dangerous : INTEGER := 0; Shared variables are not protected against multiple simultaneous READ and WRITE operations.

82 Type Conversion TYPE qit_byte IS ARRAY (7 DOWNTO 0) of qit;
TYPE qit_octal IS ARRAY (7 DOWNTO 0) of qit; . . . SIGNAL qb : qit_byte; SIGNAL qo : qit_octal; qb <= qo; -- CANNOT DO qb <= qit_byte (qo); -- Must do explicit type conversion

83 Predefined Attributes
Predefined attributes in VHDL provide functions for more efficient coding or mechanisms for modeling hardware characteristics. Attributes can be applied to arrays, types, signals and entities Syntax: object’attribute

84 Array Attributes Array attributes are used to find the range, length, or boundaries of arrays Figure 7.41 shows all the predefined array attributes. TYPE qit_4by8 IS ARRAY ( 3 DOWNTO 0, 0 TO 7 ) OF qit; Signal sq_4_8: qit_4by8; sq_4_8’RIGHT(i) is the ith dimension of sq _4_8 sq _4_8’RIGHT = sq_4_8’RIGHT(1)

85 Figure 7.41 Array Attributes
Attribute Description Example Result ======= ========== =============== ============ ‘LEFT Left bound sq_4_8’LEFT(1) 3 ‘RIGHT Right bound sq_4_8’RIGHT 0 sq_4_8’RIGHT(2) 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) 0 TO 7 sq_4_8’RANGE(1) 3 DNTO 0 ‘REVERSE_RANGE Reverse range sq_4_8’REVERSE_RANGE(2) 7 DNTO 0 sq_4_8’REVERSE_RANGE(1) 0 TO 3 ‘LENGTH Length sq_4_8’LENGTH 4 ‘ASCENDING If Ascending sq_4_8’ASCENDING(2) TRUE sq_4_8’ASCENDING(1) FALSE

86 Type Attributes Type attributes are used for accessing elements of defined types and are only valid fo non-array types Note that several type and array attributes use the same name (but meaning is totally different) Note that TYPE qit IS ('0', '1', 'Z', 'X'); TYPE qqit IS (q0, q1, qZ, qX); SUBTYPE rit IS qit RANGE '0' TO 'Z';

87 Figure 7.42 Type Attributes
Attribute Description Example Result ======= =============== =============== ====== ‘BASE Base of type rit’BASE qit ‘LEFT Left bound of rit’LEFT ‘0’ type or subtype qit’LEFT ‘0’ ‘RIGHT Right bound of rit’RIGHT ‘Z’ type or subtype qit’RIGHT ‘X’ ‘HIGH Upper bound of INTEGER’HIGH Large type or subtype rit’HIGH ‘Z’ ‘LOW Lower bound of POSITIVE’LOW 1 type or subtype qit’LOW ‘0’ ‘POS(V) Position of value qit’POS(‘Z’) 2 V in base of type. rit’POS(‘X’) 3 ‘VAL(P) Value at Position qit’VAL(3) ‘X’ P in base of type. rit’VAL(3) ‘X’

88 Figure 7.42 Type Attributes
Attribute Description Example Result ======= =============== =============== ====== ‘SUCC(V) Value, after value rit’SUCC(‘Z’) ‘X’ V in base of type. ‘PRED(V) Value, before value rit’PRED(‘1’) ‘0’ ‘LEFTOF(V) Value, left of value rit’LEFTOF(‘1’) ‘0’ V in base of type. rit’LEFTOF(‘0’) Error ‘RIGHTOF(V) Value, right of value rit’RIGHTOF(‘1’) ‘Z’ V in base of type. rit’RIGHTOF(‘Z’) ‘X’ ‘ASCENDING if range is ascending qit’ASCENDING TRUE qqit’ASCENDING TRUE ‘IMAGE (V) Converts value qit’IMAGE(‘Z’) “’Z’” V of type to string. qqit’IMAGE(qZ) “qZ” ‘VALUE(S) Converts string qqit’VALUE(“qZ”) qZ S to value of type.

89 Signal Attributes Signal attributes are used for objects in the signal class of any type Signal attributes are used for finding events, transactions, or timings of events and transactions on signals Example in Figure 7.43 on page 255

90 Figure 7.44 Signal Attributes Bit: s1

91 Signal Attributes: Falling edge F/F
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; -- (c = '0' AND c‘EVENT)

92 Toggle F/F 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;

93 Entity Attributes Entity attributes may be used to generate a string corresponding to name of signals, components, architectures, entities, .. Attributes: ‘SIMPLE_NAME: Generates simple name of a named entity ‘PATH_NAME: Generates a string containing entity names and labels from the top of hierarchy leading to the named entity. ‘INSTANCE_NAME: Generates a name that contains entity, architecture, and instantiation labels leading to the design entity.

94 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) SIGNAL instance : STRING (1 TO and2'INSTANCE_NAME'LENGTH) BEGIN o1 <= i1 NAND i2 AFTER 3 NS; simple <= nand2'SIMPLE_NAME; instance <= nand2'INSTANCE_NAME; path <= nand2'PATH_NAME; END single_delay;

95 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; --Simple: nand2 --Path: :xoring:u1: --Instance:

96 User-defined Attributes
VHDL allows definition and use of user-defined attributes. User-defined attributes do not have simulation semantics Declaration: ATTRIBTE identifier: type; Ex. ATTRIBUTE sub_dir : STRING; Ex. ATTRIBUTE sub_dir OF brief_d_flip_flop : ENTITY IS “/user/vhdl”;

97 User-defined Attributes
Usage: brief_d_flip_flop’sub_dir evaluates to “/user/vhdl”.

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

99 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; -- rise = 8 NS -- fall = 10 NS

100 Package Basic_utilities package in page 262-264 A package Functions
Procedures Types Attributes Basic_utilities package in page

101 Summary Declaration of types and the usage of objects of various types
Unconstrained array File type, basic I/O, read/write Predefined attributes Basic_utilities package


Download ppt "Utilities for High Level Description"

Similar presentations


Ads by Google