never executed always true always false
    1 module GHC.CmmToAsm.AArch64.Cond  where
    2 
    3 import GHC.Prelude
    4 
    5 -- https://developer.arm.com/documentation/den0024/a/the-a64-instruction-set/data-processing-instructions/conditional-instructions
    6 
    7 -- TODO: This appears to go a bit overboard? Maybe we should stick with what LLVM
    8 -- settled on for fcmp?
    9 -- false: always yields false, regardless of operands.
   10 -- oeq: yields true if both operands are not a QNAN and op1 is equal to op2.
   11 -- ogt: yields true if both operands are not a QNAN and op1 is greater than op2.
   12 -- oge: yields true if both operands are not a QNAN and op1 is greater than or equal to op2.
   13 -- olt: yields true if both operands are not a QNAN and op1 is less than op2.
   14 -- ole: yields true if both operands are not a QNAN and op1 is less than or equal to op2.
   15 -- one: yields true if both operands are not a QNAN and op1 is not equal to op2.
   16 -- ord: yields true if both operands are not a QNAN.
   17 -- ueq: yields true if either operand is a QNAN or op1 is equal to op2.
   18 -- ugt: yields true if either operand is a QNAN or op1 is greater than op2.
   19 -- uge: yields true if either operand is a QNAN or op1 is greater than or equal to op2.
   20 -- ult: yields true if either operand is a QNAN or op1 is less than op2.
   21 -- ule: yields true if either operand is a QNAN or op1 is less than or equal to op2.
   22 -- une: yields true if either operand is a QNAN or op1 is not equal to op2.
   23 -- uno: yields true if either operand is a QNAN.
   24 -- true: always yields true, regardless of operands.
   25 --
   26 -- LLVMs icmp knows about:
   27 -- eq: yields true if the operands are equal, false otherwise. No sign interpretation is necessary or performed.
   28 -- ne: yields true if the operands are unequal, false otherwise. No sign interpretation is necessary or performed.
   29 -- ugt: interprets the operands as unsigned values and yields true if op1 is greater than op2.
   30 -- uge: interprets the operands as unsigned values and yields true if op1 is greater than or equal to op2.
   31 -- ult: interprets the operands as unsigned values and yields true if op1 is less than op2.
   32 -- ule: interprets the operands as unsigned values and yields true if op1 is less than or equal to op2.
   33 -- sgt: interprets the operands as signed values and yields true if op1 is greater than op2.
   34 -- sge: interprets the operands as signed values and yields true if op1 is greater than or equal to op2.
   35 -- slt: interprets the operands as signed values and yields true if op1 is less than op2.
   36 -- sle: interprets the operands as signed values and yields true if op1 is less than or equal to op2.
   37 
   38 data Cond
   39     = ALWAYS -- b.al
   40     | EQ     -- b.eq
   41     | NE     -- b.ne
   42     -- signed
   43     | SLT    -- b.lt
   44     | SLE    -- b.le
   45     | SGE    -- b.ge
   46     | SGT    -- b.gt
   47     -- unsigned
   48     | ULT    -- b.lo
   49     | ULE    -- b.ls
   50     | UGE    -- b.hs
   51     | UGT    -- b.hi
   52     -- ordered
   53     | OLT    -- b.mi
   54     | OLE    -- b.ls
   55     | OGE    -- b.ge
   56     | OGT    -- b.gt
   57     -- unordered
   58     | UOLT   -- b.lt
   59     | UOLE   -- b.le
   60     | UOGE   -- b.pl
   61     | UOGT   -- b.hi
   62     -- others
   63     | NEVER  -- b.nv
   64     | VS     -- oVerflow set
   65     | VC     -- oVerflow clear
   66     deriving Eq