Coder Social home page Coder Social logo

Comments (26)

axtens avatar axtens commented on September 28, 2024 2

@iHiD ah silly me, I forgot about that

from cobol.

github-actions avatar github-actions commented on September 28, 2024

Hi and welcome to Exercism! 👋

Thanks for opening an issue 🙂

  • If you are suggesting a new feature or an improvement to Exercism, please take a read of this post, which will likely result in a faster response.
  • If you are reporting a bug in the website, thank you! We are getting a lot of reports at the moment (which is great), but we triage and reply as soon as we can.
  • If you are requesting support, someone will help shortly.
  • For everything else, we will reply or triage your issue to the right repository soon.

from cobol.

kytrinyx avatar kytrinyx commented on September 28, 2024

@SteveHayward which language are you learning? Are you able to request mentoring through the UI on the site?

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

iHiD avatar iHiD commented on September 28, 2024

@SteveHayward The file you uploaded is empty. It's probably best to just paste the code directly into a comment 🙂

(cc @exercism/cobol to help you)

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024
   IDENTIFICATION DIVISION.
   PROGRAM-ID. YACHT.
   DATA DIVISION.
   WORKING-STORAGE SECTION.
   01 WS-RESULT PIC 99.
   01 WS-CATEGORY PIC X(15).
   88 YACHT-CAT VALUE "YACHT".
   88 STRAIGHT VALUE "STRAIGHT".
   88 CHOICE VALUE "CHOICE".
   88 FOUR-OF-A-KIND VALUE "FOUR-OF-A-KIND".
   88 FULL-HOUSE VALUE "FULL-HOUSE".
   88 SIXES VALUE "SIXES".
   88 FIVES VALUE "FIVES".
   88 FOURS VALUE "FOURS".
   88 THREES VALUE "THREES".
   88 TWOS VALUE "TWOS".
   88 ONES VALUE "ONWS".
   01 WS-DICE.
   88 IS-YACHT VALUE 66666 OR 55555 OR 44444 OR 33333 OR 22222 OR           11111.
     05 DIE OCCURS 5 PIC 9.
   01 I PIC 9.
   01 TEMP PIC 9.
   01 ROLL-BY-DIE.
   05 DIE-COUNT OCCURS 6 PIC 9.
   PROCEDURE DIVISION.
   MAIN-PROCEDURE.
     PERFORM YACHT.
     MOVE 0 TO WS-RESULT. MOVE 00000 TO WS-DICE. 
     MOVE 000000 TO ROLL-BY-DIE. 
   YACHT.
     IF YACHT-CAT
        IF IS-YACHT MOVE 50 TO WS-RESULT GO TO DONE.
     IF STRAIGHT
        IF ROLL-BY-DIE = 111110 OR 011111 
        COMPUTE WS-RESULT = 30 GO TO DONE.
     IF CHOICE
        COMPUTE WS-RESULT =  DIE-COUNT(1) * 1 + DIE-COUNT(2) * 2              + DIE-COUNT(3) * 3 + DIE-COUNT(4) * 4 
        + DIE-COUNT (5) * 5 + DIE-COUNT(6) * 6 
        GO TO DONE.
     IF FOUR-OF-A-KIND
        IF DIE-COUNT(1) > 3 OR DIE-COUNT(2) > 3
        OR DIE-COUNT(3) > 3 OR DIE-COUNT(4) > 3
        OR DIE-COUNT(5) > 3 OR DIE-COUNT(6) > 3
        COMPUTE WS-RESULT = DIE-COUNT(1) * 1 
        + DIE-COUNT(2) * 2 + DIE-COUNT(3) * 3 
        + DIE-COUNT(4) * 4 + DIE-COUNT (5) * 5 
        + DIE-COUNT(6) * 6
        GO TO DONE.
     IF FULL-HOUSE
        IF DIE-COUNT(1) = 3 OR DIE-COUNT(2) = 3
        OR DIE-COUNT(3) = 3 OR DIE-COUNT(4) = 3
        OR DIE-COUNT(5) = 3 OR DIE-COUNT(6) = 3
        IF DIE-COUNT(1) = 2 OR DIE-COUNT(2) = 2
        OR DIE-COUNT(3) = 2 OR DIE-COUNT(4) = 2
        OR DIE-COUNT(5) = 2 OR DIE-COUNT(6) = 2
        COMPUTE WS-RESULT = DIE-COUNT(1) * 1 
        + DIE-COUNT(2) * 2 + DIE-COUNT(3) * 3 
        + DIE-COUNT(4) * 4 + DIE-COUNT (5) * 5 
        + DIE-COUNT(6) * 6
        GO TO DONE.
    IF SIXES
       COMPUTE WS-RESULT = DIE-COUNT(6) * 6
       GO TO DONE.
    IF FIVES
       COMPUTE WS-RESULT = DIE-COUNT(5) * 5
       GO TO DONE.
    IF FOURS
       COMPUTE WS-RESULT = DIE-COUNT(4) * 4
       GO TO DONE.
    IF THREES
       COMPUTE WS-RESULT = DIE-COUNT(3) * 3
       GO TO DONE.
    IF TWOS
       COMPUTE WS-RESULT = DIE-COUNT(2) * 2
       GO TO DONE.
    IF ONES
       COMPUTE WS-RESULT = DIE-COUNT(1) * 1
       GO TO DONE.
   DONE.

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

Closed accidentally - please reopen

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

axtens avatar axtens commented on September 28, 2024

Okay, I give it a look.

from cobol.

axtens avatar axtens commented on September 28, 2024

@SteveHayward please can you request mentoring? I can answer you here, but this isn't the best place for long-running conversations.

Currently your test run output is as follows

Run cobolcheck.
**** FAIL:   1. Yacht                                                                           
    EXPECTED +00000000050.0000000, WAS +00000000000.0000000
     PASS:   2. Not Yacht                                                                       
**** FAIL:   3. Ones                                                                            
    EXPECTED +00000000003.0000000, WAS +00000000000.0000000
**** FAIL:   4. Ones, out of order                                                              
    EXPECTED +00000000003.0000000, WAS +00000000000.0000000
     PASS:   5. No ones                                                                         
**** FAIL:   6. Twos                                                                            
    EXPECTED +00000000002.0000000, WAS +00000000000.0000000
**** FAIL:   7. Fours                                                                           
    EXPECTED +00000000008.0000000, WAS +00000000000.0000000
**** FAIL:   8. Yacht counted as threes                                                         
    EXPECTED +00000000015.0000000, WAS +00000000000.0000000
     PASS:   9. Yacht of 3s counted as fives                                                    
**** FAIL:  10. Fives                                                                           
    EXPECTED +00000000010.0000000, WAS +00000000000.0000000
**** FAIL:  11. Sixes                                                                           
    EXPECTED +00000000006.0000000, WAS +00000000000.0000000
**** FAIL:  12. Full house two small, three big                                                 
    EXPECTED +00000000016.0000000, WAS +00000000000.0000000
**** FAIL:  13. Full house three small, two big                                                 
    EXPECTED +00000000019.0000000, WAS +00000000000.0000000
     PASS:  14. Two pair is not a full house                                                    
     PASS:  15. Four of a kind is not a full house                                              
     PASS:  16. Yacht is not a full house                                                       
**** FAIL:  17. Four of a Kind                                                                  
    EXPECTED +00000000024.0000000, WAS +00000000000.0000000
**** FAIL:  18. Yacht can be scored as Four of a Kind                                           
    EXPECTED +00000000012.0000000, WAS +00000000000.0000000
     PASS:  19. Full house is not Four of a Kind                                                
**** FAIL:  20. Little Straight                                                                 
    EXPECTED +00000000030.0000000, WAS +00000000000.0000000
     PASS:  21. Little Straight as Big Straight                                                 
     PASS:  22. Four in order but not a little straight                                         
     PASS:  23. No pairs but not a little straight                                              
     PASS:  24. Minimum is 1, maximum is 5, but not a little straight                           
**** FAIL:  25. Big Straight                                                                    
    EXPECTED +00000000030.0000000, WAS +00000000000.0000000
     PASS:  26. Big Straight as little straight                                                 
     PASS:  27. No pairs but not a big straight                                                 
**** FAIL:  28. Choice                                                                          
    EXPECTED +00000000023.0000000, WAS +00000000000.0000000
**** FAIL:  29. Yacht as choice                                                                 
    EXPECTED +00000000010.0000000, WAS +00000000000.0000000
 
 29 TEST CASES WERE EXECUTED
 13 PASSED
 16 FAILED
=================================================

There are a few things that you should deal with in the short term before working on the logic per se.

  1. The code inside MAIN-PROCEDURE. gets ignored by the tester. The tester starts at YACHT. so you should do any initialisation immediately after that entry point.

from cobol.

axtens avatar axtens commented on September 28, 2024
  1. If your problem-solving approach is to enumerate every possible arrangement of dice, then your procedure division is going to be very very large.

from cobol.

axtens avatar axtens commented on September 28, 2024
  1. The testing framework puts the type of roll in WS-CATEGORY. It might be worthwhile using EVALUATE WS-CATEGORY to deal with various roll types. See the .CUT file to see what the options are.

from cobol.

iHiD avatar iHiD commented on September 28, 2024

(@axtens He can't request mentoring because you can only request mentoring once your solution passes the tests)

from cobol.

axtens avatar axtens commented on September 28, 2024
  1. INSPECT WS-DICE TALLYING would be one way of working out how many of what dice have been rolled.

from cobol.

axtens avatar axtens commented on September 28, 2024

@SteveHayward see how you go with that. Oh, that reminds me

  1. Consider breaking the logic up into separate paragraphs for each of the roll types, e.g.
         EVALUATE WS-CATEGORY
           WHEN 'ones'
            PERFORM SCORE-ONES-ROLL 
                THRU SCORE-ONES-ROLL-EXIT
           WHEN 'twos'
            PERFORM SCORE-TWOS-ROLL 
                THRU SCORE-TWOS-ROLL-EXIT

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

axtens avatar axtens commented on September 28, 2024

Please take the attached file, remove the .txt extension, and place in your tst/yacht folder replacing the .cut file that exists there.

This demonstrates how to comment out tests. I have left the first test uncommented. As you implement your logic, remove the comments from each testcase until you are able to get through the full set.

yacht.cut.txt

from cobol.

axtens avatar axtens commented on September 28, 2024

One more thing. Can you describe to me the process you intend to follow to establish whether a roll is a big straight or a small straight? Use English words rather than going straight into code. A lot programming is problem-solving: until you can adequately describe the problem, the solution remains largely distant.

from cobol.

axtens avatar axtens commented on September 28, 2024

The reason I ask is that you've got

         IF STRAIGHT
            IF ROLL-BY-DIE = 111110 OR 011111
            COMPUTE WS-RESULT = 30 GO TO DONE.

How are you building ROLL-BY-DIE? Why are you using a six-element array and what is it representing?

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

axtens avatar axtens commented on September 28, 2024

Wow, that's a cool way of approaching it.

When I was doing the task myself, I took a completely different tack, sorting the dice into lowest-to-highest order. Thus there had to be 2 of the first and 3 of the last, or 3 of the first and 2 of the last, for it to be a full-house.

Your way is still going to take a bit of work to enumerate all the full-house possibilities, e.g.
320000, 230000, 302000, 203000, 300200, 200300 ... 032000 ... 000032 etc, so you'll then have to come up with a way of detecting 23 and 32 without having to enumerate all the zeroes in the pattern. (Thinking out loud) maybe inspecting the ROLL-BY-DIE tallying 0 2 and 3 and then accepting everything that has 4 zeroes, one 3 and one 2.

from cobol.

axtens avatar axtens commented on September 28, 2024

How did you get on? I had a go at solving this one using your approach. The overall code size shrank by abouit 80% compared to my sorting approach. I'm happy to share the code with you if you want.

-- Bruce

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

axtens avatar axtens commented on September 28, 2024
       IDENTIFICATION DIVISION.
       PROGRAM-ID. YACHT.
       DATA DIVISION.
       WORKING-STORAGE SECTION.
       01 WS-CATEGORY PIC X(15).
       01 WS-DICE PIC 9(5).
       01 ROLL-COUNTERS PIC 9(6).
       01 ROLL-COUNTER REDEFINES ROLL-COUNTERS.
        03 ROLL-COUNT PIC 9 OCCURS 6 TIMES INDEXED BY ROLL-INDEX.
       01 POINT-COUNT PIC 9.
       01 THREE-ROLLED PIC 9.
       01 TWO-ROLLED PIC 9.
       01 ROLL-LOOP PIC 9.
       01 WS-RESULT PIC 99 VALUE 0.
       PROCEDURE DIVISION.
       YACHT.
         MOVE ZEROES TO WS-RESULT.
         PERFORM COUNT-POINTS.
         EVALUATE WS-CATEGORY
           WHEN 'ones'
            MULTIPLY ROLL-COUNT(1) BY 1 GIVING WS-RESULT
           WHEN 'twos'
            MULTIPLY ROLL-COUNT(2) BY 2 GIVING WS-RESULT
           WHEN 'threes'
            MULTIPLY ROLL-COUNT(3) BY 3 GIVING WS-RESULT
           WHEN 'fours'
            MULTIPLY ROLL-COUNT(4) BY 4 GIVING WS-RESULT
           WHEN 'fives'
            MULTIPLY ROLL-COUNT(5) BY 5 GIVING WS-RESULT
           WHEN 'sixes'
            MULTIPLY ROLL-COUNT(6) BY 6 GIVING WS-RESULT
           WHEN 'little straight'
            IF ROLL-COUNTERS = 111110
             MOVE 30 TO WS-RESULT
            END-IF
           WHEN 'big straight'
            IF ROLL-COUNTERS = 011111
             MOVE 30 TO WS-RESULT
            END-IF
           WHEN 'four of a kind'
             PERFORM VARYING ROLL-LOOP FROM 1 BY 1 UNTIL ROLL-LOOP > 6
              SET ROLL-INDEX TO ROLL-LOOP
              IF ROLL-COUNT(ROLL-INDEX) >= 4 
               MULTIPLY ROLL-LOOP BY 4 GIVING WS-RESULT
              END-IF
             END-PERFORM 
            WHEN 'full house'
             MOVE ZEROES TO THREE-ROLLED
             MOVE ZEROES TO TWO-ROLLED
             PERFORM VARYING ROLL-LOOP FROM 1 BY 1 UNTIL ROLL-LOOP > 6
              SET ROLL-INDEX TO ROLL-LOOP
              IF ROLL-COUNT(ROLL-INDEX) = 3 
               MOVE ROLL-LOOP TO THREE-ROLLED
              END-IF
              IF ROLL-COUNT(ROLL-INDEX) = 2
               MOVE ROLL-LOOP TO TWO-ROLLED
              END-IF
             END-PERFORM 
             IF TWO-ROLLED NOT = ZEROES AND THREE-ROLLED NOT = ZEROES
              COMPUTE WS-RESULT = TWO-ROLLED * 2 + THREE-ROLLED * 3
             END-IF
           WHEN 'choice'
            COMPUTE WS-RESULT = ROLL-COUNT(1) * 1 +
             ROLL-COUNT(2) * 2 +
             ROLL-COUNT(3) * 3 +
             ROLL-COUNT(4) * 4 +
             ROLL-COUNT(5) * 5 +
             ROLL-COUNT(6) * 6 
           WHEN 'yacht'
             IF ROLL-COUNT(1) = 5 OR 
                ROLL-COUNT(2) = 5 OR 
                ROLL-COUNT(3) = 5 OR 
                ROLL-COUNT(4) = 5 OR 
                ROLL-COUNT(5) = 5 OR 
                ROLL-COUNT(6) = 5 
                 MOVE 50 TO WS-RESULT
             END-IF 
         END-EVALUATE.
       YACHT-EXIT.
         EXIT.
       
       COUNT-POINTS.
         PERFORM VARYING ROLL-LOOP FROM 1 BY 1 UNTIL ROLL-LOOP > 6
          MOVE ZEROES TO POINT-COUNT
          SET ROLL-INDEX TO ROLL-LOOP
          INSPECT WS-DICE TALLYING POINT-COUNT FOR ALL ROLL-LOOP
          MOVE POINT-COUNT TO ROLL-COUNT(ROLL-INDEX) 
         END-PERFORM.
       COUNT-POINTS-EXIT.
        EXIT.

from cobol.

SteveHayward avatar SteveHayward commented on September 28, 2024

from cobol.

axtens avatar axtens commented on September 28, 2024

Anytime. Glad to be of assistance.

Bruce

from cobol.

Related Issues (17)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.