module Language.MIXAL.OpCode where

import Language.MIXAL.AST

-- |Return the numeric version of an opcode.  If the opcode
-- corresponds to a specific field value, return that too; otherwise
-- Nothing.  In the Nothing case, the F value should be supplied by
-- the user and assembled into (or extracted from) the binary
-- instruction.  In the Just case a specific F-value is required to
-- distinguish the opcode based on the instruction involved.
opCode :: OpCode -> (Integer, Maybe Integer)
opCode op =
    case op of
      LDA -> (8, Nothing)
      LDX -> (15, Nothing)
      LD1 -> (9, Nothing)
      LD2 -> (10, Nothing)
      LD3 -> (11, Nothing)
      LD4 -> (12, Nothing)
      LD5 -> (13, Nothing)
      LD6 -> (14, Nothing)

      LDAN -> (16, Nothing)
      LDXN -> (23, Nothing)
      LD1N -> (17, Nothing)
      LD2N -> (18, Nothing)
      LD3N -> (19, Nothing)
      LD4N -> (20, Nothing)
      LD5N -> (21, Nothing)
      LD6N -> (22, Nothing)

      STA -> (24, Nothing)
      STX -> (31, Nothing)
      ST1 -> (25, Nothing)
      ST2 -> (26, Nothing)
      ST3 -> (27, Nothing)
      ST4 -> (28, Nothing)
      ST5 -> (29, Nothing)
      ST6 -> (30, Nothing)
      STJ -> (32, Nothing)
      STZ -> (33, Nothing)

      ADD -> (1, Nothing)
      SUB -> (2, Nothing)
      MUL -> (3, Nothing)
      DIV -> (4, Nothing)

      ENTA -> (48, Just 2)
      ENTX -> (55, Just 2)
      ENT1 -> (49, Just 2)
      ENT2 -> (50, Just 2)
      ENT3 -> (51, Just 2)
      ENT4 -> (52, Just 2)
      ENT5 -> (53, Just 2)
      ENT6 -> (54, Just 2)

      ENNA -> (48, Just 3)
      ENNX -> (55, Just 3)
      ENN1 -> (49, Just 3)
      ENN2 -> (50, Just 3)
      ENN3 -> (51, Just 3)
      ENN4 -> (52, Just 3)
      ENN5 -> (53, Just 3)
      ENN6 -> (54, Just 3)

      INCA -> (48, Just 0)
      INCX -> (55, Just 0)
      INC1 -> (49, Just 0)
      INC2 -> (50, Just 0)
      INC3 -> (51, Just 0)
      INC4 -> (52, Just 0)
      INC5 -> (53, Just 0)
      INC6 -> (54, Just 0)

      DECA -> (48, Just 1)
      DECX -> (55, Just 1)
      DEC1 -> (49, Just 1)
      DEC2 -> (50, Just 1)
      DEC3 -> (51, Just 1)
      DEC4 -> (52, Just 1)
      DEC5 -> (53, Just 1)
      DEC6 -> (54, Just 1)

      CMPA -> (56, Nothing)
      CMPX -> (63, Nothing)
      CMP1 -> (57, Nothing)
      CMP2 -> (58, Nothing)
      CMP3 -> (59, Nothing)
      CMP4 -> (60, Nothing)
      CMP5 -> (61, Nothing)
      CMP6 -> (62, Nothing)

      JMP -> (39, Just 0)
      JSJ -> (39, Just 1)
      JOV -> (39, Just 2)
      JNOV -> (39, Just 3)

      JL -> (39, Just 4)
      JE -> (39, Just 5)
      JG -> (39, Just 6)
      JGE -> (39, Just 7)
      JNE -> (39, Just 8)
      JLE -> (39, Just 9)

      JAN -> (40, Just 0)
      JAZ -> (40, Just 1)
      JAP -> (40, Just 2)
      JANN -> (40, Just 3)
      JANZ -> (40, Just 4)
      JANP -> (40, Just 5)

      JXN -> (47, Just 0)
      JXZ -> (47, Just 1)
      JXP -> (47, Just 2)
      JXNN -> (47, Just 3)
      JXNZ -> (47, Just 4)
      JXNP -> (47, Just 5)

      J1N -> (41, Just 0)
      J1Z -> (41, Just 1)
      J1P -> (41, Just 2)
      J1NN -> (41, Just 3)
      J1NZ -> (41, Just 4)
      J1NP -> (41, Just 5)

      J2N -> (42, Just 0)
      J2Z -> (42, Just 1)
      J2P -> (42, Just 2)
      J2NN -> (42, Just 3)
      J2NZ -> (42, Just 4)
      J2NP -> (42, Just 5)

      J3N -> (43, Just 0)
      J3Z -> (43, Just 1)
      J3P -> (43, Just 2)
      J3NN -> (43, Just 3)
      J3NZ -> (43, Just 4)
      J3NP -> (43, Just 5)

      J4N -> (44, Just 0)
      J4Z -> (44, Just 1)
      J4P -> (44, Just 2)
      J4NN -> (44, Just 3)
      J4NZ -> (44, Just 4)
      J4NP -> (44, Just 5)

      J5N -> (45, Just 0)
      J5Z -> (45, Just 1)
      J5P -> (45, Just 2)
      J5NN -> (45, Just 3)
      J5NZ -> (45, Just 4)
      J5NP -> (45, Just 5)

      J6N -> (46, Just 0)
      J6Z -> (46, Just 1)
      J6P -> (46, Just 2)
      J6NN -> (46, Just 3)
      J6NZ -> (46, Just 4)
      J6NP -> (46, Just 5)

      IN -> (36, Nothing)
      OUT -> (37, Nothing)
      IOC -> (35, Nothing)

      JRED -> (38, Nothing)
      JBUS -> (34, Nothing)

      NUM -> (5, Just 0)
      CHAR -> (5, Just 1)

      SLA -> (6, Just 0)
      SRA -> (6, Just 1)
      SLAX -> (6, Just 2)
      SRAX -> (6, Just 3)
      SLC -> (6, Just 4)
      SRC -> (6, Just 5)

      MOVE -> (7, Nothing)
      NOP -> (0, Nothing)
      HLT -> (5, Just 2)