Pregunta

Estoy tratando de aprender BNF e intentando reunir un código ASM Z80. Como soy nuevo en ambos campos, mi pregunta es, ¿estoy incluso en el camino correcto? Estoy tratando de escribir el formato de Z80 ASM como EBNF para poder averiguar a dónde ir desde allí para crear el código de la máquina desde la fuente. Por el momento tengo lo siguiente:

Assignment = Identifier, ":" ;

Instruction = Opcode, [ Operand ], [ Operand ] ;

Operand = Identifier | Something* ;

Something* = "(" , Identifier, ")" ;

Identifier = Alpha, { Numeric | Alpha } ;

Opcode = Alpha, Alpha ;

Int = [ "-" ], Numeric, { Numeric } ;

Alpha = "A" | "B" | "C" | "D" | "E" | "F" | 
        "G" | "H" | "I" | "J" | "K" | "L" | 
        "M" | "N" | "O" | "P" | "Q" | "R" | 
        "S" | "T" | "U" | "V" | "W" | "X" | 
        "Y" | "Z" ;

Numeric = "0" | "1" | "2" | "3"| "4" | 
          "5" | "6" | "7" | "8" | "9" ;

Cualquier retroalimentación direccional si me equivoco sería excelente.

¿Fue útil?

Solución

Los ensambladores de la vieja escuela típicamente estaban codificados a mano en el ensamblador y utilizaron técnicas de análisis ADHOC para procesar las líneas de origen de ensamblaje para producir un código de ensamblador real. Cuando la sintaxis del ensamblador es simple (por ejemplo, siempre opcode Reg, operando) esto funcionó lo suficientemente bien.

Las máquinas modernas tienen conjuntos de instrucciones desordenados y desagradables con muchas variaciones de instrucciones y operandos, que pueden expresarse con una sintaxis compleja que permite que múltiples registros de índices participen en la expresión de operandos. Permitir expresiones sofisticadas en tiempo de ensamblaje con constantes fijas y reubicables con varios tipos de operadores de suma lo complica. Ensambladores sofisticados que permiten compilación condicional, macros, declaraciones de datos estructuradas, etc. Todos agregan nuevas demandas sobre la sintaxis. El procesamiento de toda esta sintaxis mediante métodos ad hoc es muy difícil y es la razón por la que se inventaron los generadores analizadores.

El uso de un generador BNF y un analizador es una forma muy razonable de construir un ensamblador moderno, incluso para un procesador heredado como el Z80. He construido tales ensambladores para máquinas de 8 bits de Motorola, como el 6800/6809, y me estoy preparando para hacer lo mismo para un X86 moderno. Creo que te diriges exactamente por el camino correcto.

********** EDITAR **************** La OP preguntó por ejemplo las definiciones de Lexer y Parser. He proporcionado ambos aquí.

Estos son extractos de especificaciones reales para un Asssembler 6809. Las definiciones completas son 2-3x del tamaño de las muestras aquí.

Para mantener el espacio bajo, he editado gran parte de la complejidad de la esquina oscura, que es el punto de estas definiciones. Uno podría estar consternado por la complejidad aparente; El punto es que con tales definiciones, estás tratando de describir La forma del idioma, no lo codifica procesalmente. Pagará una complejidad significativamente mayor si codifica todo esto de manera ad hoc, y será mucho menos mantenible.

También será de alguna ayuda saber que estas definiciones se utilizan con un sistema de análisis de programas de alta gama que tiene herramientas de lexing/análisis como subsistemas, llamadosEl kit de herramientas de reingeniería de software DMS. DMS construirá automáticamente ASTS desde el
Las reglas de la gramática en la especificación del analizador, lo que hace que sea mucho más fácil superar herramientas de análisis. Por último, la especificación del analizador contiene las llamadas declaraciones de "PrettyPrinter", lo que permite que los DMS reinseguen el texto fuente del ASTS. (¡El verdadero propósito del Grammer era permitirnos construir ASTS que representen instrucciones de ensamblador, y luego escupirlas para ser alimentadas a un ensamblador real!)

Una cosa notable: cómo se indican las reglas Lexemes y Gramática (¡el MetaSyntxax!) Varía algo entre los diferentes sistemas de generadores Lexer/Parser. La sintaxis de las especificaciones basadas en DMS no es una excepción. DMS tiene reglas gramaticales relativamente sofisticadas propias, que realmente no son prácticas para explicar en el espacio disponible aquí. Tendrá que vivir con la idea de que otros sistemas usan notaciones similares, para EBNF para reglas y variantes de expresión regulares para Lexemes.

Dados los intereses del OP, puede implementar Lexer/analizadores similares con cualquier herramienta de generador Lexer/analizador, por ejemplo, Flex/YACC, JavaCC, ANTLR, ...

********** Lexer ****************

-- M6809.lex: Lexical Description for M6809
-- Copyright (C) 1989,1999-2002 Ira D. Baxter

%%
#mainmode Label

#macro digit "[0-9]"
#macro hexadecimaldigit "<digit>|[a-fA-F]"

#macro comment_body_character "[\u0009 \u0020-\u007E]" -- does not include NEWLINE

#macro blank "[\u0000 \ \u0009]"

#macro hblanks "<blank>+"

#macro newline "\u000d \u000a? \u000c? | \u000a \u000c?" -- form feed allowed only after newline

#macro bare_semicolon_comment "\; <comment_body_character>* "

#macro bare_asterisk_comment "\* <comment_body_character>* "

...[snip]

#macro hexadecimal_digit "<digit> | [a-fA-F]"

#macro binary_digit "[01]"

#macro squoted_character "\' [\u0021-\u007E]"

#macro string_character "[\u0009 \u0020-\u007E]"

%%Label -- (First mode) processes left hand side of line: labels, opcodes, etc.

#skip "(<blank>*<newline>)+"
#skip "(<blank>*<newline>)*<blank>+"
  << (GotoOpcodeField ?) >>

#precomment "<comment_line><newline>"

#preskip "(<blank>*<newline>)+"
#preskip "(<blank>*<newline>)*<blank>+"
  << (GotoOpcodeField ?) >>

-- Note that an apparant register name is accepted as a label in this mode
#token LABEL [STRING] "<identifier>"
  <<  (local (;; (= [TokenScan natural] 1) ; process all string characters
         (= [TokenLength natural] ?:TokenCharacterCount)=
         (= [TokenString (reference TokenBodyT)] (. ?:TokenCharacters))
         (= [Result (reference string)] (. ?:Lexeme:Literal:String:Value))
         [ThisCharacterCode natural]
         (define Ordinala #61)
         (define Ordinalf #66)
         (define OrdinalA #41)
         (define OrdinalF #46)
     );;
     (;; (= (@ Result) `') ; start with empty string
     (while (<= TokenScan TokenLength)
      (;;   (= ThisCharacterCode (coerce natural TokenString:TokenScan))  
        (+= TokenScan) ; bump past character
        (ifthen (>= ThisCharacterCode Ordinala)
           (-= ThisCharacterCode #20) ; fold to upper case
        )ifthen
        (= (@ Result) (append (@ Result) (coerce character ThisCharacterCode)))=

        );;
     )while
     );;
  )local
  (= ?:Lexeme:Literal:String:Format (LiteralFormat:MakeCompactStringLiteralFormat 0))  ; nothing interesting in string
  (GotoLabelList ?)
  >>

%%OpcodeField

#skip "<hblanks>"
  << (GotoEOLComment ?) >>
#ifnotoken
  << (GotoEOLComment ?) >>

-- Opcode field tokens
#token 'ABA'       "[aA][bB][aA]"
   << (GotoEOLComment ?) >>
#token 'ABX'       "[aA][bB][xX]"
   << (GotoEOLComment ?) >>
#token 'ADC'       "[aA][dD][cC]"
   << (GotoABregister ?) >>
#token 'ADCA'      "[aA][dD][cC][aA]"
   << (GotoOperand ?) >>
#token 'ADCB'      "[aA][dD][cC][bB]"
   << (GotoOperand ?) >>
#token 'ADCD'      "[aA][dD][cC][dD]"
   << (GotoOperand ?) >>
#token 'ADD'       "[aA][dD][dD]"
   << (GotoABregister ?) >>
#token 'ADDA'      "[aA][dD][dD][aA]"
   << (GotoOperand ?) >>
#token 'ADDB'      "[aA][dD][dD][bB]"
   << (GotoOperand ?) >>
#token 'ADDD'      "[aA][dD][dD][dD]"
   << (GotoOperand ?) >>
#token 'AND'       "[aA][nN][dD]"
   << (GotoABregister ?) >>
#token 'ANDA'      "[aA][nN][dD][aA]"
   << (GotoOperand ?) >>
#token 'ANDB'      "[aA][nN][dD][bB]"
   << (GotoOperand ?) >>
#token 'ANDCC'     "[aA][nN][dD][cC][cC]"
   << (GotoRegister ?) >>
...[long list of opcodes snipped]

#token IDENTIFIER [STRING] "<identifier>"
  <<  (local (;; (= [TokenScan natural] 1) ; process all string characters
         (= [TokenLength natural] ?:TokenCharacterCount)=
         (= [TokenString (reference TokenBodyT)] (. ?:TokenCharacters))
         (= [Result (reference string)] (. ?:Lexeme:Literal:String:Value))
         [ThisCharacterCode natural]
         (define Ordinala #61)
         (define Ordinalf #66)
         (define OrdinalA #41)
         (define OrdinalF #46)
     );;
     (;; (= (@ Result) `') ; start with empty string
     (while (<= TokenScan TokenLength)
      (;;   (= ThisCharacterCode (coerce natural TokenString:TokenScan))  
        (+= TokenScan) ; bump past character
        (ifthen (>= ThisCharacterCode Ordinala)
           (-= ThisCharacterCode #20) ; fold to upper case
        )ifthen
        (= (@ Result) (append (@ Result) (coerce character ThisCharacterCode)))=

        );;
     )while
     );;
  )local
  (= ?:Lexeme:Literal:String:Format (LiteralFormat:MakeCompactStringLiteralFormat 0))  ; nothing interesting in string
  (GotoOperandField ?)
  >>

#token '#'   "\#" -- special constant introduction (FDB)
   << (GotoDataField ?) >>

#token NUMBER [NATURAL] "<decimal_number>"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertDecimalTokenStringToNatural (. format) ? 0 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
 (GotoOperandField ?)
  >>

#token NUMBER [NATURAL] "\$ <hexadecimal_digit>+"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertHexadecimalTokenStringToNatural (. format) ? 1 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
 (GotoOperandField ?)
  >>

#token NUMBER [NATURAL] "\% <binary_digit>+"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertBinaryTokenStringToNatural (. format) ? 1 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
 (GotoOperandField ?)
  >>

#token CHARACTER [CHARACTER] "<squoted_character>"
  <<  (= ?:Lexeme:Literal:Character:Value (TokenStringCharacter ? 2))
  (= ?:Lexeme:Literal:Character:Format (LiteralFormat:MakeCompactCharacterLiteralFormat 0 0)) ; nothing special about character
  (GotoOperandField ?)
  >>


%%OperandField

#skip "<hblanks>"
  << (GotoEOLComment ?) >>
#ifnotoken
  << (GotoEOLComment ?) >>

-- Tokens signalling switch to index register modes
#token ','   "\,"
   <<(GotoRegisterField ?)>>
#token '['   "\["
   <<(GotoRegisterField ?)>>

-- Operators for arithmetic syntax
#token '!!'  "\!\!"
#token '!'   "\!"
#token '##'  "\#\#"
#token '#'   "\#"
#token '&'   "\&"
#token '('   "\("
#token ')'   "\)"
#token '*'   "\*"
#token '+'   "\+"
#token '-'   "\-"
#token '/'   "\/"
#token '//'   "\/\/"
#token '<'   "\<"
#token '<'   "\<" 
#token '<<'  "\<\<"
#token '<='  "\<\="
#token '</'  "\<\/"
#token '='   "\="
#token '>'   "\>"
#token '>'   "\>"
#token '>='  "\>\="
#token '>>'  "\>\>"
#token '>/'  "\>\/"
#token '\\'  "\\"
#token '|'   "\|"
#token '||'  "\|\|"

#token NUMBER [NATURAL] "<decimal_number>"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertDecimalTokenStringToNatural (. format) ? 0 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
  >>

#token NUMBER [NATURAL] "\$ <hexadecimal_digit>+"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertHexadecimalTokenStringToNatural (. format) ? 1 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
  >>

#token NUMBER [NATURAL] "\% <binary_digit>+"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertBinaryTokenStringToNatural (. format) ? 1 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
  >>

-- Notice that an apparent register is accepted as a label in this mode
#token IDENTIFIER [STRING] "<identifier>"
  <<  (local (;; (= [TokenScan natural] 1) ; process all string characters
         (= [TokenLength natural] ?:TokenCharacterCount)=
         (= [TokenString (reference TokenBodyT)] (. ?:TokenCharacters))
         (= [Result (reference string)] (. ?:Lexeme:Literal:String:Value))
         [ThisCharacterCode natural]
         (define Ordinala #61)
         (define Ordinalf #66)
         (define OrdinalA #41)
         (define OrdinalF #46)
     );;
     (;; (= (@ Result) `') ; start with empty string
     (while (<= TokenScan TokenLength)
      (;;   (= ThisCharacterCode (coerce natural TokenString:TokenScan))  
        (+= TokenScan) ; bump past character
        (ifthen (>= ThisCharacterCode Ordinala)
           (-= ThisCharacterCode #20) ; fold to upper case
        )ifthen
        (= (@ Result) (append (@ Result) (coerce character ThisCharacterCode)))=

        );;
     )while
     );;
  )local
  (= ?:Lexeme:Literal:String:Format (LiteralFormat:MakeCompactStringLiteralFormat 0))  ; nothing interesting in string
  >>

%%Register -- operand field for TFR, ANDCC, ORCC, EXG opcodes

#skip "<hblanks>"
#ifnotoken << (GotoRegisterField ?) >>

%%RegisterField -- handles registers and indexing mode syntax
-- In this mode, names that look like registers are recognized as registers

#skip "<hblanks>"
  << (GotoEOLComment ?) >>
#ifnotoken
  << (GotoEOLComment ?) >>

#token '['   "\["
#token ']'   "\]"
#token '--'  "\-\-"
#token '++'  "\+\+"

#token 'A'      "[aA]"
#token 'B'      "[bB]"
#token 'CC'     "[cC][cC]"
#token 'DP'     "[dD][pP] | [dD][pP][rR]" -- DPR shouldnt be needed, but found one instance
#token 'D'      "[dD]"
#token 'Z'      "[zZ]"

-- Index register designations
#token 'X'      "[xX]"
#token 'Y'      "[yY]"
#token 'U'      "[uU]"
#token 'S'      "[sS]"
#token 'PCR'    "[pP][cC][rR]"
#token 'PC'     "[pP][cC]"

#token ','    "\,"

-- Operators for arithmetic syntax
#token '!!'  "\!\!"
#token '!'   "\!"
#token '##'  "\#\#"
#token '#'   "\#"
#token '&'   "\&"
#token '('   "\("
#token ')'   "\)"
#token '*'   "\*"
#token '+'   "\+"
#token '-'   "\-"
#token '/'   "\/"
#token '<'   "\<"
#token '<'   "\<" 
#token '<<'  "\<\<"
#token '<='  "\<\="
#token '<|'  "\<\|"
#token '='   "\="
#token '>'   "\>"
#token '>'   "\>"
#token '>='  "\>\="
#token '>>'  "\>\>"
#token '>|'  "\>\|"
#token '\\'  "\\"
#token '|'   "\|"
#token '||'  "\|\|"

#token NUMBER [NATURAL] "<decimal_number>"
  << (local [format LiteralFormat:NaturalLiteralFormat]
    (;; (= ?:Lexeme:Literal:Natural:Value (ConvertDecimalTokenStringToNatural (. format) ? 0 0))
    (= ?:Lexeme:Literal:Natural:Format (LiteralFormat:MakeCompactNaturalLiteralFormat format))
    );;
 )local
  >>

... [snip]

%% -- end M6809.lex

****************** PARSER ****************

-- M6809.ATG: Motorola 6809 assembly code parser
-- (C) Copyright 1989;1999-2002 Ira D. Baxter; All Rights Reserved

m6809 = sourcelines ;

sourcelines = ;
sourcelines = sourcelines sourceline EOL ;
  <<PrettyPrinter>>: { V(CV(sourcelines[1]),H(sourceline,A<eol>(EOL))); }

-- leading opcode field symbol should be treated as keyword.

sourceline = ;
sourceline = labels ;
sourceline = optional_labels 'EQU' expression ;
  <<PrettyPrinter>>: { H(optional_labels,A<opcode>('EQU'),A<operand>(expression)); }
sourceline = LABEL 'SET' expression ;
  <<PrettyPrinter>>: { H(A<firstlabel>(LABEL),A<opcode>('SET'),A<operand>(expression)); }
sourceline = optional_label instruction ;
  <<PrettyPrinter>>: { H(optional_label,instruction); }
sourceline = optional_label optlabelleddirective ;
  <<PrettyPrinter>>: { H(optional_label,optlabelleddirective); }
sourceline = optional_label implicitdatadirective ;
  <<PrettyPrinter>>: { H(optional_label,implicitdatadirective); }
sourceline = unlabelleddirective ;
sourceline = '?ERROR' ;
  <<PrettyPrinter>>: { A<opcode>('?ERROR'); }

optional_label = labels ;
optional_label = LABEL ':' ;
  <<PrettyPrinter>>: { H(A<firstlabel>(LABEL),':'); }
optional_label = ;

optional_labels = ;
optional_labels = labels ;
labels = LABEL ;
  <<PrettyPrinter>>: { A<firstlabel>(LABEL); }
labels = labels ',' LABEL ;
  <<PrettyPrinter>>: { H(labels[1],',',A<otherlabels>(LABEL)); }

unlabelleddirective = 'END' ;
  <<PrettyPrinter>>: { A<opcode>('END'); }
unlabelleddirective = 'END' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('END'),A<operand>(expression)); }
unlabelleddirective = 'IF' expression EOL conditional ;
  <<PrettyPrinter>>: { V(H(A<opcode>('IF'),H(A<operand>(expression),A<eol>(EOL))),CV(conditional)); }
unlabelleddirective = 'IFDEF' IDENTIFIER EOL conditional ;
  <<PrettyPrinter>>: { V(H(A<opcode>('IFDEF'),H(A<operand>(IDENTIFIER),A<eol>(EOL))),CV(conditional)); }
unlabelleddirective = 'IFUND' IDENTIFIER EOL conditional ;
  <<PrettyPrinter>>: { V(H(A<opcode>('IFUND'),H(A<operand>(IDENTIFIER),A<eol>(EOL))),CV(conditional)); }
unlabelleddirective = 'INCLUDE' FILENAME ;
  <<PrettyPrinter>>: { H(A<opcode>('INCLUDE'),A<operand>(FILENAME)); }
unlabelleddirective = 'LIST' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('LIST'),A<operand>(expression)); }
unlabelleddirective = 'NAME' IDENTIFIER ;
  <<PrettyPrinter>>: { H(A<opcode>('NAME'),A<operand>(IDENTIFIER)); }
unlabelleddirective = 'ORG' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('ORG'),A<operand>(expression)); }
unlabelleddirective = 'PAGE' ;
  <<PrettyPrinter>>: { A<opcode>('PAGE'); }
unlabelleddirective = 'PAGE' HEADING ;
  <<PrettyPrinter>>: { H(A<opcode>('PAGE'),A<operand>(HEADING)); }
unlabelleddirective = 'PCA' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('PCA'),A<operand>(expression)); }
unlabelleddirective = 'PCC' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('PCC'),A<operand>(expression)); }
unlabelleddirective = 'PSR' expression ;
  <<PrettyPrinter>>: { H(A<opcode>('PSR'),A<operand>(expression)); }
unlabelleddirective = 'TABS' numberlist ;
  <<PrettyPrinter>>: { H(A<opcode>('TABS'),A<operand>(numberlist)); }
unlabelleddirective = 'TITLE' HEADING ;
  <<PrettyPrinter>>: { H(A<opcode>('TITLE'),A<operand>(HEADING)); }
unlabelleddirective = 'WITH' settings ;
  <<PrettyPrinter>>: { H(A<opcode>('WITH'),A<operand>(settings)); }

settings = setting ;
settings = settings ',' setting ;
  <<PrettyPrinter>>: { H*; }
setting = 'WI' '=' NUMBER ;
  <<PrettyPrinter>>: { H*; }
setting = 'DE' '=' NUMBER ;
  <<PrettyPrinter>>: { H*; }
setting = 'M6800' ;
setting = 'M6801' ;
setting = 'M6809' ;
setting = 'M6811' ;

-- collects lines of conditional code into blocks
conditional = 'ELSEIF' expression EOL conditional ;
  <<PrettyPrinter>>: { V(H(A<opcode>('ELSEIF'),H(A<operand>(expression),A<eol>(EOL))),CV(conditional[1])); }
conditional = 'ELSE' EOL else ;
  <<PrettyPrinter>>: { V(H(A<opcode>('ELSE'),A<eol>(EOL)),CV(else)); }
conditional = 'FIN' ;
  <<PrettyPrinter>>: { A<opcode>('FIN'); }
conditional = sourceline EOL conditional ;
  <<PrettyPrinter>>: { V(H(sourceline,A<eol>(EOL)),CV(conditional[1])); }

else = 'FIN' ;
  <<PrettyPrinter>>: { A<opcode>('FIN'); }
else = sourceline EOL else ;
  <<PrettyPrinter>>: { V(H(sourceline,A<eol>(EOL)),CV(else[1])); }

-- keyword-less directive, generates data tables

implicitdatadirective = implicitdatadirective ',' implicitdataitem ;
  <<PrettyPrinter>>: { H*; }
implicitdatadirective = implicitdataitem ;

implicitdataitem = '#' expression ;
  <<PrettyPrinter>>: { A<operand>(H('#',expression)); }
implicitdataitem = '+' expression ;
  <<PrettyPrinter>>: { A<operand>(H('+',expression)); }
implicitdataitem = '-' expression ;
  <<PrettyPrinter>>: { A<operand>(H('-',expression)); }
implicitdataitem = expression ;
  <<PrettyPrinter>>: { A<operand>(expression); }
implicitdataitem = STRING ;
  <<PrettyPrinter>>: { A<operand>(STRING); }

-- instructions valid for m680C (see Software Dynamics ASM manual)
instruction = 'ABA' ;
  <<PrettyPrinter>>: { A<opcode>('ABA'); }
instruction = 'ABX' ;
  <<PrettyPrinter>>: { A<opcode>('ABX'); }

instruction = 'ADC' 'A' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>(H('ADC','A')),A<operand>(operandfetch)); }
instruction = 'ADC' 'B' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>(H('ADC','B')),A<operand>(operandfetch)); }
instruction = 'ADCA' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>('ADCA'),A<operand>(operandfetch)); }
instruction = 'ADCB' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>('ADCB'),A<operand>(operandfetch)); }
instruction = 'ADCD' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>('ADCD'),A<operand>(operandfetch)); }

instruction = 'ADD' 'A' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>(H('ADD','A')),A<operand>(operandfetch)); }
instruction = 'ADD' 'B' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>(H('ADD','B')),A<operand>(operandfetch)); }
instruction = 'ADDA' operandfetch ;
  <<PrettyPrinter>>: { H(A<opcode>('ADDA'),A<operand>(operandfetch)); }

[..snip...]

-- condition code mask for ANDCC and ORCC
conditionmask = '#' expression ;
  <<PrettyPrinter>>: { H*; }
conditionmask = expression ;

target = expression ;

operandfetch = '#' expression ; --immediate
  <<PrettyPrinter>>: { H*; }

operandfetch = memoryreference ;

operandstore = memoryreference ;

memoryreference = '[' indexedreference ']' ;
  <<PrettyPrinter>>: { H*; }
memoryreference = indexedreference ;

indexedreference = offset ;
indexedreference = offset ',' indexregister ;
  <<PrettyPrinter>>: { H*; }
indexedreference = ',' indexregister ;
  <<PrettyPrinter>>: { H*; }
indexedreference = ',' '--' indexregister ;
  <<PrettyPrinter>>: { H*; }
indexedreference = ',' '-' indexregister ;
  <<PrettyPrinter>>: { H*; }
indexedreference = ',' indexregister '++' ;
  <<PrettyPrinter>>: { H*; }
indexedreference = ',' indexregister '+' ;
  <<PrettyPrinter>>: { H*; }

offset = '>' expression ; -- page zero ref
  <<PrettyPrinter>>: { H*; }
offset = '<' expression ; -- long reference
  <<PrettyPrinter>>: { H*; }
offset = expression ;
offset = 'A' ;
offset = 'B' ;
offset = 'D' ;

registerlist = registername ;
registerlist = registerlist ',' registername ;
  <<PrettyPrinter>>: { H*; }

registername = 'A' ;
registername = 'B' ;
registername = 'CC' ;
registername = 'DP' ;
registername = 'D' ;
registername = 'Z' ;
registername = indexregister ;

indexregister = 'X' ;
indexregister = 'Y' ;
indexregister = 'U' ;  -- not legal on M6811
indexregister = 'S' ;
indexregister = 'PCR' ;
indexregister = 'PC' ;

expression = sum '=' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '<<' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '</' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '<=' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '<' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '>>' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '>/' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '>=' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '>' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum '#' sum ;
  <<PrettyPrinter>>: { H*; }
expression = sum ;

sum = product ;
sum = sum '+' product ;
  <<PrettyPrinter>>: { H*; }
sum = sum '-' product ;
  <<PrettyPrinter>>: { H*; }
sum = sum '!' product ;
  <<PrettyPrinter>>: { H*; }
sum = sum '!!' product ;
  <<PrettyPrinter>>: { H*; }

product = term '*' product ;
  <<PrettyPrinter>>: { H*; }
product = term '||' product ; -- wrong?
  <<PrettyPrinter>>: { H*; }
product = term '/' product ;
  <<PrettyPrinter>>: { H*; }
product = term '//' product ;
  <<PrettyPrinter>>: { H*; }
product = term '&' product ;
  <<PrettyPrinter>>: { H*; }
product = term '##' product ;
  <<PrettyPrinter>>: { H*; }
product = term ;

term = '+' term ;
  <<PrettyPrinter>>: { H*; }
term = '-' term ; 
  <<PrettyPrinter>>: { H*; }
term = '\\' term ; -- complement
  <<PrettyPrinter>>: { H*; }
term = '&' term ; -- not

term = IDENTIFIER ;
term = NUMBER ;
term = CHARACTER ;
term = '*' ;
term = '(' expression ')' ;
  <<PrettyPrinter>>: { H*; }

numberlist = NUMBER ;
numberlist = numberlist ',' NUMBER ;
  <<PrettyPrinter>>: { H*; }

Otros consejos

BNF se usa más generalmente para idiomas estructurados y anidados como Pascal, C ++ o realmente cualquier cosa derivada de la familia Algol (que incluye idiomas modernos como C#). Si estuviera implementando un ensamblador, podría usar algunas expresiones regulares simples para que coincidan con el código de operación y los operandos. Ha pasado un tiempo desde que usé el lenguaje de ensamblaje Z80, pero puede usar algo como:

/\s*(\w{2,3})\s+((\w+)(,\w+)?)?/

Esto coincidiría con cualquier línea que consista en un código de operación de dos o tres letras seguido de uno o dos operandos separados por una coma. Después de extraer una línea de ensamblador como esta, miraría el código de operación y generaría los bytes correctos para la instrucción, incluidos los valores de los operandos si corresponde.

El tipo de analizador que he esbozado anteriormente usando expresiones regulares se llamaría un analizador "ad hoc", lo que esencialmente significa que divide y examina la entrada en algún tipo de base de bloque (en el caso del lenguaje de ensamblaje, por línea de texto).

No creo que necesite pensar demasiado. No tiene sentido hacer un analizador que desarme "ld a, a" en una operación de carga, destino y registro de origen, cuando puede hacer que la coincida todo (caso de módulo y espacio en blanco) en un código de operación directamente.

No hay tantos códigos de operación, y no están organizados de tal manera que realmente obtenga mucho beneficio de analizar y comprender al ensamblador IMO. Obviamente, necesitaría un analizador para los argumentos de byte/dirección/indexación, pero aparte de eso, solo tendría una búsqueda individual.

Licenciado bajo: CC-BY-SA con atribución
No afiliado a StackOverflow
scroll top