Mod51 Benchmarks & Details



Some REAL WORLD code, (does YOUR controller sort prime numbers ?!) that illustrate the benefits of Modula-2's low level operations, with the C51 core in embedded control horsepower.
Modula-2 has true NATIVE BOOLEAN types, and BITSET, ROTATE, ELSIF, operators, and has little emphasis on Pointers - all of which adds up to a better 'fit' for embedded control than C!.
Also obvious is the high code clarity of Mod51 - one reason it is three times less error prone than C.

How does your Controller / Language combination compare ?

For more language details see Mod51 Summary


Mod51 Interrupt - Picket Fence D to A Converter

Picket Fence DAC is a high speed, precision DAC.
Key Features for a controller to support this are

  • Boolean Processor
  • Bit Addressable Bytes
  • Priority Control on INTERRUPT

    Other 8 bit CISC/RISC controllers lack some, or all (!) of these abilities, so do not perform this task efficently at all.

    VAR                                                                          
    
     DACaPIN : BOOLEAN AT P1.6;
     DACbPIN : BOOLEAN AT P1.7;
    
     DAC_A, DAC_B, PWM : BYTE BITADDRESSABLE;
     DACa,DACb,SaveCY  : BOOLEAN;
     PeriodCounter     : BYTE;         (* optional, for slower timebases *)
    
    PROCEDURE (*$Is0*) INTERRUPT_1BH; (* Timer1, samples BIT DATA  *)
    BEGIN   (* ===== Example is for 2 x 8 BIT DAC  ================  *)
     SaveCY := CY;
     INC(PWM);      (* roll over does not matter *)
     DACaPIN := DACa;
     DACbPIN := DACb;      (* remove delay-difference in Interrupt as factor *)
                           (* does ONE of these IF statements ONLY *)
     IF PWM.0  THEN        (* 128 Pickets, odd numbers *)
      DACa := DAC_A.7;
      DACb := DAC_B.7;
     ELSIF PWM.1 THEN      (* 64 Pickets xxxx_xx10 *)
      DACa := DAC_A.6;
      DACb := DAC_B.6;
     ELSIF PWM.2 THEN      (* 32 Pickets xxxx_x100 *)
      DACa := DAC_A.5;
      DACb := DAC_B.5;
     ELSIF PWM.3 THEN      (* 16 Pickets xxxx_1000 *)
      DACa := DAC_A.4;
      DACb := DAC_B.4;
     ELSIF PWM.4 THEN      (*  8 Pickets xxx1_0000 *)
      DACa := DAC_A.3;
      DACb := DAC_B.3;
     ELSIF PWM.5 THEN      (*  4 Pickets xx10_0000 *)
      DACa := DAC_A.2;
      DACb := DAC_B.2;
     ELSIF PWM.6 THEN      (*  2 Pickets x010_0000 *)
      DACa := DAC_A.1;
      DACb := DAC_B.1;
     ELSIF PWM.7 THEN      (*  1 Pickets 1000_0000 *)
      DACa := DAC_A.0;
      DACb := DAC_B.0;
     ELSE              (* All LOW, /256 times INT possible.. *)
      DACa := FALSE;
      DACb := FALSE;
     INC(PeriodCounter);
     END;
     CY := SaveCY;
    END INTERRUPT_1BH;    (* core, 129 bytes, for 2 x 8 bit *)
    

    Mod51 Interrupt / Delta Modulation A to D Converter

    Delta Modulation ADC - This runs as a 7 bit delta modulator, for linear ADC. Shows INTERRUPT, and BOOLEAN support. C51 is very good at this type of work - other cores suffer.
    Note: The C51 can code this without any PUSH/POP

    VAR                                                                          
          DELTASIG_Res,
          DELTASIG_Ctr   : BYTE BITADDRESSABLE;
          DACaPIN        : BOOLEAN AT P3.7;
          Comp           : BOOLEAN AT P3.6;     (* 89C2051 family *)
          PeriodCounter  : BYTE BITADDRESSABLE; (* For slower timebases *)
    
    PROCEDURE (*$Is0*) INTERRUPT_0BH; (* Timer0, fast pickets *)
    BEGIN
      IF Comp THEN
        DACaPIN := FALSE;
      ELSE
        DACaPIN := TRUE;
      END;
      IF DELTASIG_Ctr.7 THEN        (* End of cycle, 7 bits... *)
        DeltaValue   := DELTASIG_Res;
        DELTASIG_Res := DELTASIG_Res AND 00H;
        DELTASIG_Ctr := 0FFH;                      (* Start next cycle *)
        INC (PeriodCounter);                       (* For lower timebases *)
        ChkDSRatePin := NOT ChkDSRatePin;          (* Optional CRO Test *)
      ELSIF DACaPIN THEN
        INC (DELTASIG_Res);                 (* Measure averages.. *)
      END;
      INC (DELTASIG_Ctr);                   (* Roll over does not matter *)
    END INTERRUPT_0BH;                      (* Core, 35 bytes *)
    
    

    Mod51 - Real Time 24 Hour Clock

    Looks like simple code - but other compilers/cores have done this with CALLS to subroutines.
    This benchmark is a good test of DATA memory access, which the C51 performs very well - RISC cores like AVR does poorly.

    VAR                                                                          
     Tenths,Seconds,Minutes,Hours : SHORTCARD;
     Tick10 : BOOLEAN; (* Set inside an Interrupt, with 100mS sub-loop *)
    
    PROCEDURE ClockA;
    (* 24 Hours, so 23:59:59:09 ticks over to 00:00:00:00 *)
    BEGIN
     IF NOT Tick10 THEN RETURN; END; (* Not my event, return *)
     Tick10 := FALSE;
     INC(Tenths);
     IF Tenths = 10 THEN
       Tenths := 0;
       INC(Seconds);
       IF Seconds = 60 THEN
         Seconds := 0;
         INC(Minutes);
         IF Minutes = 60 THEN
           Minutes := 0;
           INC(Hours);
           IF Hours = 24 THEN
              Hours := 0;
           END;
         END;
       END;
     END;
    END ClockA;  (* 51 bytes *)
    

    Mod51 Bit Stream Support

    The BITSET type in Mod51 allows ARRAY of BITSET to implement array of bit functions, in the C51 core.
    With a Single variable, you can index any BIT in an array of BITSET typed Bytes - these can be in IDATA.
    This example shows INTERRUPT, and BOOLEAN support, and the excellant coding of Modula-2.
    This code does Bounded WINDOW bit pulse width tests, and stores valid bits into the RxCODE array, finally setting NewFrame if all BITS are valid, and a Pause is seen.
    The C51/Mod51 pairing is very good at this type of work - other cores suffer.

    
    VAR                                                                          
     RxCODE   : ARRAY[0..2] OF BITSET;  (* 24 Bits, in 'array' *)
     RxCtr    : BYTE;
     NewFrame : BOOLEAN;
    CONST
     FrameBITS  = 24;
     OneAVGE    = 3CH;              (* or Whatever you measure *)
     ZeroAVGE   = 2FH;
    
     OneMIN = OneAVGE - OneAVGE DIV 4;
     OneMAX = OneAVGE + OneAVGE DIV 4;
     ZeroMIN = ZeroAVGE -  ZeroAVGE DIV 4;
     ZeroMAX = ZeroAVGE +  ZeroAVGE DIV 4;
    
    PROCEDURE (*$IS3*) INTERRUPT_03H; (* INT0 ==\__ = P3.2  *)
    
    BEGIN
      IF TF0 THEN  (* Is FIRST / Last pulse == SYNC and FRAME decison Code *)
        TF0 := FALSE;
        IF RxCtr = FrameBITS THEN  (* end of pulses, MUST have had a VALID frame ! *)
          NewFrame := TRUE;
        ELSE  (* start of pulse learning *)
          RxCODE[0] := {};     (* Load with 24 Zeros *)
          RxCODE[1] := {};
          RxCODE[2] := {};
        END;
        RxCtr := 0;
      ELSIF RxCtr < 24 THEN   (* is Bit Picking Code ..... *)
        CASE TL0 OF
        | OneMIN..OneMAX :
           INCL(RxCODE[RxCtr >> 3],RxCtr);   (* SET single Bit, in ONE byte *)
        | ZeroMIN..ZeroMAX :   (* default is a Zero *)
        ELSE                   (* bad Bit Time Width value, so reset *)
          TF0 := TRUE;         (* catch Reset, next pass ? *)
          RxCtr := 0;
        END;
        INC(RxCtr);
      END;
    END INTERRUPT_03H;  (* just 93 bytes ! *)
    
    (* Most of the 'work' is done by the single INCL statement
       INCL(BitSet,BitNum); -> SETs (BitNum MOD 8) in BYTE variable BitSet
       BitSet can be an ARRAY ( as above ), and BitNum can be a CONST, or
       variable. BitNum > 7 is also legal, Mod51 wraps this to 0..7
    *)
    
    
    
    Modula-2 webring logo Modula-2 Webring
    [ List all | Random | << Prev | Next >> | Join | ]