- BlackBox: name: GHC.Prim.gtChar# kind: Expression type: 'gtChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.geChar# kind: Expression type: 'geChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.eqChar# kind: Expression type: 'eqChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.neChar# kind: Expression type: 'neChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.ltChar# kind: Expression type: 'ltChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.leChar# kind: Expression type: 'leChar# :: Char# -> Char# -> Int#' template: '(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.ord# kind: Expression type: 'ord :: Char# -> Int#' template: $signed({{(~SIZE[~TYPO]-~SIZE[~TYP[0]]) {1'b0}},~VAR[c][0]}) - BlackBox: name: GHC.Prim.*# kind: Expression type: '(*#) :: Int# -> Int# -> Int#' template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.remInt# kind: Expression type: 'remInt# :: Int# -> Int# -> Int#' template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.andI# kind: Expression type: 'andI# :: Int# -> Int# -> Int#' template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.orI# kind: Expression type: 'orI# :: Int# -> Int# -> Int#' template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xorI# kind: Expression type: 'xorI# :: Int# -> Int# -> Int#' template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.notI# kind: Expression type: 'notI# :: Int# -> Int#' template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.negateInt# kind: Expression type: 'negateInt# :: Int# -> Int#' template: -(~ARG[0]) - BlackBox: name: GHC.Prim.># kind: Expression type: '(>#) :: Int# -> Int# -> Int#' template: '(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.>=# kind: Expression type: '(>=#) :: Int# -> Int# -> Int#' template: '(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.==# kind: Expression type: '(==) :: Int# -> Int# -> Int#' template: '(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim./=# kind: Expression type: '(/=#) :: Int# -> Int# -> Int#' template: '(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.<# kind: Expression type: '(<#) :: Int# -> Int# -> Int#' template: '(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.<=# kind: Expression type: '(<=#) :: Int# -> Int# -> Int#' template: '(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.chr# kind: Expression type: 'ord :: Int# -> Char#' template: $unsigned(~VAR[i][0][0+:~SIZE[~TYPO]]) - BlackBox: name: GHC.Prim.int2Word# kind: Expression type: 'int2Word# :: Int# -> Word#' template: $unsigned(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.uncheckedIShiftL# kind: Expression type: 'uncheckedIShiftL# :: Int# -> Int# -> Int#' template: ~ARG[0] <<< ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedIShiftRA# kind: Expression type: 'uncheckedIShiftRA# :: Int# -> Int# -> Int#' template: ~ARG[0] >>> ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedIShiftRL# kind: Expression type: 'uncheckedIShiftRL# :: Int# -> Int# -> Int#' template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.timesWord# kind: Expression type: 'timesWord# :: Word# -> Word# -> Word#' template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.remWord# kind: Expression type: 'remWord# :: Word# -> Word# -> Word#' template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.and# kind: Expression type: 'and# :: Word# -> Word# -> Word#' template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.or# kind: Expression type: 'or# :: Word# -> Word# -> Word#' template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xor# kind: Expression type: 'xor# :: Word# -> Word# -> Word#' template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.not# kind: Expression type: 'not# :: Word# -> Word#' template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.uncheckedShiftL# kind: Expression type: 'uncheckedShiftL# :: Word# -> Int# -> Word#' template: ~ARG[0] << ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRL# kind: Expression type: 'uncheckedShiftRL# :: Word# -> Int# -> Word#' template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.word2Int# kind: Expression type: 'int2Word# :: Word# -> Int#' template: $signed(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.gtWord# kind: Expression type: 'gtWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.geWord# kind: Expression type: 'geWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.eqWord# kind: Expression type: 'eqWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.neWord# kind: Expression type: 'neWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.ltWord# kind: Expression type: 'ltWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.leWord# kind: Expression type: 'leWord# :: Word# -> Word# -> Int#' template: '(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]''sd1 : ~SIZE[~TYPO]''sd0' - BlackBox: name: GHC.Prim.byteSwap16# kind: Declaration type: 'byteSwap16# :: Word# -> Word#' template: |- // byteSwap16 begin~IF ~IW64 ~THEN assign ~RESULT = {~VAR[w][0][63:16],~VAR[w][0][7:0],~VAR[w][0][15:8]};~ELSE assign ~RESULT = {~VAR[w][0][31:16],~VAR[w][0][7:0],~VAR[w][0][15:8]};~FI // byteSwap16 end workInfo: Never - BlackBox: name: GHC.Prim.byteSwap32# kind: Declaration type: 'byteSwap32# :: Word# -> Word#' template: |- // byteSwap32 begin~IF ~IW64 ~THEN assign ~RESULT = {~VAR[w][0][63:32],~VAR[w][0][7:0],~VAR[w][0][15:8],~VAR[w][0][23:16],~VAR[w][0][31:24]};~ELSE assign ~RESULT = {~VAR[w][0][7:0],~VAR[w][0][15:8],~VAR[w][0][23:16],~VAR[w][0][31:24]};~FI // byteSwap32 end workInfo: Never - BlackBox: name: GHC.Prim.byteSwap64# kind: Declaration type: 'byteSwap64# :: Word# -> Word#' template: |- // byteSwap64 begin assign ~RESULT = {~VAR[w][0][7:0],~VAR[w][0][15:8],~VAR[w][0][23:16],~VAR[w][0][31:24] ,~VAR[w][0][39:32],~VAR[w][0][47:40],~VAR[w][0][55:48],~VAR[w][0][63:56]}; // byteSwap64 end workInfo: Never - BlackBox: name: GHC.Prim.byteSwap# kind: Declaration type: 'byteSwap# :: Word# -> Word#' template: |- // byteSwap begin~IF ~IW64 ~THEN assign ~RESULT = {~VAR[w][0][7:0],~VAR[w][0][15:8],~VAR[w][0][23:16],~VAR[w][0][31:24] ,~VAR[w][0][39:32],~VAR[w][0][47:40],~VAR[w][0][55:48],~VAR[w][0][63:56]};~ELSE assign ~RESULT = {~VAR[w][0][7:0],~VAR[w][0][15:8],~VAR[w][0][23:16],~VAR[w][0][31:24]};~FI // byteSwap end workInfo: Never - BlackBox: name: GHC.Prim.narrow8Int# kind: Declaration type: 'narrow8Int# :: Int# -> Int#' template: |- // narrow8Int begin assign ~RESULT = $signed(~VAR[i][0][7:0]); // narrow8Int end workInfo: Never - BlackBox: name: GHC.Prim.narrow16Int# kind: Declaration type: 'narrow16Int# :: Int# -> Int#' template: |- // narrow16Int begin assign ~RESULT = $signed(~VAR[i][0][15:0]); // narrow16Int end workInfo: Never - BlackBox: name: GHC.Prim.narrow32Int# kind: Declaration type: 'narrow32Int# :: Int# -> Int#' template: |- // narrow32Int begin assign ~RESULT = $signed(~VAR[i][0][31:0]); // narrow32Int end workInfo: Never - BlackBox: name: GHC.Prim.narrow8Word# kind: Declaration type: 'narrow8Int# :: Word# -> Word#' template: |- // narrow8Word begin assign ~RESULT = $unsigned(~VAR[w][0][7:0]); // narrow8Word end workInfo: Never - BlackBox: name: GHC.Prim.narrow16Word# kind: Declaration type: 'narrow16Word# :: Word# -> Word#' template: |- // narrow16Word begin assign ~RESULT = $unsigned(~VAR[w][0][15:0]); // narrow16Word end workInfo: Never - BlackBox: name: GHC.Prim.narrow32Word# kind: Declaration type: 'narrow32Int# :: Word# -> Word#' template: |- // narrow32Word begin assign ~RESULT = $unsigned(~VAR[w][0][31:0]); // narrow32Word end workInfo: Never - BlackBox: name: GHC.Prim.bitReverse# kind: Declaration type: 'bitReverse# :: Word# -> Word#' template: |- // bitReverse begin genvar ~GENSYM[i][0]; ~GENERATE for (~SYM[0] = 0; ~SYM[0] < ~IF ~IW64 ~THEN 64 ~ELSE 32 ~FI; ~SYM[0]=~SYM[0]+1) begin : ~GENSYM[bitReverse][2] assign ~RESULT[~SYM[0]] = ~VAR[x][0][~IF ~IW64 ~THEN 63 ~ELSE 31 ~FI-~SYM[0]]; end ~ENDGENERATE // bitReverse end workInfo: Never - BlackBox: name: GHC.Prim.bitReverse8# kind: Declaration type: 'bitReverse8# :: Word# -> Word#' template: |- // bitReverse8 begin genvar ~GENSYM[i][0]; ~GENERATE for (~SYM[0] = 0; ~SYM[0] < 8; ~SYM[0]=~SYM[0]+1) begin : ~GENSYM[bitReverse8][2] assign ~RESULT[~SYM[0]] = ~VAR[x][0][7-~SYM[0]]; end ~ENDGENERATE // bitReverse8 end workInfo: Never - BlackBox: name: GHC.Prim.bitReverse16# kind: Declaration type: 'bitReverse16# :: Word# -> Word#' template: |- // bitReverse16 begin genvar ~GENSYM[i][0]; ~GENERATE for (~SYM[0] = 0; ~SYM[0] < 16; ~SYM[0]=~SYM[0]+1) begin : ~GENSYM[bitReverse16][2] assign ~RESULT[~SYM[0]] = ~VAR[x][0][15-~SYM[0]]; end ~ENDGENERATE // bitReverse16 end workInfo: Never - BlackBox: name: GHC.Prim.bitReverse32# kind: Declaration type: 'bitReverse32# :: Word# -> Word#' template: |- // bitReverse32 begin genvar ~GENSYM[i][0]; ~GENERATE for (~SYM[0] = 0; ~SYM[0] < 32; ~SYM[0]=~SYM[0]+1) begin : ~GENSYM[bitReverse32][2] assign ~RESULT[~SYM[0]] = ~VAR[x][0][31-~SYM[0]]; end ~ENDGENERATE // bitReverse32 end workInfo: Never - BlackBox: name: GHC.Prim.bitReverse64# kind: Declaration type: 'bitReverse64# :: Word# -> Word#' template: |- // bitReverse64 begin genvar ~GENSYM[i][0]; ~GENERATE for (~SYM[0] = 0; ~SYM[0] < 64; ~SYM[0]=~SYM[0]+1) begin : ~GENSYM[bitReverse64][2] assign ~RESULT[~SYM[0]] = ~VAR[x][0][63-~SYM[0]]; end ~ENDGENERATE // bitReverse64 end workInfo: Never - BlackBox: name: GHC.Prim.quotInt# kind: Expression type: 'quotInt# :: Int# -> Int# -> Int#' template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.quotWord# kind: Expression type: 'quotWord# :: Word# -> Word# -> Word#' template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.int8ToInt# kind: Declaration template: |- // int8ToInt begin assign ~RESULT = ~ARG[0]; // int8ToInt end workInfo: Never - BlackBox: name: GHC.Prim.intToInt8# kind: Declaration template: |- // intToInt8 begin assign ~RESULT = ~ARG[0]; // intToInt8 end workInfo: Never - BlackBox: name: GHC.Prim.negateInt8# kind: Expression template: -(~ARG[0]) - BlackBox: name: GHC.Prim.timesInt8# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotInt8# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remInt8# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftLInt8# kind: Expression template: ~ARG[0] <<< ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRAInt8# kind: Expression template: ~ARG[0] >>> ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLInt8# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.int8ToWord8# kind: Expression template: $unsigned(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqInt8# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geInt8# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtInt8# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leInt8# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltInt8# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neInt8# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.word8ToWord# kind: Declaration template: |- // word8ToWord begin assign ~RESULT = ~ARG[0]; // word8ToWord end workInfo: Never - BlackBox: name: GHC.Prim.wordToWord8# kind: Declaration template: |- // wordToWord8 begin assign ~RESULT = ~ARG[0]; // wordToWord8 end workInfo: Never - BlackBox: name: GHC.Prim.timesWord8# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotWord8# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remWord8# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.andWord8# kind: Expression template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.orWord8# kind: Expression template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xorWord8# kind: Expression template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.notWord8# kind: Expression template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.uncheckedShiftLWord8# kind: Expression template: ~ARG[0] << ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLWord8# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.word8ToInt8# kind: Expression template: $signed(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqWord8# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geWord8# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtWord8# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leWord8# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltWord8# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neWord8# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.int16ToInt# kind: Declaration template: |- // int16ToInt begin assign ~RESULT = ~ARG[0]; // int16ToInt end workInfo: Never - BlackBox: name: GHC.Prim.intToInt16# kind: Declaration template: |- // intToInt16 begin assign ~RESULT = ~ARG[0]; // intToInt16 end workInfo: Never - BlackBox: name: GHC.Prim.negateInt16# kind: Expression template: -(~ARG[0]) - BlackBox: name: GHC.Prim.timesInt16# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotInt16# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remInt16# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftLInt16# kind: Expression template: ~ARG[0] <<< ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRAInt16# kind: Expression template: ~ARG[0] >>> ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLInt16# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.int16ToWord16# kind: Expression template: $unsigned(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqInt16# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geInt16# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtInt16# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leInt16# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltInt16# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neInt16# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.word16ToWord# kind: Declaration template: |- // word16ToWord begin assign ~RESULT = ~ARG[0]; // word16ToWord end workInfo: Never - BlackBox: name: GHC.Prim.wordToWord16# kind: Declaration template: |- // wordToWord16 begin assign ~RESULT = ~ARG[0]; // wordToWord16 end workInfo: Never - BlackBox: name: GHC.Prim.timesWord16# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotWord16# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remWord16# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.andWord16# kind: Expression template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.orWord16# kind: Expression template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xorWord16# kind: Expression template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.notWord16# kind: Expression template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.uncheckedShiftLWord16# kind: Expression template: ~ARG[0] << ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLWord16# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.word16ToInt16# kind: Expression template: $signed(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqWord16# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geWord16# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtWord16# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leWord16# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltWord16# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neWord16# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.int32ToInt# kind: Declaration template: |- // int32ToInt begin assign ~RESULT = ~ARG[0]; // int32ToInt end workInfo: Never - BlackBox: name: GHC.Prim.intToInt32# kind: Declaration template: |- // intToInt32 begin assign ~RESULT = ~ARG[0]; // intToInt32 end workInfo: Never - BlackBox: name: GHC.Prim.negateInt32# kind: Expression template: -(~ARG[0]) - BlackBox: name: GHC.Prim.timesInt32# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotInt32# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remInt32# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftLInt32# kind: Expression template: ~ARG[0] <<< ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRAInt32# kind: Expression template: ~ARG[0] >>> ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLInt32# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.int32ToWord32# kind: Expression template: $unsigned(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqInt32# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geInt32# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtInt32# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leInt32# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltInt32# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neInt32# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.word32ToWord# kind: Declaration template: |- // word32ToWord begin assign ~RESULT = ~ARG[0]; // word32ToWord end workInfo: Never - BlackBox: name: GHC.Prim.wordToWord32# kind: Declaration template: |- // wordToWord32 begin assign ~RESULT = ~ARG[0]; // wordToWord32 end workInfo: Never - BlackBox: name: GHC.Prim.timesWord32# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotWord32# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remWord32# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.andWord32# kind: Expression template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.orWord32# kind: Expression template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xorWord32# kind: Expression template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.notWord32# kind: Expression template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.uncheckedShiftLWord32# kind: Expression template: ~ARG[0] << ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRLWord32# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.word32ToInt32# kind: Expression template: $signed(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqWord32# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geWord32# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtWord32# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leWord32# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltWord32# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neWord32# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.int64ToInt# kind: Declaration template: |- // int64ToInt begin assign ~RESULT = ~ARG[0]; // int64ToInt end workInfo: Never - BlackBox: name: GHC.Prim.intToInt64# kind: Declaration template: |- // intToInt64 begin assign ~RESULT = ~ARG[0]; // intToInt64 end workInfo: Never - BlackBox: name: GHC.Prim.negateInt64# kind: Expression template: -(~ARG[0]) - BlackBox: name: GHC.Prim.timesInt64# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotInt64# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remInt64# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedIShiftL64# kind: Expression template: ~ARG[0] <<< ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedIShiftRA64# kind: Expression template: ~ARG[0] >>> ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedIShiftRL64# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.int64ToWord64# kind: Expression template: $unsigned(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqInt64# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geInt64# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtInt64# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leInt64# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltInt64# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neInt64# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.word64ToWord# kind: Declaration template: |- // word64ToWord begin assign ~RESULT = ~ARG[0]; // word64ToWord end workInfo: Never - BlackBox: name: GHC.Prim.wordToWord64# kind: Declaration template: |- // wordToWord64 begin assign ~RESULT = ~ARG[0]; // wordToWord64 end workInfo: Never - BlackBox: name: GHC.Prim.timesWord64# kind: Expression template: ~ARG[0] * ~ARG[1] - BlackBox: name: GHC.Prim.quotWord64# kind: Expression template: ~ARG[0] / ~ARG[1] - BlackBox: name: GHC.Prim.remWord64# kind: Expression template: ~ARG[0] % ~ARG[1] - BlackBox: name: GHC.Prim.and64# kind: Expression template: ~ARG[0] & ~ARG[1] - BlackBox: name: GHC.Prim.or64# kind: Expression template: ~ARG[0] | ~ARG[1] - BlackBox: name: GHC.Prim.xor64# kind: Expression template: ~ARG[0] ^ ~ARG[1] - BlackBox: name: GHC.Prim.not64# kind: Expression template: ~ ~ARG[0] - BlackBox: name: GHC.Prim.uncheckedShiftL64# kind: Expression template: ~ARG[0] << ~ARG[1] - BlackBox: name: GHC.Prim.uncheckedShiftRL64# kind: Expression template: ~ARG[0] >> ~ARG[1] - BlackBox: name: GHC.Prim.word64ToInt64# kind: Expression template: $signed(~ARG[0]) workInfo: Never - BlackBox: name: GHC.Prim.eqWord64# kind: Expression template: "(~ARG[0] == ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.geWord64# kind: Expression template: "(~ARG[0] >= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.gtWord64# kind: Expression template: "(~ARG[0] > ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.leWord64# kind: Expression template: "(~ARG[0] <= ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.ltWord64# kind: Expression template: "(~ARG[0] < ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0" - BlackBox: name: GHC.Prim.neWord64# kind: Expression template: "(~ARG[0] != ~ARG[1]) ? ~SIZE[~TYPO]'sd1 : ~SIZE[~TYPO]'sd0"