Bulls and Cows is an old game played with pencil and paper that was later implemented using computers.
Create a four digit random number from the digits 1 to 9, without duplication.
The program should:
The score is computed as:
This is written to run under CP/M and includes an RNG to generate the secret.
bdosequ5putcharequ2rawioequ6putsequ9cstatequ11readsequ10org100hmvic,putslxid,signon; Print namecallbdos;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Initialize the RNG with keyboard inputmvic,putslxid,entropy; Ask for randomnesscallbdosmvib,9; 9 times,randloop:mvic,3; read 3 keys.lxih,xabcdat + 1randkey:pushb; Read a keypushhrandkeywait:mvic,rawiomvie,0FFhcallbdosanaajzrandkeywaitpophpopbxram; XOR it with the random memorymovm,ainxhdcrcjnzrandkey; Go get more charactersdcrbjnzrandloopmvic,putslxi d,done; Tell the user we're donecallbdos;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Generate 4-digit secret codelxih,secretmvib,4gencode:pushhpushbcallrandcodepopbpophmovm,ainxhdcrbjnzgencode;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; User makes a guessreadguess:mvic,puts; Ask for guesslxid,guesscallbdosmvic,reads; Read guesslxid,bufdefcallbdoscallnewline; Print newlinemvib,4; Check inputlxih,bufvalidate:mova,mcpi'9' + 1; >9?jncinval; = invalidcpi'1'; <1?jcinval; = invalidsui'0'; Make ASCII digit into numbermovm,ainxhdcrbjnzvalidate;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Count bullsmvic,putslxid,bulls; Output "Bulls:"callbdoslxid,secretlxih,buflxib,4; No bulls, counter = 4bullloop:ldaxd; Get secret digitcmpm; Match to buffer digitczcountmatchinxhinxddcrcjnzbulllooppushb; Keep bulls for cow count,pushb; and for final check.callprintcount;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Count cowsmvic,putslxid,cows; Output ", Cows:"callbdospoppsw; Retrieve the bulls (into A reg)cma; Negate amount of bullsinramovb,a; Use it as start of cow countmvid,4; For all 4 secret digits..lxih,secretcowouter:mova,m; Grab secret digit to testpushh; Store secret positionmvie,4; For all 4 input digits...lxih,bufcowinner:cmpm; Compare to current secret digitczcountmatchinxhdcre; While there are more digits in bufjnzcowinner; Test next digitpoph; Restore secret positioninxh; Look at next secret digitdcrd; While there are digits leftjnzcowouterpushb; Keep cow countcallprintcountcallnewline;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Check win conditionpoppsw; Cow count (in A)popb; Bull count (in B)anaa; To win, there must be 0 cows...jnzreadguessmvia,4; And 4 bulls.cmpbjnzreadguessmvic,putslxid,winjmpbdos;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Increment bull/cow countercountmatch:inrbret;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Print a newlinenewline:mvic,putslxid,nljmp bdos;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Output counter as ASCIIprintcount:mvia,'0'addbmvic,putcharmove,ajmpbdos;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; User entered invalid inputinval:mvic,putslxid,invalidcallbdosjmpreadguess;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Generate random number 1-9 that isn't in keyrandcode:callxabcrandani0fh; Low nybbleanaa; 0 = invalidjzrandcodecpi10; >9 = invalidjncrandcode;; Check if it is a duplicatemvib,4 lxih,secretcheckdup:cmpm jzrandcodeinxhdcrbjnzcheckdupret ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; The "X ABC" 8-bit random number generator;; (Google that to find where it came from)xabcrand: lxi h,xabcdat inr m ; X++ mov a,m ; X, inx h ; xra m ; ^ C, inx h ; xra m ; ^ A, mov m,a ; -> A inx h add m ; + B, mov m,a ; -> B rar ; >>1 dcx h xra m ; ^ A, dcx h add m ; + C mov m,a ; -> C ret;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Strings signon:db'Bulls and Cows',13,10,'$'entropy:db'Please mash the keyboard to generate entropy...$'done:db'done.',13,10,13,10,'$'bulls:db'Bulls: $'cows:db', Cows: $'guess:db'Guess: $'invalid: db'Invalid input.',13,10,'$'win:db'You win!',13,10,'$'nl:db13,10,'$';;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; Variablesxabcdat:ds4; RNG statesecret:ds4; Holds the secret codebufdef:db4,0; User input buffer buf:ds4
HOW TO RETURN random.digit: RETURN choice "123456789"HOW TO MAKE SECRET secret: PUT "" IN secret FOR i IN {1..4}: PUT random.digit IN digit WHILE SOME j IN {1..i-1} HAS secret item j = digit: PUT random.digit IN digit PUT secret^digit IN secretHOW TO RETURN guess count.bulls secret: PUT 0 IN bulls FOR i IN {1..4}: IF secret item i = guess item i: PUT bulls+1 IN bulls RETURN bullsHOW TO RETURN guess count.cows secret: PUT -(guess count.bulls secret) IN cows FOR c IN guess: IF c in secret: PUT cows+1 IN cows RETURN cowsHOW TO REPORT has.duplicates guess: FOR i IN {1..3}: FOR j IN {i+1..4}: IF guess item i = guess item j: SUCCEED FAILHOW TO REPORT is.valid guess: IF SOME digit IN guess HAS digit not.in "123456789": WRITE "Invalid digit: ", digit/ FAIL IF #guess <> 4: WRITE "Guess must contain 4 digits."/ FAIL IF has.duplicates guess: WRITE "No duplicates allowed"/ FAIL SUCCEEDHOW TO READ GUESS guess: WHILE 1=1: WRITE "Guess? " READ guess RAW IF is.valid guess: QUITHOW TO PLAY BULLS AND COWS: PUT 0, 0, 0 IN tries, bulls, cows MAKE SECRET secret WRITE "Bulls and cows"/ WRITE "--------------"/ WRITE / WHILE bulls<>4: READ GUESS guess PUT guess count.bulls secret IN bulls PUT guess count.cows secret IN cows WRITE "Bulls:",bulls,"- Cows:",cows/ PUT tries+1 IN tries WRITE "You win! Tries:", triesPLAY BULLS AND COWS
Bulls and cows--------------Guess? 1234Bulls: 0 - Cows: 1Guess? 5678Bulls: 0 - Cows: 2Guess? 1679Bulls: 0 - Cows: 2Guess? 1689Bulls: 0 - Cows: 2Guess? 1659Bulls: 1 - Cows: 2Guess? 2659Bulls: 1 - Cows: 2Guess? 3659Bulls: 1 - Cows: 3Guess? 9356Bulls: 4 - Cows: 0You win! Tries: 8
DEFINE DIGNUM="4"TYPE Score=[BYTE bulls,cows,err]PROC Generate(CHAR ARRAY secret) DEFINE DIGCOUNT="9" CHAR ARRAY digits(DIGCOUNT) BYTE i,j,d,tmp,count FOR i=0 TO DIGCOUNT-1 DO digits(i)=i+'1 OD secret(0)=DIGNUM count=DIGCOUNT FOR i=1 TO DIGNUM DO d=Rand(count) secret(i)=digits(d) count==-1 digits(d)=digits(count) ODRETURNPROC CheckScore(CHAR ARRAY code,guess Score POINTER res) BYTE i,j res.bulls=0 res.cows=0 IF guess(0)#DIGNUM THEN res.err=1 RETURN FI res.err=0 FOR i=1 TO DIGNUM DO IF guess(i)=code(i) THEN res.bulls==+1 ELSE FOR j=1 TO DIGNUM DO IF j#i AND guess(j)=code(i) THEN res.cows==+1 EXIT FI OD FI ODRETURNPROC Main() CHAR ARRAY code(DIGNUM+1),guess(255) Score res Generate(code) PrintE("Bull and cows game.") PutE() Print("I choose a 4-digit number from digits 1 to 9 without repetition. ") PrintE("Your goal is to guess it.") PutE() PrintE("Enter your guess:") DO InputS(guess) CheckScore(code,guess,res) Put(28) ;cursor up PrintF("%S -> ",guess) IF res.err THEN Print("Wrong input") ELSE PrintF("Bulls=%B Cows=%B",res.bulls,res.cows) IF res.bulls=DIGNUM THEN PutE() PutE() PrintE("You win!") EXIT FI FI PrintE(", try again:") ODRETURN
Screenshot from Atari 8-bit computer
Bull and cows game.I choose a 4-digit number from digits 1 to 9 without repetition. Your goal is to guess it.Enter your guess:12345 -> Wrong input, try again:1234 -> Bulls=0 Cows=2, try again:1243 -> Bulls=2 Cows=0, try again:5643 -> Bulls=2 Cows=0, try again:7843 -> Bulls=3 Cows=0, try again:7943 -> Bulls=2 Cows=1, try again:9843 -> Bulls=4 Cows=0You win!
withAda.Text_IO;useAda.Text_IO;withAda.Numerics.Discrete_Random;procedureBulls_And_CowsispackageRandom_Naturalis newAda.Numerics.Discrete_Random(Natural);Number:String(1..4);begindeclare-- Generation of numberuseRandom_Natural;Digit:String:="123456789";Size:Positive:=9;Dice:Generator;Position:Natural;beginReset(Dice);forIinNumber'RangeloopPosition:=Random(Dice)modSize+1;Number(I):=Digit(Position);Digit(Position..Size-1):=Digit(Position+1..Size);Size:=Size-1;endloop;end;loop-- Guessing loopPut("Enter four digits:");declareGuess:String:=Get_Line;Bulls:Natural:=0;Cows:Natural:=0;beginifGuess'Length/=4thenraiseData_Error;endif;forIinGuess'RangeloopforJinNumber'RangeloopifGuess(I)notin'1'..'9'or else(I<Jand thenGuess(I)=Guess(J))thenraiseData_Error;endif;ifNumber(I)=Guess(J)thenifI=JthenBulls:=Bulls+1;elseCows:=Cows+1;endif;endif;endloop;endloop;exitwhenBulls=4;Put_Line(Integer'Image(Bulls)&" bulls,"&Integer'Image(Cows)&" cows");exceptionwhenData_Error=>Put_Line("You should enter four different digits 1..9");end;endloop;endBulls_And_Cows;
STRING digits = "123456789";[4]CHAR chosen;STRING available := digits;FOR i TO UPB chosen DO INT c = ENTIER(random*UPB available)+1; chosen[i] := available[c]; available := available[:c-1]+available[c+1:]OD;COMMENT print((chosen, new line)); # Debug # END COMMENTOP D = (INT d)STRING: whole(d,0); # for formatting an integer #print (("I have chosen a number from ",D UPB chosen," unique digits from 1 to 9 arranged in a random order.", new line,"You need to input a ",D UPB chosen," digit, unique digit number as a guess at what I have chosen", new line));PRIO WITHIN = 5, NOTWITHIN = 5;OP WITHIN = (CHAR c, []CHAR s)BOOL: char in string(c,LOC INT,s);OP NOTWITHIN = (CHAR c, []CHAR s)BOOL: NOT ( c WITHIN s );INT guesses := 0, bulls, cows;WHILE STRING guess; guesses +:= 1; WHILE # get a good guess # print((new line,"Next guess [",D guesses,"]: ")); read((guess, new line)); IF UPB guess NE UPB chosen THEN FALSE ELSE BOOL ok; FOR i TO UPB guess WHILE ok := guess[i] WITHIN digits AND guess[i] NOTWITHIN guess[i+1:] DO SKIP OD; NOT ok FI DO print(("Problem, try again. You need to enter ",D UPB chosen," unique digits from 1 to 9", new line)) OD;# WHILE # guess NE chosenDO bulls := cows := 0; FOR i TO UPB chosen DO IF guess[i] = chosen[i] THEN bulls +:= 1 ELIF guess[i] WITHIN chosen THEN cows +:= 1 FI OD; print((" ",D bulls," Bulls",new line," ",D cows," Cows"))OD;print((new line, "Congratulations you guessed correctly in ",D guesses," attempts.",new line))
Output:
I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order.You need to input a 4 digit, unique digit number as a guess at what I have chosenNext guess [1]:
Call themoo
function with one dummy argument to play a game ofBulls and Cows in the APL session.
input←{⍞←'Guess: '⋄7↓⍞}output←{⎕←(↑'Bulls: ''Cows: '),⍕⍪⍵⋄⍵}isdigits←∧/⎕D∊⍨⊢valid←isdigits∧4=≢guess←⍎¨input⍣(valid⊣)bulls←+/=cows←+/∊∧≠game←(output⊣(bulls,cows)guess)⍣(40≡⊣)random←1+4?9⍨moo←'You win!'⊣(randomgame⊢)
To show off APL, this is written entirely in tacit style (except for the I/O). There is no explicit flow control or recursion,and there are no variables. The code is split into functions only to aid the reader, none is everreferred to twice. The following definition ofmoo
is exactly equivalent to the above:
moo←'You win!'⊣((1+4?9⍨)(({⎕←(↑'Bulls: ''Cows: '),⍕⍪⍵⋄⍵}⊣((+/=),(+/∊∧≠))(⍎¨{⍞←'Guess: '⋄7↓⍞}⍣(((∧/⎕D∊⍨⊢)∧4=≢)⊣)))⍣(40≡⊣))⊢)
GUI implementation; the prompt for a guess includes a list of all past guesses and their scores.
onpickNumber()settheNumberto""repeat4timessettheDigitto(random numberfrom1to9)asstringrepeatwhile(offsetoftheDigitintheNumber)>0settheDigitto(random numberfrom1to9)asstringendrepeatsettheNumbertotheNumber&theDigitendrepeatendpickNumbertobullsoftheGuessgivenkey:theKeysetbullCountto0repeatwiththeIndexfrom1to4iftexttheIndexoftheGuess=texttheIndexoftheKeythensetbullCounttobullCount+1endifendrepeatreturnbullCountendbullstocowsoftheGuessgivenkey:theKey,bulls:bullCountsetcowCountto-bullCountrepeatwiththeIndexfrom1to4if(offsetof(texttheIndexoftheKey)intheGuess)>0thensetcowCounttocowCount+1endifendrepeatreturncowCountendcowstoscoreoftheGuessgivenkey:theKeysetbullCounttobullsoftheGuessgivenkey:theKeysetcowCounttocowsoftheGuessgivenkey:theKey,bulls:bullCountreturn{bulls:bullCount,cows:cowCount}endscoreonrunsettheNumbertopickNumber()setpastGuessesto{}repeatsettheMessageto""repeatwithaGuessinpastGuessesset{theGuess,theResult}toaGuesssettheMessagetotheMessage&theGuess&":"&bullsoftheResult&"B, "&cowsoftheResult&"C"&linefeedendrepeatsettheMessagetotheMessage&linefeed&"Enter guess:"settheGuesstotext returnedof(display dialogtheMessagewithtitle"Bulls and Cows"defaultanswer"")settheScoretoscoreoftheGuessgivenkey:theNumberifbullsoftheScoreis4thendisplay dialog"Correct! Found the secret in "&((lengthofpastGuesses)+1)&" guesses!"exitrepeatelsesetendofpastGuessesto{theGuess,theScore}endifendrepeatendrun
rand:first.n:4uniquemap1..10=>[sample0..9]bulls:0while[bulls<>4][bulls:new0cows:new0got:stripinput"make a guess: "if?or?not?numeric?got4<>sizegot->print"Malformed answer. Try again!"else[loop.with:'isplitgot'digit[if?(to:integer digit)=rand\[i]->inc'bullselse[ifcontains?randto:integerdigit->inc'cows]]print["Bulls:"bulls"Cows:"cows"\n"]]]printcolor#green"** Well done! You made the right guess!!"
length:=4,Code:="" ; settingsWhileStrLen(Code)<length{Random,num,1,9If!InStr(Code,num)Code.=num}Gui,Add,Text,w83vInfo,I'mthinkingofa%length%-digitnumberwithnoduplicatedigits.Gui,Add,Edit,wpvGuess,Enteraguess...Gui,Add,Button,wpDefaultvDefault,SubmitGui,Add,Edit,ymw130r8vHistoryReadOnlyGui,ShowReturnButtonSubmit:IfDefault=RestartReloadGui,Submit,NoHideIf(StrLen(Guess)!=length)GuiControl,,Info,Entera%length%-digitnumber.ElseIfGuessisnotdigitGuiControl,,Info,Entera%length%-digitnumber.Else{GuiControl,,InfoGuiControl,,GuessIf(Guess=Code){GuiControl,,Info,Correct!GuiControl,,Default,RestartDefault=Restart}response:=Response(Guess,Code)Bulls:=SubStr(response,1,InStr(response,",")-1)Cows:=SubStr(response,InStr(response,",")+1)GuiControl,,History,%History.Guess": "Bulls" Bulls "Cows" Cows`n"}ReturnGuiEscape:GuiClose:ExitAppResponse(Guess,Code){Bulls:=0,Cows:=0Loop,%StrLen(Code)If(SubStr(Guess,A_Index,1)=SubStr(Code,A_Index,1))Bulls++ElseIf(InStr(Code,SubStr(Guess,A_Index,1)))Cows++ReturnBulls","Cows}
# Usage: GAWK -f BULLS_AND_COWS.AWKBEGIN{srand()secret=""for(i=1;i<=4;){digit=int(9*rand())+1if(index(secret,digit)==0){secret=secretdigiti++}}print"Welcome to 'Bulls and Cows'!"print"I thought of a 4-digit number."print"Please enter your guess."}iswellformed($0){if(calcscore($0,secret)){exit}}functioniswellformed(number,i,digit){if(number!~/[1-9][1-9][1-9][1-9]/){print"Your guess should contain 4 digits, each from 1 to 9. Try again!"return0}for(i=1;i<=3;i++){digit=substr(number,1,1)number=substr(number,2)if(index(number,digit)!=0){print"Your guess contains a digit twice. Try again!"return0}}return1}functioncalcscore(guess,secret,bulls,cows,i,idx){# Bulls = correct digits at the right position# Cows = correct digits at the wrong positionfor(i=1;i<=4;i++){idx=index(secret,substr(guess,i,1))if(idx==i){bulls++}elseif(idx>0){cows++}}printf("Your score for this guess: Bulls = %d, Cows = %d.",bulls,cows)if(bulls<4){printf(" Try again!\n")}else{printf("\nCongratulations, you win!\n")}returnbulls==4}
Welcome to 'Bulls and Cows'!I thought of a 4-digit number.Please enter your guess.1234Your score for this guess: Bulls = 0, Cows = 1. Try again!5678Your score for this guess: Bulls = 1, Cows = 1. Try again!9651Your score for this guess: Bulls = 1, Cows = 1. Try again!5729Your score for this guess: Bulls = 0, Cows = 3. Try again!2695Your score for this guess: Bulls = 2, Cows = 1. Try again!2697Your score for this guess: Bulls = 2, Cows = 2. Try again!7692Your score for this guess: Bulls = 4, Cows = 0.Congratulations, you win!
DEFINTA-ZDIMsecretASSTRINGDIMguessASSTRINGDIMcASSTRINGDIMbulls,cows,guesses,iRANDOMIZETIMERDOWHILELEN(secret)<4c=CHR$(INT(RND*10)+48)IFINSTR(secret,c)=0THENsecret=secret+cLOOPguesses=0DOINPUT"Guess a 4-digit number with no duplicate digits: ";guessguess=LTRIM$(RTRIM$(guess))IFLEN(guess)=0THENEXITDOIFLEN(guess)<>4ORVAL(guess)=0THENPRINT"** You should enter 4 numeric digits!"GOTOlooperENDIFbulls=0:cows=0:guesses=guesses+1FORi=1TO4c=MID$(secret,i,1)IFMID$(guess,i,1)=cTHENbulls=bulls+1ELSEIFINSTR(guess,c)THENcows=cows+1ENDIFNEXTiPRINTbulls;" bulls, ";cows;" cows"IFguess=secretTHENPRINT"You won after ";guesses;" guesses!"EXITDOENDIFlooper:LOOP
100 D$ = "123456789"110 FOR I = 1 TO 4120 P = INT(RND(1) * LEN(D$)) + 1130 N$ = N$ + MID$(D$, P, 1)140 D$ = MID$(D$, 1, P - 1) + MID$(D$, P + 1, 8)150 NEXT160 PRINT "A RANDOM NUMBER HAS BEEN CREATED.170 PRINT "THE NUMBER HAS FOUR DIGITS FROM 1 TO 9, WITHOUT DUPLICATION."200 FOR Q = 0 TO 1 STEP 0210 INPUT "GUESS THE NUMBER: "; G%220 G$ = STR$(G%)230 M = LEN(G$) <> 4 OR G% = 0240 IF NOT M THEN FOR I = 2 TO 4 : M = MID$(G$, I, 1) = "0" : IF NOT M THEN NEXT I250 IF NOT M THEN FOR I = 1 TO 3 : FOR J = I + 1 TO 4 : M = MID$(G$, I, 1) = MID$(G$, J, 1) : IF NOT M THEN NEXT J, I260 IF M THEN PRINT "THE GUESS IS MALFORMED." : NEXT Q270 B = 0280 C = 0300 FOR I = 1 TO 4310 C$ = MID$(N$, I, 1)320 BULL = MID$(G$, I, 1) = C$330 COW = 0340 IF NOT BULL THEN FOR J = 1 TO 4 : COW = MID$(G$, J, 1) = C$ : IF NOT COW THEN NEXT J350 B = B + BULL360 C = C + COW370 NEXT I380 PRINT B " BULLS, " C " COWS"390 Q = G$ = N$400 NEXT Q
Based on the AppleSoft BASIC version. Modifications as follows:
100D$="123456789"110FORI=1TO4120P=INT(RND(1)*LEN(D$))+1130N$=N$+MID$(D$,P,1)140D$=MID$(D$,1,P-1)+MID$(D$,P+1,8)150NEXT160PRINTCHR$(147);"A RANDOM NUMBER HAS BEEN CREATED."170PRINT"THE NUMBER HAS FOUR DIGITS FROM 1 TO 9, WITHOUT DUPLICATION."200FORQ=0TO1STEP0210INPUT"GUESS THE NUMBER: ";G%219REM CONVERT TO STRING AND TRIM LEADING SPACE220G$=RIGHT$(STR$(G%),4)230M=LEN(G$)<>4ORG%=0240IFNOTMTHENGOSUB600250IFNOTMTHENGOSUB700260IFMTHENPRINT"THE GUESS IS MALFORMED.":NEXTQ270B=0280C=0300FORI=1TO4310C$=MID$(N$,I,1)320BULL=MID$(G$,I,1)=C$330COW=0340IFNOTBULLTHENFORJ=1TO4:COW=MID$(G$,J,1)=C$:IFNOTCOWTHENNEXTJ350B=B+ABS(BULL)360C=C+ABS(COW)370NEXTI380PRINT"BULLS:";B:PRINT"COWS:";C390Q=ABS(G$=N$)400NEXTQ500PRINT"GOOD JOB!":END600FORI=2TO4:M=MID$(G$,I,1)="0"610IFNOTMTHENNEXTI620RETURN700FORI=1TO3710FORJ=I+1TO4720M=MID$(G$,I,1)=MID$(G$,J,1)730IFNOTMTHENNEXTJ,I740RETURN
100 PROGRAM "Bulls.bas"110 RANDOMIZE 120 STRING C$*4130 LET GUESS=0140 DO150 LET C$=STR$(RND(8701)+1199)160 LOOP UNTIL CHECK$(C$)=C$170 CLEAR SCREEN:PRINT "Welcome to 'Bulls and Cows!'"180 DO190 DO200 PRINT :INPUT PROMPT "Guess a 4-digit number with no duplicate digits: ":G$210 IF CHECK$(G$)="" THEN PRINT "You should enter 4-digit number with no duplicate digits."220 LOOP UNTIL CHECK$(G$)=G$ AND G$<>""230 LET GUESS=GUESS+1:LET BULLS,COWS=0240 FOR I=1 TO 4250 IF C$(I)=G$(I) THEN260 LET BULLS=BULLS+1270 ELSE IF POS(C$,G$(I))<>0 THEN280 LET COWS=COWS+1290 END IF300 NEXT310 PRINT BULLS;"bulls,";COWS;"cows"320 LOOP UNTIL C$=G$330 PRINT "You won after";GUESS;"guesses!"340 DEF CHECK$(S$)350 LET CHECK$=""360 IF LEN(STR$(VAL(S$)))=4 AND POS(S$,"0")=0 THEN LET CHECK$=S$370 FOR I=1 TO 4380 IF POS(S$(:I-1),S$(I)) OR POS(S$(I+1:),S$(I)) THEN LET CHECK$=""390 NEXT400 END DEF
10DIMn(10):LETc$=""20FORi=1TO430LETd=INT(RND*9+1)40IFn(d)=1THENGOTO3050LETn(d)=160LETc$=c$+STR$d70NEXTi80LETguesses=090INPUT"Guess a 4-digit number (1 to 9) with no duplicate digits: ";guess100IFguess=0THENSTOP110IFguess>9999ORguess<1000THENPRINT"Only 4 numeric digits, please":GOTO90120LETbulls=0:LETcows=0:LETguesses=guesses+1:LETg$=STR$guess130FORi=1TO4140IFg$(i)=c$(i)THENLETbulls=bulls+1:GOTO160150IFn(VALg$(i))=1THENLETcows=cows+1160NEXTi170PRINTbulls;" bulls, ";cows;" cows"180IFc$=g$THENPRINT"You won after ";guesses;" guesses!":GOTO10190GOTO90
:: Bulls and Cows Task from Rosetta Code:: Batch File Implementation@echo offsetlocal enabledelayedexpansion:: initialization:beginset"list_chars=123456789"set"list_length=9"set"code="set"code_length=4"%== this should be less than 10 ==%set"tries=0"%== number of tries ==%:: generate the code to be guessed by playerset"chars_left=%list_chars%"for/l%%cin(1,1,%code_length%)do(set/a"rnd=!random!%% (%list_length% + 1 -%%c)"for%%?in(!rnd!)doset"pick_char=!chars_left:~%%?,1!"set"code=!code!!pick_char!"for%%?in(!pick_char!)doset"chars_left=!chars_left:%%?=!"):: get the min and max allowable guess for input validationset"min=!list_chars:~0,%code_length%!"set"max="for/l%%cin(1,1,%code_length%)doset"max=!max!!list_chars:~-%%c,1!":: display game:displayclsecho(echo(Bulls and Cows Gameecho(Batch File Implementationecho(echo(Gameplay:echo(echo(I have generated a%code_length%-digit code from digits 1-9 without duplication.echo(Your objective is to guess it. If your guess is equal to my code,echo(then you WIN. If not, I will score your guess:echo(echo(** A score of one BULL is accumulated for each digit in your guessecho(that equals the corresponding digit in my code.echo(echo(** A score of one COW is accumulated for each digit in your guessecho(that also appears in my code, but in the WRONG position.echo(echo(Now, start guessing^^!:: input guess:guessecho(set"guess="%== clear input ==%set/p"guess=Your Guess: ":: validate inputif"!guess!"gtr"%max%"gotoinvalidif"!guess!"lss"%min%"gotoinvalidset/a"last_idx=%code_length% - 1"for/l%%iin(0,1,%last_idx%)do(set/a"next_idx=%%i + 1"for/l%%jin(!next_idx!,1,%last_idx%)do(if"!guess:~%%i,1!"equ"!guess:~%%j,1!"gotoinvalid))gotoscore:: display that input is invalid:invalidecho(Please input a valid guess.gotoguess:: scoring section:scoreset/a"tries+=1"if"%guess%"equ"%code%"gotowinset"cow=0"set"bull=0"for/l%%iin(0,1,%last_idx%)do(for/l%%jin(0,1,%last_idx%)do(if"!guess:~%%i,1!"equ"!code:~%%j,1!"(if"%%i"equ"%%j"(set/a"bull+=1")else(set/a"cow+=1")))):: display score and go back to user inputecho(BULLS =%bull%; COWS =%cow%.gotoguess:: player wins!:winecho(echo(After%tries% tries, YOU CRACKED IT^^! My code is%code%.echo(set/p"opt=Play again? "if/i"!opt!"equ"y"gotobeginexit /b 0
Bulls and Cows GameBatch File ImplementationGameplay:I have generated a 4-digit code from digits 1-9 without duplication.Your objective is to guess it. If your guess is equal to my code,then you WIN. If not, I will score your guess:** A score of one BULL is accumulated for each digit in your guessthat equals the corresponding digit in my code.** A score of one COW is accumulated for each digit in your guessthat also appears in my code, but in the WRONG position.Now, start guessing!Your Guess: 0123Please input a valid guess.Your Guess: 1234BULLS = 0; COWS = 3.Your Guess: 4123BULLS = 2; COWS = 1....Your Guess: 4391BULLS = 2; COWS = 0.Your Guess: 4521BULLS = 3; COWS = 0.Your Guess: 4621BULLS = 3; COWS = 0.Your Guess: 4821After 10 tries, YOU CRACKED IT! My code is 4821.Play again?
secret$=""REPEATc$=CHR$(&30+RND(9))IFINSTR(secret$,c$)=0secret$+=c$UNTILLEN(secret$)=4PRINT"Guess a four-digit number with no digit used twice."'guesses%=0REPEATREPEATINPUT"Enter your guess: "guess$IFLEN(guess$)<>4PRINT"Must be a four-digit number"UNTILLEN(guess$)=4guesses%+=1IFguess$=secret$PRINT"You won after ";guesses%" guesses!":ENDbulls%=0cows%=0FORi%=1TO4c$=MID$(secret$,i%,1)IFMID$(guess$,i%,1)=c$THENbulls%+=1ELSEIFINSTR(guess$,c$)THENcows%+=1ENDIFENDIFNEXTi%PRINT"You got ";bulls%" bull(s) and ";cows%" cow(s)."UNTILFALSE
get "libhdr"static $( randstate = ? $)let randdigit() = valof$( let x = ? $( randstate := random(randstate) x := (randstate >> 7) & 15 $) repeatuntil 0 < x <= 9 resultis x$)let gensecret(s) be for i=0 to 3 s!i := randdigit() repeatuntil valof $( for j=0 to i-1 if s!i = s!j then resultis false resultis true $)let bulls(secret, guess) = valof$( let x = 0 for i=0 to 3 if secret!i = guess!i then x := x + 1 resultis x$)let cows(secret, guess) = valof$( let x = 0 for i=0 to 3 for j=0 to 3 unless i=j if secret!i = guess!j then x := x + 1 resultis x$)let readguess(guess) be$( let g, v = ?, true writes("Enter a guess, or 0 to quit: ") g := readn() if g=0 then finish for i=3 to 0 by -1 $( guess!i := g rem 10 g := g / 10 $) for i=0 to 2 for j = i+1 to 3 v := v & guess!i ~= 0 & guess!j ~= 0 & guess!i ~= guess!j if v then return writes("Invalid guess.*N")$) repeatlet play(secret) be$( let tries, b, c = 0, ?, ? let guess = vec 3 $( readguess(guess) b := bulls(secret, guess) c := cows(secret, guess) writef("Bulls: %N, cows: %N*N", b, c); tries := tries + 1 $) repeatuntil b = 4 writef("You win in %N tries.*N", tries)$)let start() be$( let secret = vec 3 writes("Bulls and cows*N----- --- ----*N") writes("Please enter a random seed: ") randstate := readn() wrch('*N') gensecret(secret) play(secret)$)
Bulls and cows----- --- ----Please enter a random seed: 20394Enter a guess, or 0 to quit: 1234Bulls: 0, cows: 3Enter a guess, or 0 to quit: 4321Bulls: 1, cows: 2Enter a guess, or 0 to quit: 1423Bulls: 2, cows: 1Enter a guess, or 0 to quit: 1243Bulls: 1, cows: 2Enter a guess, or 0 to quit: 4123Bulls: 3, cows: 0Enter a guess, or 0 to quit: 4523Bulls: 2, cows: 0Enter a guess, or 0 to quit: 5123Bulls: 3, cows: 0Enter a guess, or 0 to quit: 6123Bulls: 3, cows: 0Enter a guess, or 0 to quit: 7123Bulls: 4, cows: 0You win in 9 tries.
secret_length = 4secret = [1 2 3 4 5 6 7 8 9].shuffle.pop secret_lengthscore = { guess | cows = 0 bulls = 0 guess.each_with_index { digit, index | true? digit == secret[index] { bulls = bulls + 1 } { true? secret.include?(digit) { cows = cows + 1 } } } [cows: cows, bulls: bulls]}won = falseguesses = 1p "I have chosen a number with four unique digits from 1 through 9. Can you guess it?"while { not won } { print "Guess #{guesses}: " guess = g.strip.dice.map { d | d.to_i } when { guess == secret } { p "You won in #{guesses} guesses!"; won = true } { guess.include?(0) || guess.include?(null) } { p "Your guess should only include digits 1 through 9." } { guess.length != secret.length } { p "Your guess was not the correct length. The number has exactly #{secret.length} digits." } { guess.unique.length != secret.length } { p "Each digit should only appear once in your guess." } { true } { result = score guess p "Score: #{result[:bulls]} bulls, #{result[:cows]} cows." guesses = guesses + 1 } }
#include<stdio.h>#include<stdarg.h>#include<stdlib.h>#include<stdbool.h>#include<curses.h>#include<string.h>#define MAX_NUM_TRIES 72#define LINE_BEGIN 7#define LAST_LINE 18intyp=LINE_BEGIN,xp=0;charnumber[5];charguess[5];#define MAX_STR 256voidmvaddstrf(inty,intx,constchar*fmt,...){va_listargs;charbuf[MAX_STR];va_start(args,fmt);vsprintf(buf,fmt,args);move(y,x);clrtoeol();addstr(buf);va_end(args);}voidask_for_a_number(){inti=0;charsymbols[]="123456789";move(5,0);clrtoeol();addstr("Enter four digits: ");while(i<4){intc=getch();if((c>='1')&&(c<='9')&&(symbols[c-'1']!=0)){addch(c);symbols[c-'1']=0;guess[i++]=c;}}}voidchoose_the_number(){inti=0,j;charsymbols[]="123456789";while(i<4){j=rand()%9;if(symbols[j]!=0){number[i++]=symbols[j];symbols[j]=0;}}}
The following function contains the code to check how many bulls and cows there are.
booltake_it_or_not(){inti;intcows=0,bulls=0;for(i=0;i<4;i++){if(number[i]==guess[i]){bulls++;}elseif(strchr(number,guess[i])!=NULL){cows++;}}move(yp,xp);addstr(guess);addch(' ');if(bulls==4){yp++;returntrue;}if((cows==0)&&(bulls==0))addch('-');while(cows-->0)addstr("O");while(bulls-->0)addstr("X");yp++;if(yp>LAST_LINE){yp=LINE_BEGIN;xp+=10;}returnfalse;}boolask_play_again(){inti;while(yp-->=LINE_BEGIN){move(yp,0);clrtoeol();}yp=LINE_BEGIN;xp=0;move(21,0);clrtoeol();addstr("Do you want to play again? [y/n]");while(true){inta=getch();switch(a){case'y':case'Y':returntrue;case'n':case'N':returnfalse;}}}intmain(){boolbingo,again;inttries=0;initscr();cbreak();noecho();clear();number[4]=guess[4]=0;mvaddstr(0,0,"I choose a number made of 4 digits (from 1 to 9) without repetitions\n""You enter a number of 4 digits, and I say you how many of them are\n""in my secret number but in wrong position (cows or O), and how many\n""are in the right position (bulls or X)");do{move(20,0);clrtoeol();move(21,0);clrtoeol();srand(time(NULL));choose_the_number();do{ask_for_a_number();bingo=take_it_or_not();tries++;}while(!bingo&&(tries<MAX_NUM_TRIES));if(bingo)mvaddstrf(20,0,"You guessed %s correctly in %d attempts!",number,tries);elsemvaddstrf(20,0,"Sorry, you had only %d tries...; the number was %s",MAX_NUM_TRIES,number);again=ask_play_again();tries=0;}while(again);nocbreak();echo();endwin();returnEXIT_SUCCESS;}
usingSystem;namespaceBullsnCows{classProgram{staticvoidMain(string[]args){int[]nums=newint[]{1,2,3,4,5,6,7,8,9};KnuthShuffle<int>(refnums);int[]chosenNum=newint[4];Array.Copy(nums,chosenNum,4);Console.WriteLine("Your Guess ?");while(!game(Console.ReadLine(),chosenNum)){Console.WriteLine("Your next Guess ?");}Console.ReadKey();}publicstaticvoidKnuthShuffle<T>(refT[]array){System.Randomrandom=newSystem.Random();for(inti=0;i<array.Length;i++){intj=random.Next(array.Length);Ttemp=array[i];array[i]=array[j];array[j]=temp;}}publicstaticboolgame(stringguess,int[]num){char[]guessed=guess.ToCharArray();intbullsCount=0,cowsCount=0;if(guessed.Length!=4){Console.WriteLine("Not a valid guess.");returnfalse;}for(inti=0;i<4;i++){intcurguess=(int)char.GetNumericValue(guessed[i]);if(curguess<1||curguess>9){Console.WriteLine("Digit must be ge greater 0 and lower 10.");returnfalse;}if(curguess==num[i]){bullsCount++;}else{for(intj=0;j<4;j++){if(curguess==num[j])cowsCount++;}}}if(bullsCount==4){Console.WriteLine("Congratulations! You have won!");returntrue;}else{Console.WriteLine("Your Score is {0} bulls and {1} cows",bullsCount,cowsCount);returnfalse;}}}}
#include<iostream>#include<string>#include<algorithm>#include<cstdlib>boolcontains_duplicates(std::strings){std::sort(s.begin(),s.end());returnstd::adjacent_find(s.begin(),s.end())!=s.end();}voidgame(){typedefstd::string::size_typeindex;std::stringsymbols="0123456789";unsignedintconstselection_length=4;std::random_shuffle(symbols.begin(),symbols.end());std::stringselection=symbols.substr(0,selection_length);std::stringguess;while(std::cout<<"Your guess? ",std::getline(std::cin,guess)){if(guess.length()!=selection_length||guess.find_first_not_of(symbols)!=std::string::npos||contains_duplicates(guess)){std::cout<<guess<<" is not a valid guess!";continue;}unsignedintbulls=0;unsignedintcows=0;for(indexi=0;i!=selection_length;++i){indexpos=selection.find(guess[i]);if(pos==i)++bulls;elseif(pos!=std::string::npos)++cows;}std::cout<<bulls<<" bulls, "<<cows<<" cows.\n";if(bulls==selection_length){std::cout<<"Congratulations! You have won!\n";return;}}std::cerr<<"Oops! Something went wrong with input, or you've entered end-of-file!\nExiting ...\n";std::exit(EXIT_FAILURE);}intmain(){std::cout<<"Welcome to bulls and cows!\nDo you want to play? ";std::stringanswer;while(true){while(true){if(!std::getline(std::cin,answer)){std::cout<<"I can't get an answer. Exiting.\n";returnEXIT_FAILURE;}if(answer=="yes"||answer=="Yes"||answer=="y"||answer=="Y")break;if(answer=="no"||answer=="No"||answer=="n"||answer=="N"){std::cout<<"Ok. Goodbye.\n";returnEXIT_SUCCESS;}std::cout<<"Please answer yes or no: ";}game();std::cout<<"Another game? ";}}
importceylon.random{DefaultRandom}sharedvoidrun(){valuerandom=DefaultRandom();functiongenerateDigits()=>random.elements(1..9).distinct.take(4).sequence();functionvalidate(Stringguess){variablevalueok=true;if(!guess.every((Characterelement)=>element.digit)){print("numbers only, please");ok=false;}if('0'inguess){print("only 1 to 9, please");ok=false;}if(guess.distinct.shorterThan(guess.size)){print("no duplicates, please");ok=false;}if(guess.size!=4){print("4 digits please");ok=false;}returnok;}functionscore({Integer*}target,{Integer*}guess){variablevaluebulls=0;variablevaluecows=0;for([a,b]inzipPairs(target,guess)){if(a==b){bulls++;}elseif(target.contains(b)){cows++;}}return[bulls,cows];}while(true){valuedigits=generateDigits();print("I have chosen my four digits, please guess what they are. Use only the digits 1 to 9 with no duplicates and enter them with no spaces. eg 1234 Enter q or Q to quit.");while(true){if(existsline=process.readLine()){if(line.uppercased=="Q"){return;}if(validate(line)){valueguessDigits=line.map((Characterelement)=>Integer.parse(element.string)).narrow<Integer>();value[bulls,cows]=score(digits,guessDigits);if(bulls==4){print("You win!");break;}else{print("Bulls: ``bulls``, Cows: ``cows``");}}}}}}
(nsbulls-and-cows)(defnbulls[guesssolution](count(filter true?(map =guesssolution))))(defncows[guesssolution](-(count(filter(setsolution)guess))(bullsguesssolution)))(defnvalid-input?"checks whether the string is a 4 digit number with unique digits"[user-input](if(re-seq#"^(?!.*(\d).*\1)\d{4}$"user-input)truefalse))(defnenter-guess[]"Let the user enter a guess. Verify the input. Repeat until valid.returns a list of digits enters by the user (# # # #)"(println"Enter your guess: ")(let[guess(read-line)](if(valid-input?guess)(map#(Character/digit%10)guess)(recur))))(defnbulls-and-cows[]"generate a random 4 digit number from the list of (1 ... 9): no repeating digitsplayer tries to guess the number with bull and cows rules gameplay"(let[solution(take4(shuffle(range110)))](println"lets play some bulls and cows!")(loop[guess(enter-guess)](println(bullsguesssolution)" bulls and "(cowsguesssolution)" cows.")(if(not=guesssolution)(recur(enter-guess))(println"You have won!")))))(bulls-and-cows)
% This program needs to be merged with PCLU's "misc" library% to use the random number generator.%% pclu -merge $CLUHOME/lib/misc.lib -compile bulls_cows.clu% Seed the random number generator with the current timeinit_rng = proc () d: date := now() seed: int := ((d.hour*60) + d.minute)*60 + d.second random$seed(seed)end init_rng% Generate a secretmake_secret = proc () returns (sequence[int]) secret: array[int] := array[int]$[0,0,0,0] for i: int in int$from_to(1,4) do digit: int valid: bool := false while ~valid do digit := 1+random$next(9) valid := true for j: int in int$from_to(1, i-1) do if secret[i] = digit then valid := false break end end end secret[i] := digit end return(sequence[int]$a2s(secret))end make_secret% Count the bullsbulls = proc (secret, input: sequence[int]) returns (int) n_bulls: int := 0 for i: int in int$from_to(1,4) do if secret[i] = input[i] then n_bulls := n_bulls + 1 end end return(n_bulls)end bulls% Count the cowscows = proc (secret, input: sequence[int]) returns (int) n_cows: int := 0 for i: int in int$from_to(1,4) do for j: int in int$from_to(1,4) do if i ~= j cand secret[i] = input[j] then n_cows := n_cows + 1 end end end return(n_cows)end cows% Read a guessplayer_guess = proc () returns (sequence[int]) pi: stream := stream$primary_input() po: stream := stream$primary_output() while true do % we will keep reading until the guess is valid stream$puts(po, "Guess? ") guess: string := stream$getl(pi) % check length if string$size(guess) ~= 4 then stream$putl(po, "Invalid guess: need four digits.") continue end % get and check digits valid: bool := true digits: sequence[int] := sequence[int]$[] for c: char in string$chars(guess) do i: int := char$c2i(c) - 48 if ~(i>=1 & i<=9) then valid := false break end digits := sequence[int]$addh(digits,i) end if ~valid then stream$putl(po, "Invalid guess: each position needs to be a digit 1-9.") continue end % check that there are no duplicates valid := true for i: int in int$from_to(1,4) do for j: int in int$from_to(i+1,4) do if digits[i] = digits[j] then valid := false break end end end if ~valid then stream$putl(po, "Invalid guess: there must be no duplicate digits.") continue end return(digits) endend player_guess% Play a gameplay_game = proc (secret: sequence[int]) po: stream := stream$primary_output() n_guesses: int := 0 while true do n_guesses := n_guesses + 1 guess: sequence[int] := player_guess() n_bulls: int := bulls(secret, guess) n_cows: int := cows(secret, guess) stream$putl(po, "Bulls: " || int$unparse(n_bulls) || ", cows: " || int$unparse(n_cows)) if n_bulls = 4 then stream$putl(po, "Congratulations! You won in " || int$unparse(n_guesses) || " tries.") break end endend play_gamestart_up = proc () po: stream := stream$primary_output() init_rng() stream$putl(po, "Bulls and cows\n----- --- ----\n") play_game(make_secret())end start_up
Bulls and cows----- --- ----Guess? 1234Bulls: 0, cows: 1Guess? 5678Bulls: 0, cows: 2Guess? 4579Bulls: 1, cows: 2Guess? 3579Bulls: 2, cows: 2Guess? 3759Bulls: 4, cows: 0Congratulations! You won in 5 tries.
To handle I/O, we use functions namedsay
(which simply outputs a string) andprompt
(which takes a prompt string to display to the user and returns a line of input, without a trailing newline). These require platform-specific implementations. Here's how they can be implemented for the SpiderMonkey shell:
say = printprompt = (str) -> putstr str readline! ? quit!
We can now solve the task usingsay
andprompt
:
const SIZE = 4secret = _.sample ['1' to '9'], SIZEfor ever var guess for ever guess := _.uniq prompt 'Enter a guess: ' if guess.length === SIZE and not _.difference guess, ['1' to '9'] .length break say 'Malformed guess; try again.' bulls = cows = 0 for i til SIZE if guess[i] === secret[i] ++bulls else if _.contains secret, guess[i] ++cows if bulls === SIZE break say "#bulls bull#{[if bulls !== 1 then 's']}, #cows cow#{[if cows !== 1 then 's']}."say 'A winner is you!'
(defunget-number()(do((digits'()))((>=(lengthdigits)4)digits)(pushnew(1+(random9))digits)))(defuncompute-score(guessnumber)(let((cows0)(bulls0))(mapnil(lambda(guess-digitnumber-digit)(cond((=guess-digitnumber-digit)(incfbulls))((memberguess-digitnumber)(incfcows))))guessnumber)(valuescowsbulls)))(defunnumber->guess(number)(when(integerpnumber)(do((digits'()))((zeropnumber)digits)(multiple-value-bind(quotientremainder)(floornumber10)(pushremainderdigits)(setfnumberquotient)))))(defunvalid-guess-p(guess)(and(=4(lengthguess))(every(lambda(digit)(<=1digit9))guess)(equalguess(remove-duplicatesguess))))(defunplay-game(&optional(stream*query-io*))(do((number(get-number))(cows0)(bulls0))((=4bulls))(formatstream"~&Guess a 4-digit number: ")(let((guess(number->guess(readstream))))(cond((not(valid-guess-pguess))(formatstream"~&Malformed guess."))(t(setf(valuescowsbulls)(compute-scoreguessnumber))(if(=4bulls)(formatstream"~&Correct, you win!")(formatstream"~&Score: ~a cows, ~a bulls."cowsbulls)))))))
size=4secret=('1'..'9').to_a.sample(size)guess=[]ofChari=0loopdoi+=1loopdoprint"Guess#{i}: "guess=gets.not_nil!.chomp.charsexitifguess.empty?breakifguess.size==size&&guess.all?{|x|('1'..'9').includes?x}&&guess.uniq.size==sizeputs"Problem, try again. You need to enter#{size} unique digits from 1 to 9"endifguess==secretputs"Congratulations you guessed correctly in#{i} attempts"breakendbulls=cows=0size.timesdo|j|ifguess[j]==secret[j]bulls+=1elsifsecret.includes?guess[j]cows+=1endendputs"Bulls:#{bulls}; Cows:#{cows}"end
voidmain(){importstd.stdio,std.random,std.string,std.algorithm,std.range,std.ascii;immutablehidden="123456789"d.randomCover.take(4).array;while(true){"Next guess: ".write;constd=readln.strip.array.sort().release;if(d.count==4&&d.all!isDigit&&d.uniq.count==4){immutablebulls=d.zip(hidden).count!q{a[0]==a[1]},cows=d.count!(g=>hidden.canFind(g))-bulls;if(bulls==4)return" You guessed it!".writeln;writefln("bulls %d, cows %d",bulls,cows);}" Bad guess! (4 unique digits, 1-9)".writeln;}}
Next guess: 6548bulls 0, cows 3 Bad guess! (4 unique digits, 1-9)Next guess: 5284bulls 2, cows 1 Bad guess! (4 unique digits, 1-9)Next guess: 4386bulls 0, cows 2 Bad guess! (4 unique digits, 1-9)Next guess: - Bad guess! (4 unique digits, 1-9)Next guess: 5894bulls 3, cows 0 Bad guess! (4 unique digits, 1-9)Next guess: 5874bulls 3, cows 0 Bad guess! (4 unique digits, 1-9)Next guess: 5814 You guessed it!
See#Pascal.
union { ulong state; struct { byte x; byte a; byte b; byte c; } fields;} rng;proc rand() byte: rng.fields.x := rng.fields.x + 1; rng.fields.a := rng.fields.a >< rng.fields.c >< rng.fields.x; rng.fields.b := rng.fields.b + rng.fields.a; rng.fields.c := rng.fields.c + (rng.fields.b >> 1) >< rng.fields.a; rng.fields.ccorpproc rand_digit() byte: byte digit; while digit := rand() & 15; digit < 1 or digit >= 10 do od; digitcorpproc make_secret([4]byte secret) void: int i, j; bool ok; for i from 0 upto 3 do while secret[i] := rand_digit(); ok := true; for j from 0 upto i-1 do ok := ok and secret[i] /= secret[j] od; not ok do od odcorpproc bulls([4]byte secret, guess) byte: byte i, count; count := 0; for i from 0 upto 3 do if secret[i] = guess[i] then count := count + 1 fi od; countcorpproc cows([4]byte secret, guess) byte: byte i, j, count; count := 0; for i from 0 upto 3 do for j from 0 upto 3 do if i /= j and secret[i] = guess[j] then count := count + 1 fi od od; countcorpproc read_guess([4]byte guess) void: word guessNo; byte i; while write("Guess? "); readln(guessNo); if guessNo<1111 or guessNo>9999 then true else for i from 3 downto 0 do guess[i] := guessNo % 10; guessNo := guessNo / 10; od; guess[0]*guess[1]*guess[2]*guess[3] = 0 fi do writeln("A guess must be a four-digit number not containing zeroes.") odcorpproc play_game([4]byte secret) word: [4]byte guess; word tries; tries := 1; while read_guess(guess); writeln("Bulls: ", bulls(secret, guess), ", cows: ", cows(secret, guess)); bulls(secret, guess) /= 4 do tries := tries + 1 od; triescorpproc main() void: [4]byte secret; word tries; write("Please enter a random seed: "); readln(rng.state); make_secret(secret); tries := play_game(secret); writeln(); writeln("You got it in ", tries, " tries.")corp
Please enter a random seed: 123456Guess? 1234Bulls: 2, cows: 1Guess? 5678Bulls: 0, cows: 0Guess? 9234Bulls: 1, cows: 2Guess? 1934Bulls: 3, cows: 0Guess? 1294Bulls: 2, cows: 2Guess? 1924Bulls: 4, cows: 0You got it in 6 tries.
Note: This example was deliberately written in an abstracted style, separating out the algorithms, game logic, and UI.
def Digit := 1..9def Number := Tuple[Digit,Digit,Digit,Digit]/** Choose a random number to be guessed. */def pick4(entropy) { def digits := [1,2,3,4,5,6,7,8,9].diverge() # Partial Fisher-Yates shuffle for i in 0..!4 { def other := entropy.nextInt(digits.size() - i) + i def t := digits[other] digits[other] := digits[i] digits[i] := t } return digits(0, 4)}/** Compute the score of a guess. */def scoreGuess(actual :Number, guess :Number) { var bulls := 0 var cows := 0 for i => digit in guess { if (digit == actual[i]) { bulls += 1 } else if (actual.indexOf1(digit) != -1) { cows += 1 } } return [bulls, cows]}/** Parse a guess string into a list of digits (Number). */def parseGuess(guessString, fail) :Number { if (guessString.size() != 4) { return fail(`I need four digits, not ${guessString.size()} digits.`) } else { var digits := [] for c in guessString { if (('1'..'9')(c)) { digits with= c - '0' } else { return fail(`I need a digit from 1 to 9, not "$c".`) } } return digits } }/** The game loop: asking for guesses and reporting scores and win conditions. The return value is null or a broken reference if there was a problem. */def bullsAndCows(askUserForGuess, tellUser, entropy) { def actual := pick4(entropy) def gameTurn() { return when (def guessString := askUserForGuess <- ()) -> { escape tellAndContinue { def guess := parseGuess(guessString, tellAndContinue) def [bulls, cows] := scoreGuess(actual, guess) if (bulls == 4) { tellUser <- (`You got it! The number is $actual!`) null } else { tellAndContinue(`Your score for $guessString is $bulls bulls and $cows cows.`) } } catch message { # The parser or scorer has something to say, and the game continues afterward when (tellUser <- (message)) -> { gameTurn() } } } catch p { # Unexpected problem of some sort tellUser <- ("Sorry, game crashed.") throw(p) } } return gameTurn()}
def replBullsAndCows() { when ( bullsAndCows(fn { def [guess, env] := e`def guess; guess`.evalToPair(interp.getTopScope().nestOuter()) interp.setTopScope(env) println("Please type “ bind guess := \"your guess here\" ”.") guess }, println, entropy) ) -> {} catch p { println(`$p${p.eStack()}`) }}
(Java Swing)
def guiBullsAndCows() { var lastGuess := "" def op := <unsafe:javax.swing.makeJOptionPane> return bullsAndCows(fn { lastGuess := op.showInputDialog(null, "Enter your guess:", lastGuess) if (lastGuess == null) { # canceled, so just fail to return an answer and let the game logic get GCed Ref.promise()[0] } else { lastGuess } }, fn msg { op.showMessageDialog(null, msg) }, entropy)}
dig[] = [ 1 2 3 4 5 6 7 8 9 ]for i = 1 to 4 h = i - 1 + random (10 - i) swap dig[i] dig[h].# print dig[]len g[] 4attempts = 0repeat repeat ok = 0 s$[] = strchars input if len s$[] = 4 ok = 1 for i = 1 to 4 g[i] = number s$[i] if g[i] = 0 ok = 0 . . . until ok = 1 . print g[] attempts += 1 bulls = 0 cows = 0 for i = 1 to 4 if g[i] = dig[i] bulls += 1 else for j = 1 to 4 if dig[j] = g[i] cows += 1 . . . . print "bulls:" & bulls & " cows:" & cows until bulls = 4.print "Well done! " & attempts & " attempts needed."
classBULLS_AND_COWScreateexecutefeatureexecute-- Initiate game.doio.put_string("Let's play bulls and cows.%N")createanswer.make_emptyplayendfeature{NONE}play-- Plays bulls ans cows.localcount,seed:INTEGERguess:STRINGdofromuntilseed>0loopio.put_string("Enter a positive integer.%NYour play will be generated from it.%N")io.read_integerseed:=io.last_integerendgenerate_answer(seed)io.put_string("Your game has been created.%N Try to guess the four digit number.%N")createguess.make_emptyfromuntilguess~answerloopio.put_string("Guess: ")io.read_lineguess:=io.last_stringifguess.count=4andguess.is_naturalandnotguess.has('0')thenio.put_string(score(guess)+"%N")count:=count+1elseio.put_string("Your input does not have the correct format.")endendio.put_string("Congratulations! You won with "+count.out+" guesses.")endanswer:STRINGgenerate_answer(s:INTEGER)-- Answer with 4-digits between 1 and 9 stored in 'answer'.requirepositive_seed:s>0localrandom:RANDOMran:INTEGERdocreaterandom.set_seed(s)fromuntilanswer.count=4loopran:=(random.double_item*10).floorifran>0andnotanswer.has_substring(ran.out)thenanswer.append(ran.out)endrandom.forthendensureanswer_not_void:answer/=Voidcorrect_length:answer.count=4endscore(g:STRING):STRING-- Score for the guess 'g' depending on 'answer'.requiresame_length:answer.count=g.countlocalk:INTEGERa,ge:STRINGdoResult:=""a:=answer.twinge:=g.twinacross1|..|a.countascloopifa[c.item]~ge[c.item]thenResult:=Result+"BULL "a[c.item]:=' 'ge[c.item]:=' 'endendacross1|..|a.countascloopifa[c.item]/=' 'thenk:=ge.index_of(a[c.item],1)ifk>0thenResult:=Result+"COW "ge[k]:=' 'endendendendend
Let's play bulls and cows.Enter a positive integer.Your play will be generated from it.2Guess: 2497BULL COWGuess: 2486BULL COW COWGuess: 2485BULL COW COWGuess: 2483BULL BULL COW COWGuess: 2438BULL COW COW COWGuess: 2843BULL BULL BULL BULLCongratulations! You won with 6 guesses.
ELENA 6.x :
import system'routines;import extensions;class GameMaster{ field _numbers; field _attempt; constructor() { // generate secret number var randomNumbers := new int[]{1,2,3,4,5,6,7,8,9}.randomize(9); _numbers := randomNumbers.Subarray(0, 4); _attempt := new Integer(1); } ask() { var row := console.print("Your Guess #",_attempt," ?").readLine(); ^ row.toArray() } proceed(guess) { int cows := 0; int bulls := 0; if (guess.Length != 4) { bulls := -1 } else { try { for (int i := 0; i < 4; i+=1) { var ch := guess[i]; var number := ch.toString().toInt(); // check range ifnot (number > 0 && number < 10) { InvalidArgumentException.raise() }; // check duplicates var duplicate := guess.seekEach::(x => (x == ch)&&(x.equalReference(ch).Inverted)); if (nil != duplicate) { InvalidArgumentException.raise() }; if (number == _numbers[i]) { bulls += 1 } else { if (_numbers.ifExists(number)) { cows += 1 } } } } catch(Exception e) { bulls := -1 } }; bulls => -1 { console.printLine("Not a valid guess."); ^ true } 4 { console.printLine("Congratulations! You have won!"); ^ false } ! { _attempt.append(1); console.printLine("Your Score is ",bulls," bulls and ",cows," cows"); ^ true } }}public program(){ var gameMaster := new GameMaster(); var process := $lazy gameMaster.proceed(gameMaster.ask()); process.doWhile(); console.readChar()}
Your Guess #1 ?2497Your Score is 1 bulls and 1 cowsYour Guess #2 ?2486Your Score is 1 bulls and 2 cowsYour Guess #3 ?2485Your Score is 1 bulls and 2 cowsYour Guess #4 ?2483Your Score is 2 bulls and 2 cowsYour Guess #5 ?2438Your Score is 1 bulls and 3 cowsYour Guess #6 ?2843Congratulations! You have won!
defmoduleBulls_and_cowsdodefplay(size\\4)dosecret=Enum.take_random(1..9,size)|>Enum.map(&to_string/1)play(size,secret)enddefpplay(size,secret)doguess=input(size)ifguess==secretdoIO.puts"You win!"else{bulls,cows}=count(guess,secret)IO.puts" Bulls:#{bulls}; Cows:#{cows}"play(size,secret)endenddefpinput(size)doguess=IO.gets("Enter your#{size}-digit guess: ")|>String.stripconddoguess==""->IO.puts"Give up"exit(:normal)String.length(guess)==sizeandString.match?(guess,~r/^[1-9]+$/)->String.codepoints(guess)true->input(size)endenddefpcount(guess,secret)doEnum.zip(guess,secret)|>Enum.reduce({0,0},fn{g,s},{bulls,cows}->conddog==s->{bulls+1,cows}ginsecret->{bulls,cows+1}true->{bulls,cows}endend)endendBulls_and_cows.play
Enter your 4-digit guess: 1234 Bulls: 1; Cows: 1Enter your 4-digit guess: 5678 Bulls: 0; Cows: 2Enter your 4-digit guess: 2345 Bulls: 0; Cows: 1Enter your 4-digit guess: 1456 Bulls: 1; Cows: 0Enter your 4-digit guess: 1782You win!
(defunget-list-4-random-digits()"Generate a list of 4 random non-repeating digits."(let((list-of-digits'(0123456789))(one-digit)(four-digits))(dotimes(n4)(setqone-digit(seq-random-eltlist-of-digits))(pushone-digitfour-digits)(setqlist-of-digits(delqone-digit(copy-sequencelist-of-digits))))four-digits))(defunlist-digits(guess-string)"List individual digits of GUESS-STRING."(let((list-of-digits)(one-digit)(total-digits(lengthguess-string)))(dotimes(ntotal-digits)(setqone-digit(string-to-number(substringguess-stringn(1+n))))(pushone-digitlist-of-digits))(reverselist-of-digits)))(defunnumber-list-to-string(numbers)(mapconcat#'number-to-stringnumbers))(defunfour-non-repeating-digits-p(guess-string)"Test if GUESS-STRING has 4 one-digit numbers that do not repeat.";; if GUESS-STRING contains non-numeric characters, then;; the non-numeric characters will be converted to 0s(let((number-list(list-digitsguess-string)))(and;; GUESS-STRING must consist of exactly 4 digits(string-match-p"^[[:digit:]]\\{4\\}$"guess-string);; the length of the list must still be 4 after;; removing duplicate characters, and(=(length(seq-uniqnumber-list))4))))(defuncount-bulls(guessanswer)"Count number of bulls in GUESS as compared to ANSWER.In this game, a bull is an exact match. Both GUESS andANSWER are lists of numbers."(let((bulls0)(position-in-list-1))(dolist(guess-numberguess)(setqposition-in-list(1+position-in-list))(when(=guess-number(nthposition-in-listanswer))(setqbulls(1+bulls))))bulls))(defunis-cow-p(number-listpositionanswer)"Test if NUMBER-LIST is in ANSWER but not in same POSITION."(and;; NUMBER-LIST is found in ANSWER(seq-positionanswernumber-list);; NUMBER-LIST is not in same POSITION in ANSWER(not(equalnumber-list(nthpositionanswer)))))(defuncount-cows(guessanswer)"Count number of cows in GUESS as compared to ANSWER.In this game, a cow is a match, but only in a different position.Both GUESS and ANSWER are lists of numbers."(let((cows0)(zero-based-position0))(dotimes(n4)(when(is-cow-p(nthzero-based-positionguess)zero-based-positionanswer)(setqcows(1+cows)))(setqzero-based-position(1+zero-based-position)))cows))(defuncount-bulls-and-cows(guessanswercount)"Give game feedback for GUESS as compared to ANSWER."(let((cows(count-cowsguessanswer))(bulls(count-bullsguessanswer)))(goto-char(point-max))(insert(format"\n%3s - %s Bulls = %s Cows = %s"count(number-list-to-stringguess)bullscows))(when(=bulls4)(insert" You win!")t)))(defunget-player-guess()"Get player guess."(let((player-guess))(setqplayer-guess(read-string"Enter a 4 digit number or Q to quit: "))player-guess))(defunplay-bulls-and-cows()"Play bulls and cows game."(interactive)(let((answer(get-list-4-random-digits))(player-guess-string)(player-guess-list-of-numbers)(count0))(with-current-buffer(pop-to-buffer"bulls and cows game")(erase-buffer)(insert(propertize(concat"Rules: Enter a 4 digit number whose digits do not repeat.""\n For example, 2468 is 4 digit number with non-repeating digits.""\n Digits that match both the number and position will be scored as bulls.""\n Digits that match the number but *not* the position will be scored as cows.")'face'shadow));; (insert "Rules: Enter a 4 digit number whose digits do not repeat.");; (insert "\n For example, 2468 is 4 digit number with non-repeating digits.");; (insert "\n Digits that match both the number and position will be scored as bulls.");; (insert "\n Digits that match the number but *not* the position will be scored as cows.")(insert(propertize(concat"\n""\nTurn Your guess Result""\n---- ---------- ------")'face'bold))(catch'end-game(whilet(progn;; get input(setqplayer-guess-string(get-player-guess))(setqplayer-guess-list-of-numbers(list-digitsplayer-guess-string));; evaluate input(cond((string-equal-ignore-caseplayer-guess-string"Q")(insert"\nGame ended because Q was entered")(throw'end-gamet))((four-non-repeating-digits-pplayer-guess-string);; increase count of turns played by 1(setqcount(1+count));; count-bulls-and-cows returns nil if 4 bulls(and(count-bulls-and-cowsplayer-guess-list-of-numbersanswercount)(throw'end-gamet)))(t(goto-char(point-max))(insert(propertize(format"\nThe guess entered was %S\nYou must enter a number with 4 non-repeating digits or Q to quit."player-guess-string)'face'error))))))))))
(play-bulls-and-cows)
Rules: Enter a 4 digit number whose digits do not repeat. For example, 2468 is 4 digit number with non-repeating digits. Digits that match both the number and position will be scored as bulls. Digits that match the number but *not* the position will be scored as cows.Turn Your guess Result---- ---------- ------ 1 - 2468 Bulls = 0 Cows = 1 2 - 1357 Bulls = 0 Cows = 1 3 - 5724 Bulls = 0 Cows = 1 4 - 6857 Bulls = 0 Cows = 0 5 - 8572 Bulls = 0 Cows = 1 6 - 6853 Bulls = 0 Cows = 0 7 - 0219 Bulls = 1 Cows = 3 8 - 9201 Bulls = 4 Cows = 0 You win!
Module:
-module(bulls_and_cows).-export([generate_secret/0,score_guess/2,play/0]).% generate the secret codegenerate_secret()->generate_secret([],4,lists:seq(1,9)).generate_secret(Secret,0,_)->Secret;generate_secret(Secret,N,Digits)->Next=lists:nth(random:uniform(length(Digits)),Digits),generate_secret(Secret++[Next],N-1,Digits--[Next]).% evaluate a guessscore_guess(Secret,Guess)whenlength(Secret)=/=length(Guess)->throw(badguess);score_guess(Secret,Guess)->Bulls=count_bulls(Secret,Guess),Cows=count_cows(Secret,Guess,Bulls),[Bulls,Cows].% count bulls (exact matches)count_bulls(Secret,Guess)->length(lists:filter(fun(I)->lists:nth(I,Secret)==lists:nth(I,Guess)end,lists:seq(1,length(Secret)))).% count cows (digits present but out of place)count_cows(Secret,Guess,Bulls)->length(lists:filter(fun(I)->lists:member(I,Guess)end,Secret))-Bulls.% play a gameplay()->play_round(generate_secret()).play_round(Secret)->play_round(Secret,read_guess()).play_round(Secret,Guess)->play_round(Secret,Guess,score_guess(Secret,Guess)).play_round(_,_,[4,0])->io:put_chars("Correct!\n");play_round(Secret,_,Score)->io:put_chars("\tbulls:"),io:write(hd(Score)),io:put_chars(", cows:"),io:write(hd(tl(Score))),io:put_chars("\n"),play_round(Secret).read_guess()->lists:map(fun(D)->D-48end,lists:sublist(io:get_line("Enter your 4-digit guess: "),4)).
Script:
#!/usr/bin/escript% Play Bulls and Cowsmain(_)->random:seed(now()),bulls_and_cows:play().
Sample play:
Enter your 4-digit guess: 8376bulls:1, cows:0Enter your 4-digit guess: 8941bulls:1, cows:1Enter your 4-digit guess: 8529bulls:1, cows:1Enter your 4-digit guess: 4926bulls:1, cows:1Enter your 4-digit guess: 9321Correct!
include std\text.einclude std\os.einclude std\sequence.einclude std\console.esequence bcData = {0,0} --bull,cow score for the playersequence goalNum = { {0,0,0,0}, {0,0,0,0}, 0} --computer's secret number digits (element 1), marked as bull/cow--indexes in element 2, integer value of it in element 3sequence currentGuess = { {0,0,0,0}, {0,0,0,0}, 0} --player's guess, same format as goalNumsequence removeChars = 0 & " 0\r\t\n" --characters to trim (remove) from user's input. \r, \t are single escaped characters,--0 is ascii 0x0 and number zero is ascii 48, or 0x30. The rest are wysiwyginteger tries = 0 --track number of tries to guess the numbersequence bcStrings ={"bull", "cow"} --stores singular and/or plural strings depending on score in bcDatagoalNum[1] = rand( {9,9,9,9} ) --rand function works on objects. here it outputs into each sequence element.goalNum[3] = goalNum[1][1] * 1000 + goalNum[1][2] * 100 + goalNum[1][3] * 10 + goalNum[1][4] --convert digits to an integer--and store itprocedure getInputAndProcess(integer stage = 1) --object = 1 sets default value for the parameter if it isn't specified goalNum[2][1..4] = 0 --{0,0,0,0} --set these to unscaned (0) since the scanning will start over. currentGuess[1][1..4] = 0 --{0,0,0,0} --these too, or they will contain old marks currentGuess[2][1..4] = 0 tries += 1 --equivalent to tries = tries + 1, but faster and shorter to write bcData[1..2] = 0 -- {0,0} if stage <= 1 then --if this process was run for the first time or with no parameters, then.. puts(1,"The program has thought of a four digit number using only digits 1 to 9.\nType your guess and press enter.\n") end if while 1 label "guesscheck" do --labels can be used to specify a jump point from exit or retry, and help readability currentGuess[1] = trim(gets(0), removeChars) --get user input, trim unwanted characters from it, store it in currentGuess[1] currentGuess[1] = mapping( currentGuess[1], {49,50,51,52,53,54,55,56,57}, {1,2,3,4,5,6,7,8,9} ) --convert ascii codes to -- integer digits they represent integer tempF = find('0',currentGuess[1]) if length(currentGuess[1]) != 4 or tempF != 0 then --if the input string is now more than 4 characters/integers, --the input won't be used. puts(1,"You probably typed too many digits or a 0. Try typing a new 4 digit number with only numbers 1 through 9.\n") retry "guesscheck" else exit "guesscheck" end if end while --convert separate digits to the one integer they represent and store it, like with goalNum[3] currentGuess[3] = currentGuess[1][1] * 1000 + currentGuess[1][2] * 100 + currentGuess[1][3] * 10 + currentGuess[1][4] --convert digits to the integer they represent, to print to a string later --check for bulls for i = 1 to 4 do if goalNum[1][i] = currentGuess[1][i] then goalNum[2][i] = 1 currentGuess[2][i] = 1 bcData[1] += 1 end if end for --check for cows, but not slots marked as bulls or cows already. for i = 1 to 4 label "iGuessElem"do --loop through each guessed digit for j = 1 to 4 label "jGoalElem" do --but first go through each goal digit, comparing the first guessed digit, --and then the other guessed digits 2 through 4 if currentGuess[2][i] = 1 then --if the guessed digit we're comparing right now has been marked as bull or cow already continue "iGuessElem" --skip to the next guess digit without comparing this guess digit to the other goal digits end if if goalNum[2][j] = 1 then --if the goal digit we're comparing to right now has been marked as a bull or cow already continue "jGoalElem" --skip to the next goal digit end if if currentGuess[1][i] = goalNum[1][j] then --if the guessed digit is the same as the goal one, --it won't be a bull, so it's a cow bcData[2] += 1 --score one more cow goalNum[2][j] = 1 --mark this digit as a found cow in the subsequence that stores 0's or 1's as flags continue "iGuessElem" --skip to the next guess digit, so that this digit won't try to check for --matches(cow) with other goal digits end if end for --this guess digit was compared to one goal digit , try comparing this guess digit with the next goal digit end for --this guess digit was compared with all goal digits, compare the next guess digit to all the goal digits if bcData[1] = 1 then --uses singular noun when there is score of 1, else plural bcStrings[1] = "bull" else bcStrings[1] = "bulls" end if if bcData[2] = 1 then --the same kind of thing as above block bcStrings[2] = "cow" else bcStrings[2] = "cows" end if if bcData[1] < 4 then --if less than 4 bulls were found, the player hasn't won, else they have... printf(1, "Guess #%d : You guessed %d . You found %d %s, %d %s. Type new guess.\n", {tries, currentGuess[3], bcData[1], bcStrings[1], bcData[2], bcStrings[2]} ) getInputAndProcess(2) else --else they have won and the procedure ends printf(1, "The number was %d. You guessed %d in %d tries.\n", {goalNum[3], currentGuess[3], tries} ) any_key()--wait for keypress before closing console window. end ifend procedure--run the proceduregetInputAndProcess(1)
Output :
The program has thought of a four digit number using only digits 1 to 9.Type your guess and press enter.7456Guess #1 : You guessed 7456 . You found 1 bull, 1 cow. Type new guess.7116Guess #2 : You guessed 7116 . You found 1 bull, 0 cows. Type new guess.7862Guess #3 : You guessed 7862 . You found 0 bulls, 2 cows. Type new guess.1826[...etc]6586Guess #10 : You guessed 6586 . You found 3 bulls, 0 cows. Type new guess.5586Guess #11 : You guessed 5586 . You found 3 bulls, 0 cows. Type new guess.2586Guess #12 : You guessed 2586 . You found 3 bulls, 0 cows. Type new guess.9586The number was 9586. You guessed 9586 in 13 tries.Press Any Key to continue...
openSystemletgenerate_numbertargetSize=letrnd=Random()letinitial=Seq.initInfinite(fun_->rnd.Next(1,9))initial|>Seq.distinct|>Seq.take(targetSize)|>Seq.toListletcountBullsguesstarget=lethits=List.map2(fungt->ifg=tthentrueelsefalse)guesstargetList.filter(funx->x=true)hits|>List.lengthletcountCowsguesstarget=letmutablescore=0forginguessdofortintargetdoifg=tthenscore<-score+1elsescore<-scorescoreletcountScoreguesstarget=letbulls=countBullsguesstargetletcows=countCowsguesstarget(bulls,cows)letplayRoundguesstarget=countScoreguesstargetletinlinectoic:int=intc-int'0'letlineToList(line:string)=letlistc=Seq.map(func->c|>string)line|>Seq.toListletconv=List.map(funx->Int32.Parsex)listcconvletreadLine()=letline=Console.ReadLine()ifline<>nullthenifline.Length=4thenOk(lineToListline)elseError("Input guess must be 4 characters!")elseError("Input guess cannot be empty!")letrechandleInput()=letline=readLine()matchlinewith|Okx->x|Errors->printfn"%A"shandleInput()[<EntryPoint>]letmainargv=lettarget=generate_number4letmutableshouldEnd=falsewhileshouldEnd=falsedoletguess=handleInput()let(b,c)=playRoundguesstargetprintfn"Bulls: %i | Cows: %i"bcifb=4thenshouldEnd<-trueelseshouldEnd<-false0
function get_digit( num as uinteger, ps as uinteger ) as uinteger return (num mod 10^(ps+1))\10^psend functionfunction is_malformed( num as uinteger ) as boolean if num > 9876 then return true dim as uinteger i, j for i = 0 to 2 for j = i+1 to 3 if get_digit( num, j ) = get_digit( num, i ) then return true next j next i return falseend functionfunction make_number() as uinteger dim as uinteger num = 0 while is_malformed(num) num = int(rnd*9877) wend return numend functionrandomize timerdim as uinteger count=0, num=make_number(), guess=0dim as uinteger cows, bulls, i, jwhile guess <> num count += 1 do print "Guess a number. " input guess loop while is_malformed(guess) cows = 0 bulls = 0 for i = 0 to 3 for j = 0 to 3 if get_digit( num, i ) = get_digit( guess, j ) then if i= j then bulls += 1 if i<>j then cows += 1 end if next j next i print using "You scored # bulls and # cows."; bulls; cowswendprint using "Correct. That took you ### guesses."; count
idiomatic style:
USING:iokernelmathmath.parserrandomrangessequencessets;IN:bullsncows9[1..b]4sample[48+]""map-as["guess the 4-digit number: "writeflushreadlndup[length4=][[48 57[a..b]in?]all?]biand! [48,57] is the ascii range for 0-9[2dup=[2drop"yep!"printflushf]["bulls & cows: "write[0[=1 0?+]2reduce][intersectlength]2biover-[number>string]bi@" & "glueprintflusht]if][2drop"bad input"printt]if]curryloop
imperative/oop style:
USING:accessorsassocscombinatorsfrygroupinghashtableskernellocalsmathmath.parsermath.rangesrandomsequencesstringsioascii;IN:bullsncowsTUPLE:scorebullscows;:<score>(--score)0 0scoreboa;TUPLE:cow;:<cow>(--cow)cownew;TUPLE:bull;:<bull>(--bull)bullnew;:inc-bulls(score--score)dupbulls>>1+>>bulls;:inc-cows(score--score)dupcows>>1+>>cows;:random-nums(--seq)9[1,b]4sample;:add-digits(seq--n)0[swap10*+]reducenumber>string;:new-number(--nnarr)random-numsdupadd-digits;:narr>nhash(narr--nhash){1 2 3 4}swapzip;:num>hash(n--hash)[1stringstring>number]{}map-asnarr>nhash;::cow-or-bull(ng--arr){{[nfirstgatnsecond=][<bull>]}{[nsecondgvalue?][<cow>]}[f]}cond;:add-to-score(arr--score)<score>[bull?[inc-bulls][inc-cows]if]reduce;:check-win(score--?)bulls>>4=;:sum-score(ng--score?)'[_cow-or-bull]mapsiftadd-to-scoredupcheck-win;:print-sum(score--str)dupbulls>>number>string"Bulls: "swapappendswapcows>>number>string" Cows: "swap3append"\n"append;:(validate-readln)(str--?)duplength4=notswap[letter?]all?or;:validate-readln(--str)readlndup(validate-readln)["Invalid input.\nPlease enter a valid 4 digit number: "writeflushdropvalidate-readln]when;:win(--)"\nYou've won! Good job. You're so smart."printflush;:main-loop(x--)"Enter a 4 digit number: "writeflushvalidate-readlnnum>hashswap[sum-scoreswapprint-sumprintflush]keepswapnot[main-loop][dropwin]if;:main(--)new-numberdropnarr>nhashmain-loop;
**** Bulls and cows. A game pre-dating, and similar to, Mastermind.**classBullsAndCows{Voidmain(){digits:=[1,2,3,4,5,6,7,8,9]size:=4chosen:=[,]size.times{chosen.add(digits.removeAt(Int.random(0..<digits.size)))}echo("I've chosen$size unique digits from 1 to 9 at random.Trytoguessmynumber!")guesses:=0while(true)// game loop{guesses+=1guess:=Int[,]while(true)// input loop{// get a good guessSys.out.print("\nNext guess [$guesses]:")Sys.out.flushinString:=Sys.in.readLine?.trim?:""inString.each|ch|{if(ch>='1'&&ch<='9'&&!guess.contains(ch))guess.add(ch-'0')}if(guess.size==4)break// input loopecho("Oops, try again. You need to enter$size unique digits from 1 to 9")}if(guess.all|v,i->Bool|{returnv==chosen[i]}){echo("\nCongratulations! You guessed correctly in$guesses guesses")break// game loop}bulls:=0cows:=0(0..<size).each|i|{if(guess[i]==chosen[i])bulls+=1elseif(chosen.contains(guess[i]))cows+=1}echo("\n$bulls Bulls\n$cows Cows")}}}
01.10 T %1,"BULLS AND COWS"!"----- --- ----"!!01.20 S T=0;D 301.30 D 2;D 5;S T=T+1;T "BULLS",B," COWS",C,!!01.40 I (B-4)1.301.50 T "YOU WON! GUESSES",%4,T,!!01.60 Q02.10 A "GUESS",A02.20 F X=0,3;S B=FITR(A/10);S G(3-X)=A-B*10;S A=B02.30 S A=102.40 F X=0,3;S A=A*G(X)02.50 I (-A)2.6;T "NEED FOUR NONZERO DIGITS"!;G 2.102.60 F X=0,2;F Y=X+1,3;S A=A*(FABS(G(X)-G(Y)))02.70 I (-A)2.8;T "NO DUPLICATES ALLOWED"!;G 2.102.80 R03.10 F X=0,3;S S(X)=003.20 F X=0,3;D 4;S S(X)=A04.10 S A=10*FRAN();S A=FITR(1+9*(A-FITR(A)))04.20 S Z=104.30 F Y=0,3;S Z=Z*(FABS(A-S(Y)))04.40 I (-Z)4.5,4.104.50 R05.10 S B=005.20 F X=0,3;D 5.605.30 S C=-B05.40 F X=0,3;F Y=0,3;D 5.705.50 R05.60 I (-FABS(S(X)-G(X)))5.5,5.805.70 I (-FABS(S(X)-G(Y)))5.5,5.905.80 S B=B+105.90 S C=C+1
BULLS AND COWS----- --- ----GUESS:1234BULLS= 0 COWS= 3GUESS:3214BULLS= 1 COWS= 2GUESS:3124BULLS= 2 COWS= 1GUESS:3145BULLS= 3 COWS= 0GUESS:3146BULLS= 3 COWS= 0GUESS:3147BULLS= 3 COWS= 0GUESS:3148BULLS= 3 COWS= 0GUESS:3149BULLS= 4 COWS= 0YOU WON! GUESSES= 8
includerandom.fscreatehidden4allot:ok?( str -- ? )dup4<>if2dropfalseexitthen19lshift1--rotboundsdoic@'1-dup09within0=if2dropfalseleavethen1swaplshiftoveranddup0=ifnipleavethenxorloop0<>;:initbeginhidden4boundsdo9random'1+ic!loophidden4ok?until;:check?( addr -- solved? )040dooveri+c@40doduphiddeni+c@=ifswapij=if8else1then+swapthenloopdroploopnip8/modtuck.."bulls,".."cows"4=;:guess:( "1234" -- )blparse2dupok?0=if2drop."Bad guess! (4 unique digits, 1-9)"exitthendropcheck?ifcr."You guessed it!"then;
init ok guess: 1234 1 bulls, 0 cows ok guess: 1567 1 bulls, 1 cows ok guess: 1895 2 bulls, 1 cows ok guess: 1879 4 bulls, 0 cows You guessed it! ok
modulebacimplicit nonecontains subroutineGennum(n)integer,intent(out)::n(4)integer::i,jreal::rcallrandom_number(r)n(1)=int(r*9.0)+1i=2outer:do while(i<=4)callrandom_number(r)n(i)=int(r*9.0)+1inner:doj=i-1,1,-1if(n(j)==n(i))cycleouterend doinneri=i+1end doouterend subroutineGennumsubroutineScore(n,guess,b,c)character(*),intent(in)::guessinteger,intent(in)::n(0:3)integer,intent(out)::b,cinteger::digit,i,j,indb=0;c=0doi=1,4read(guess(i:i),"(i1)")digitif(digit==n(i-1))thenb=b+1else doj=i,i+2ind=mod(j,4)if(digit==n(ind))thenc=c+1exit end if end do end if end do end subroutineScoreend modulebacprogramBulls_and_Cowsusebacimplicit noneinteger::n(4)integer::bulls=0,cows=0,tries=0character(4)::guesscallrandom_seedcallGennum(n)write(*,*)"I have selected a number made up of 4 digits (1-9) without repetitions."write(*,*)"You attempt to guess this number."write(*,*)"Every digit in your guess that is in the correct position scores 1 Bull"write(*,*)"Every digit in your guess that is in an incorrect position scores 1 Cow"write(*,*)do while(bulls/=4)write(*,*)"Enter a 4 digit number"read*,guessif(verify(guess,"123456789")/=0)then write(*,*)"That is an invalid entry. Please try again."cycle end iftries=tries+1callScore(n,guess,bulls,cows)write(*,"(a, i1, a, i1, a)")"You scored ",bulls," bulls and ",cows," cows"write(*,*)end do write(*,"(a,i0,a)")"Congratulations! You correctly guessed the correct number in ",tries," attempts"end programBulls_and_Cows
// Bulls and Cows - Written in Frinkprintln["Welcome to Bulls and Cows!"]// Put 4 random digits into target arraydigits = array[1 to 9]target = new arrayfor i = 0 to 3{ target@i = digits.removeRandom[]}// Game variablesguessCount = 0solved = 0while solved == 0{ // Round variables bulls = 0 cows = 0 // Input guess from player guess = input["Guess a 4 digit number with numbers 1 to 9: "] // Valid Guess Tests. Set validGuess to 1. If any test fails it will be set to 0 validGuess = 1 // Test for exactly 4 digits if length[guess] != 4 { println["$guess is invalid. Your guess must be 4 digits."] validGuess = 0 } // Test for any characters not in 1 - 9 using regex if guess =~ %r/[^1-9]/ { println["$guess is invalid. Your guess can only contain the digits 1 through 9."] validGuess = 0 } // Check for duplicate digits in guess comboCheck = 1 guessArr = charList[guess] // Split guess string into array of characters. guessArrCombos = guessArr.combinations[2] // Divide the array into all possible 2 digits combinations. for geussCombo = guessArrCombos { if geussCombo@0 == geussCombo@1 // If the two digits in the combinations are the same mark the comboCheck as failed. comboCheck = 0 } if comboCheck == 0 { println["$guess is invalid. Each digit in your guess should be unique."] validGuess = 0 } // If all tests pass, continue with the game. if validGuess == 1 { guessCount = guessCount + 1 for i = 0 to 3 { if parseInt[guessArr@i] == target@i // Convert guess from string to int. Frink imports all input as strings. { bulls = bulls + 1 next // If bull is found, skip the contains check. } if target.contains[parseInt[guessArr@i]] { cows = cows + 1 } } if bulls == 4 { solved = 1 // Exit from While loop. } else { // Print the results of the guess. Formatting for plurals. bullsPlural = bulls == 1 ? "bull" : "bulls" cowsPlural = cows == 1 ? "cow" : "cows" println["Your guess of $guess had $bulls $bullsPlural and $cows $cowsPlural."] } }}guessPlural = guessCount == 1 ? "guess" : "guesses"println["Congratulations! Your guess of $guess was correct! You solved this in $guessCount $guessPlural."]
Welcome to Bulls and Cows!Your guess of 1234 had 1 bull and 2 cows.Your guess of 5678 had 0 bulls and 1 cow.Your guess of 2345 had 0 bulls and 2 cows.Your guess of 3261 had 1 bull and 2 cows.Your guess of 4173 had 0 bulls and 3 cows.Your guess of 8231 had 2 bulls and 0 cows.Your guess of 7134 had 1 bull and 2 cows.Your guess of 3461 had 2 bulls and 2 cows.Congratulations! Your guess of 6431 was correct! You solved this in 9 guesses.
include "NSLog.incl"str15 guess, goalshort x, ycgRect wndrectbegin enum 1 _window _bullLabel _cowLabel _horzLine _vertLine _newGameBtn _alert = 101end enumvoid local fn showStr( string as str15 ) short r x = 20 for r = 1 to string[0] print %(x,y)chr$( string[r] ); x += 39 nextend fnvoid local fn NewGame str15 ch goal = "" : guess = "" :y = 20 window _window,,wndRect text ,,fn colorRed cls fn showStr( "????" ) do ch = chr$(rnd(9) or _"0") if instr$(0, goal, ch) == 0 then goal += ch until goal[0] == 4 nslog(@"%u",val&(goal)) //unrem for testing y += 48end fnlocal fn SetWindowFrame CGRect r = fn WindowContentRect( _window ) r.size.height += 32 r.origin.y -= 32 window _window,,r if ( r.origin.y < 150 ) alert _alert,, @"Too many guesses!",, @"Give up", YES fn newGame end ifend fnlocal fn play( ch as str15 ) short r, bulls = 0, cows = 0 if instr$(0, guess, ch) then exit fn guess += ch text,,fn colorDarkGray fn showStr( guess ) if guess[0] < 4 then exit fn for r = 1 to 4 if goal[r] == guess[r] then bulls++ : continue if instr$(0, goal, chr$(guess[r]) ) then cows++ next select case bulls == 4 text ,,fn colorRed print %(x + 31, y)("W I N!") y = 20 : fn showStr( goal ) case else : print %(x + 35, y)bulls;" "; cows y += 32 : guess = "" end select fn SetWindowFrameend fnvoid local fn BuildWindow subclass window _window, @"Bulls and cows", (0,0,311,114), NSWindowStyleMaskTitled + NSWindowStyleMaskClosable wndrect = = fn WindowContentRect( _window ) textlabel _bullLabel, @"🐂", (198,59,38,40) textlabel _cowLabel, @"🐄", (255,59,38,40) ControlSetFontWithName( _bullLabel, NULL, 30 ) ControlSetFontWithName( _cowLabel, NULL, 30 ) box _horzLine,, (12,50,287,5), NSBoxSeparator box _vertLine,, (180,12,5,90), NSBoxSeparator ViewSetAutoresizingMask( _vertLine, NSViewHeightSizable ) button _newGameBtn,,, @"New Game", (198,13,100,32) ViewSetAutoresizingMask( _newGameBtn, NSViewMaxYMargin ) text @"menlo bold",24,,fn ColorWindowBackgroundend fnvoid local fn DoDialog( evt as long, tag as long ) select ( evt ) case _windowKeyDown //: stop short ch = intval( fn EventCharacters ) if ch then fn play( chr$( ch or _"0" ) ):DialogEventSetBool(YES) case _btnClick : fn NewGame case _windowWillClose : end end selectend fnon dialog fn DoDialogfn buildWindowfn newGameHandleEvents
File:Bulls and Cows in FutureBasic.png
packagemainimport("bufio""bytes""fmt""math/rand""os""strings""time")funcmain(){fmt.Println(`Cows and BullsGuess four digit number of unique digits in the range 1 to 9.A correct digit but not in the correct place is a cow.A correct digit in the correct place is a bull.`)// generate patternpat:=make([]byte,4)rand.Seed(time.Now().Unix())r:=rand.Perm(9)fori:=rangepat{pat[i]='1'+byte(r[i])}// accept and score guessesvalid:=[]byte("123456789")guess:forin:=bufio.NewReader(os.Stdin);;{fmt.Print("Guess: ")guess,err:=in.ReadString('\n')iferr!=nil{fmt.Println("\nSo, bye.")return}guess=strings.TrimSpace(guess)iflen(guess)!=4{// malformed: not four charactersfmt.Println("Please guess a four digit number.")continue}varcows,bullsintforig,cg:=rangeguess{ifstrings.IndexRune(guess[:ig],cg)>=0{// malformed: repeated digitfmt.Printf("Repeated digit: %c\n",cg)continueguess}switchbytes.IndexByte(pat,byte(cg)){case-1:ifbytes.IndexByte(valid,byte(cg))==-1{// malformed: not a digitfmt.Printf("Invalid digit: %c\n",cg)continueguess}default:// I just think cows should go firstcows++caseig:bulls++}}fmt.Printf("Cows: %d, bulls: %d\n",cows,bulls)ifbulls==4{fmt.Println("You got it.")return}}}
#!/usr/bin/env golosh----This module is the Bulls and Cows game.----moduleBullsandcowsimportgololang.Decoratorsimportgololang.Functionsimportgololang.IOimportjava.utilfunctionmain=|args|{whiletrue{letsecret=create4RandomNumbers()println("Welcome to Bulls And Cows")whiletrue{println("Please enter a 4 digit number")println("(with only the digits 1 to 9 and no repeated digits, for example 2537)")letguess=readln("guess:")letresult=validateGuess(guess)ifresult:isValid(){letbulls,cows=bullsAndOrCows(result:digits(),secret)ifbullsis4{println("You win!")break}println("bulls:"+bulls)println("cows:"+cows)}else{println(result:message())}}}}functioncreate4RandomNumbers={letnumbers=vector[1,2,3,4,5,6,7,8,9]Collections.shuffle(numbers)letshuffled=numbers:subList(0,4)returnshuffled}unionResult={Valid={digits}Invalid={message}}@checkArguments(isString())functionvalidateGuess=|guess|{vardigits=[]try{letnumber=guess:toInt()digits=number:digits()ifdigits:exists(|d|->dis0){returnResult.Invalid("No zeroes please")}ifdigits:size()isnt4{returnResult.Invalid("Four digits please")}letdigitSet=set[digitforeachdigitindigits]ifdigitSet:size()<digits:size(){returnResult.Invalid("No duplicate numbers please")}}catch(e){returnResult.Invalid("Numbers only please")}returnResult.Valid(digits)}letis4Vector=|arg|->argoftypejava.util.List.classandarg:size()is4@checkArguments(is4Vector,is4Vector)functionbullsAndOrCows=|guess,secret|{varbulls=0varcows=0foreachiin[0..4]{letguessNum=guess:get(i)letsecretNum=secret:get(i)ifguessNumissecretNum{bulls=bulls+1}elseifsecret:exists(|num|->guessNumisnum){cows=cows+1}}return[bulls,cows]}augmentjava.lang.Integer{functiondigits=|this|{varremaining=thisletdigits=vector[]whileremaining>0{digits:prepend(remaining%10)remaining=remaining/10}returndigits}}
classBullsAndCows{staticvoidmain(args){definputReader=System.in.newReader()defnumberGenerator=newRandom()deftargetValuewhile(targetValueIsInvalid(targetValue=numberGenerator.nextInt(9000)+1000))continuedeftargetStr=targetValue.toString()defguessed=falsedefguesses=0while(!guessed){defbulls=0,cows=0print'Guess a 4-digit number with no duplicate digits: 'defguess=inputReader.readLine()if(guess.length()!=4||!guess.isInteger()||targetValueIsInvalid(guess.toInteger())){continue}guesses++4.times{if(targetStr[it]==guess[it]){bulls++}elseif(targetStr.contains(guess[it])){cows++}}if(bulls==4){guessed=true}else{println"$cows Cows and $bulls Bulls."}}println"You won after $guesses guesses!"}statictargetValueIsInvalid(value){defdigitList=[]while(value>0){if(digitList[value%10]==0||digitList[value%10]){returntrue}digitList[value%10]=truevalue=value.intdiv(10)}false}}
importData.List(partition,intersect,nub)importControl.MonadimportSystem.Random(StdGen,getStdRandom,randomR)importText.PrintfnumberOfDigits=4::Intmain=bullsAndCowsbullsAndCows::IO()bullsAndCows=dodigits<-getStdRandom$picknumberOfDigits['1'..'9']putStrLn"Guess away!"loopdigitswhereloopdigits=doinput<-getLineifokayinputthenlet(bulls,cows)=scoredigitsinputinifbulls==numberOfDigitsthenputStrLn"You win!"elsedoprintf"%d bulls, %d cows.\n"bullscowsloopdigitselsedoputStrLn"Malformed guess; try again."loopdigitsokay::String->Boolokayinput=lengthinput==numberOfDigits&&input==nubinput&&alllegalcharinputwherelegalcharc='1'<=c&&c<='9'score::String->String->(Int,Int)scoresecretguess=(lengthbulls,cows)where(bulls,nonbulls)=partition(uncurry(==))$zipsecretguesscows=length$uncurryintersect$unzipnonbullspick::Int->[a]->StdGen->([a],StdGen){- Randomly selects items from a list without replacement. -}picknlg=fnlg(lengthl-1)[]wheref0_g_ps=(ps,g)fnlgmaxps=f(n-1)(left++right)g'(max-1)(picked:ps)where(i,g')=randomR(0,max)g(left,picked:right)=splitAtil
(importrandom)(def+size+4)(def+digits+"123456789")(def+secret+(random.sample+digits++size+))(whileTrue(whileTrue(setvguess(list(distinct(raw-input"Enter a guess: "))))(when(and(=(lenguess)+size+)(all(map(fn[c](inc+digits+))guess)))(break))(print"Malformed guess; try again"))(setvbulls0)(setvcows0)(for[i(range+size+)](cond[(=(getguessi)(get+secret+i))(setvbulls(incbulls))][(in(getguessi)+secret+)(setvcows(inccows))]))(when(=bulls+size+)(break))(print(.format"{} bull{}, {} cows"bulls(if(=bulls1)"""s")cows(if(=cows1)"""s"))))(print"A winner is you!")
The following works in both Icon and Unicon.
proceduremain()digits:="123456789"every!digits:=:?digitsnum:=digits[1+:4]repeatifscore(num,getGuess(num))thenbreakwrite("Good job.")endproceduregetGuess(num)repeat{writes("Enter a guess: ")guess:=read()|stop("Quitter!")if*(guess**'123456789')==*numthenreturnguesswrite("Malformed guess: ",guess,". Try again.")}endprocedurescore(num,guess)bulls:=0cows:=*(num**guess)every(num[i:=1to*num]==guess[i],bulls+:=1,cows-:=1)write("\t",bulls," bulls and ",cows," cows")return(bulls=*num)end
A tacit recursive functional version. To play, callmoo
with a dummy argument, as inmoo 0
ormoo
.
output=.['Bulls: '&,:@'Cows: 'echo@,.":@,.valid=.*./@e.&'0123456789'*.4=#guess=.[:".&>::]$:^:(-.@valid)@(1!:1@1)@echo@'Guess:'game=.[$:^:(40-.@-:])[(+/@:=output@,e.+/@:*.~:)guessmoo=.'You win!'[(1+4?9:)game]
This version is also broken into smaller pieces.
U=.{{u^:(-.@:v)^:_.}}NB. apply u until v is trueinput=.1!:1@1@echo@'Guess: 'output=.[('Bulls: ',:'Cows: ')echo@,.":@,.isdigits=.*./@e.&'0123456789'valid=.isdigits*.4=#guess=.[:".&>inputU(valid@])bulls=.+/@:=cows=.[:+/e.*.~:game=.([:output[(bulls,cows)guess)U(40-:])random=.1+4?9:moo=.'You win!'[randomgame]
In real applications, something like'bad input' assert i.@10 e.~ a.&i.-48"_
should be used instead of".
to safely convert character input to a numeric array.
require'misc'plural=:conjunctiondefine(":m),' ',n,'s'#~1~:m)bullcow=:monaddefinenumber=.1+4?9whilst.-.guess-:numberdo.guess=.0"."0prompt'Guess my number: 'if.(4~:#guess)+.(4~:#~.guess)+.0e.guesse.1+i.9do.if.0=#guessdo.smoutput'Giving up.'return.end.smoutput'Guesses must be four different non-zero digits'continue.end.bulls=.+/guess=numbercows=.(+/guesse.number)-bullssmoutputbullsplural'bull',' and ',cowsplural'cow','.'end.smoutput'you win')
For example:
bullcow''Guessmynumber:12340bullsand1cow.Guessmynumber:56783bullsand0cows.Guessmynumber:23490bullsand0cows.Guessmynumber:15670bullsand3cows.Guessmynumber:61783bullsand0cows.Guessmynumber:61571bulland2cows.Guessmynumber:51784bullsand0cows.youwin
importjava.util.InputMismatchException;importjava.util.Random;importjava.util.Scanner;publicclassBullsAndCows{publicstaticvoidmain(String[]args){Randomgen=newRandom();inttarget;while(hasDupes(target=(gen.nextInt(9000)+1000)));StringtargetStr=target+"";booleanguessed=false;Scannerinput=newScanner(System.in);intguesses=0;do{intbulls=0;intcows=0;System.out.print("Guess a 4-digit number with no duplicate digits: ");intguess;try{guess=input.nextInt();if(hasDupes(guess)||guess<1000)continue;}catch(InputMismatchExceptione){continue;}guesses++;StringguessStr=guess+"";for(inti=0;i<4;i++){if(guessStr.charAt(i)==targetStr.charAt(i)){bulls++;}elseif(targetStr.contains(guessStr.charAt(i)+"")){cows++;}}if(bulls==4){guessed=true;}else{System.out.println(cows+" Cows and "+bulls+" Bulls.");}}while(!guessed);System.out.println("You won after "+guesses+" guesses!");}publicstaticbooleanhasDupes(intnum){boolean[]digs=newboolean[10];while(num>0){if(digs[num%10])returntrue;digs[num%10]=true;num/=10;}returnfalse;}}
Output:
Guess a 4-digit number with no duplicate digits: 58342 Cows and 0 Bulls.Guess a 4-digit number with no duplicate digits: 12341 Cows and 0 Bulls.Guess a 4-digit number with no duplicate digits: 43211 Cows and 0 Bulls.Guess a 4-digit number with no duplicate digits: 34210 Cows and 1 Bulls.Guess a 4-digit number with no duplicate digits: 84120 Cows and 0 Bulls.Guess a 4-digit number with no duplicate digits: 35601 Cows and 1 Bulls.Guess a 4-digit number with no duplicate digits: 36500 Cows and 2 Bulls.Guess a 4-digit number with no duplicate digits: 37592 Cows and 2 Bulls.Guess a 4-digit number with no duplicate digits: 39752 Cows and 2 Bulls.Guess a 4-digit number with no duplicate digits: 3957You won after 10 guesses!
#!/usr/bin/env jsfunctionmain(){varlen=4;playBullsAndCows(len);}functionplayBullsAndCows(len){varnum=pickNum(len);// print('The secret number is:\n ' + num.join('\n '));showInstructions(len);varnGuesses=0;while(true){nGuesses++;varguess=getGuess(nGuesses,len);varcensus=countBovine(num,guess);showScore(census.bulls,census.cows);if(census.bulls==len){showFinalResult(nGuesses);return;}}}functionshowScore(nBulls,nCows){print(' Bulls: '+nBulls+', cows: '+nCows);}functionshowFinalResult(guesses){print('You win!!! Guesses needed: '+guesses);}functioncountBovine(num,guess){varcount={bulls:0,cows:0};varg=guess.join('');for(vari=0;i<num.length;i++){vardigPresent=g.search(num[i])!=-1;if(num[i]==guess[i])count.bulls++;elseif(digPresent)count.cows++;}returncount;}functiongetGuess(nGuesses,len){while(true){putstr('Your guess #'+nGuesses+': ');varguess=readline();guess=String(parseInt(guess)).split('');if(guess.length!=len){print(' You must enter a '+len+' digit number.');continue;}if(hasDups(guess)){print(' No digits can be duplicated.');continue;}returnguess;}}functionhasDups(ary){vart=ary.concat().sort();for(vari=1;i<t.length;i++){if(t[i]==t[i-1])returntrue;}returnfalse;}functionshowInstructions(len){print();print('Bulls and Cows Game');print('-------------------');print(' You must guess the '+len+' digit number I am thinking of.');print(' The number is composed of the digits 1-9.');print(' No digit appears more than once.');print(' After each of your guesses, I will tell you:');print(' The number of bulls (digits in right place)');print(' The number of cows (correct digits, but in the wrong place)');print();}functionpickNum(len){varnums=[1,2,3,4,5,6,7,8,9];nums.sort(function(){returnMath.random()-0.5});returnnums.slice(0,len);}main();
Example game (cheating!):
Bulls and Cows Game------------------- You must guess the 4 digit number I am thinking of. The number is composed of the digits 1-9. No digit appears more than once. After each of your guesses, I will tell you: The number of bulls (digits in right place) The number of cows (correct digits, but in wrong place)Your guess #1: 1234 Bulls: 0, cows: 2Your guess #2: 5678 Bulls: 1, cows: 1Your guess #3: 3167 Bulls: 0, cows: 3Your guess #4: 9123 Bulls: 1, cows: 1Your guess #5: 5137 Bulls: 1, cows: 3Your guess #6: 5317 Bulls: 2, cows: 2Your guess #7: 5731 Bulls: 2, cows: 2Your guess #8: 5713 Bulls: 4, cows: 0You win! Guesses needed: 8
Also works with gojq, the Go implementation of jq.
Adapted fromWren
The following program reads the user's input from STDIN, and readsrandom digits from /dev/random using the --slurpfile command-lineoption. This makes the program more convoluted than would have beenthe case had the generation of the initial four-digit pseudo-randominteger been done in a separate step, but it does illustrate howthe limitations of jq's I/O can be circumventedin this case.
In a bash or bash-like environment, a suitable invocationwould be as follows:
jq -nrR --slurpfile raw <(< /dev/random tr -cd '0-9' | fold -w 1 | head -n 100) -f bc.jq
bc.jq
# A PRNG for generating a pseudo-random integer in range(0; .).# $array must be a sufficiently large array of pseudo-random integers in range(0;10).# $start specifies the position in $array to begin searching.# Output: {prn, start) where .prn is a PRN in range(0; .) and .start is the corresponding position in $array.def prn($array; $start): def a2n: map(tostring) | join("") | tonumber; if . == 1 then 0 else . as $n | (($n-1)|tostring|length) as $w | {$start} | until( $array[.start: .start + $w] | a2n < $n; .start+=1 ) | {start, prn: ($raw[.start: .start + $w] | a2n)} end;# Generate a 4-digit PRN from 1234 to 9876 inclusive, with no zeros or repeated digits.# Global variable: $raw (see documentation for $array above)def num: def _num($start): (8643|prn($raw; $start)) as $prn | (1234 + $prn.prn) | . as $n | tostring | if (test("0")|not) and ((explode|unique|length) == 4) then $n else _num($prn.start+4) end; _num(0);def MAX_GUESSES: 20; # saydef instructions: "All guesses should have exactly 4 distinct digits excluding zero.", "Keep guessing until you guess the chosen number (maximum \(MAX_GUESSES) valid guesses).\n";def play: num as $num | ($num|tostring|explode) as $numArray | { guesses: 0 } | instructions, "Enter your guess:", (label $out | foreach range(0; infinite) as $i (.; if .bulls == 4 or .guesses == MAX_GUESSES then break $out else .guess = input | if .guess == $num then .emit = "You have won with \(.guesses+1) valid guesses!" else .n = (.guess | try tonumber catch null) | if .n == null then .emit = "Not a valid number" elif .guess|test("[+-.]") then .emit = "The guess should not contain a sign or decimal point." elif .guess|test("0") then .emit = "The guess cannot contain zero." elif .guess|length != 4 then .emit = "The guess must have exactly 4 digits." else .guessArray = (.guess | explode ) | if .guessArray | unique | length < 4 then .emit = "All digits must be distinct." else . + {bulls: 0, cows: 0 } | reduce range(0; .guessArray|length) as $i ( .; if $numArray[$i] == .guessArray[$i] then .bulls += 1 elif (.guessArray[$i] | IN($numArray[])) then .cows += 1 else . end) | .emit = "Your score for this guess: Bulls = \(.bulls) Cows = \(.cows)" | .guesses += 1 end end end end; select(.emit).emit, if .bulls == 4 then "Congratulations!" elif .guesses == MAX_GUESSES then "\nYou have now had \(.guesses) valid guesses, the maximum allowed. Bye!" else "Enter your next guess:" end ) );play
functioncowsbulls()print("Welcome to Cows & Bulls! I've picked a number with unique digits between 1 and 9, go ahead and type your guess.\nYou get one bull for every right number in the right position.\nYou get one cow for every right number, but in the wrong position.\nEnter 'n' to pick a new number and 'q' to quit.\n>")functionnew_number()s=[1:9]n=""fori=9:-1:6n*=string(delete!(s,rand(1:i)))endreturnnendanswer=new_number()whiletrueinput=chomp(readline(STDIN))input=="q"&&breakifinput=="n"answer=new_number()print("\nI've picked a new number, go ahead and guess\n>")continueend!ismatch(r"^[1-9]{4}$",input)&&(print("Invalid guess: Please enter a 4-digit number\n>");continue)ifinput==answerprint("\nYou're right! Good guessing!\nEnter 'n' for a new number or 'q' to quit\n>")elsebulls=sum(answer.data.==input.data)cows=sum([answer[x]!=input[x]&&contains(input.data,answer[x])forx=1:4])print("\nNot quite! Your guess is worth:\n$bulls Bulls\n$cows Cows\nPlease guess again\n\n>")endendend
The following version checks thoroughly that the input of the player is constituted of four distincts digits.
functionbullsandcows()bulls=cows=turns=0result=(s=[];whilelength(unique(s))<4push!(s,rand('1':'9'))end;unique(s))println("A game of bulls and cows!")while(bulls!=4)print("Your guess? ")guess=collect(chomp(readline(STDIN)))if!(length(unique(guess))==length(guess)==4&&all(isdigit,guess))println("please, enter four distincts digits")continueendbulls=sum(map(==,guess,result))cows=length(intersect(guess,result))-bullsprintln("$bulls bulls and$cows cows!");turns+=1endprintln("You win! You succeeded in$turns guesses.")end
julia> bullsandcows()A game of bulls and cows!Your guess? 12340 bulls and 2 cows!Your guess? 12334please, enter four distincts digitsYour guess? 56781 bulls and 1 cows!Your guess? 1111please, enter four distincts digitsYour guess? grrplease, enter four distincts digitsYour guess? ...please, enter four distincts digitsYour guess?
run in ngn/k.
n:1+-4?9loop:{`1:"guess: ";g:(`i$-1_1:`)-48/ -48 to convert ascii digit codepoints to corresponding int values$[n~g;[`0:"yup!";`exit0](4=#g)&*/(g<10)&~g<0;`0:"bulls & cows: "," & "/$(b;(#g^g^n)-b:+/n=g)`0:"bad input"]}{1}loop/0/ "while true: loop". 0 is a dummy arg
constvalMAX_GUESSES=20// sayfunmain(){valnum=('1'..'9').shuffled().take(4).joinToString("")println("All guesses should have exactly 4 distinct digits excluding zero.")println("Keep guessing until you guess the chosen number (maximum$MAX_GUESSES valid guesses).\n")varguesses=0while(true){print("Enter your guess : ")valguess=readln().trim()if(guess==num){println("You've won with${++guesses} valid guesses!")break}valn=guess.toIntOrNull()if(n==null)println("Not a valid number")elseif('-'inguess||'+'inguess)println("Can't contain a sign")elseif('0'inguess)println("Can't contain zero")elseif(guess.length!=4)println("Must have exactly 4 digits")elseif(guess.toSet().size<4)println("All digits must be distinct")else{varbulls=0varcows=0for((i,c)inguess.withIndex()){if(num[i]==c)bulls++elseif(cinnum)cows++}println("Your score for this guess: Bulls =$bulls Cows =$cows")guesses++if(guesses==MAX_GUESSES)println("You've now had$guesses valid guesses, the maximum allowed")}}}
Sample input/output:
Enter your guess : 1234Your score for this guess: Bulls = 0 Cows = 2Enter your guess : 1256Your score for this guess: Bulls = 0 Cows = 2Enter your guess : 2178Your score for this guess: Bulls = 1 Cows = 0Enter your guess : 2519Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 2569Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 2579Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 2589Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 2539Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 2549You've won with 9 valid guesses!
This game uses an HTML form to submit the answer. The random number and history are stored in a session using Lasso's built in session management.
[definerandomizer()=>{local(n=string)while(#n->size<4)=>{local(r=integer_random(1,9)->asString)#n!>>#r?#n->append(#r)}return#n}definecowbullchecker(n::string,a::string)=>{integer(#n)==integer(#a)?return(:true,map('cows'=0,'bulls'=4,'choice'=#a))local(cowbull=map('cows'=0,'bulls'=0,'choice'=#a),'checked'=array)loop(4)=>{if(#checked!>>integer(#a->values->get(loop_count)))=>{#checked->insert(integer(#a->values->get(loop_count)))if(integer(#n->values->get(loop_count))==integer(#a->values->get(loop_count)))=>{#cowbull->find('bulls')+=1else(#n->values>>#a->values->get(loop_count))#cowbull->find('cows')+=1}}}#cowbull->find('bulls')==4?return(:true,map('cows'=0,'bulls'=4,'choice'=#a))return(:true,#cowbull)}session_start('user')session_addvar('user','num')session_addvar('user','historic_choices')// set up randvar(num)->isNotA(::string)?var(num=randomizer)var(historic_choices)->isNotA(::array)?var(historic_choices=array)local(success=false)// check answerif(web_request->param('a')->asString->size)=>{local(success,result)=cowbullchecker($num,web_request->param('a')->asString)$historic_choices->insert(#result)}if(web_request->params->asStaticArray>>'restart')=>{$num=randomizer$historic_choices=array}]<h1>Bulls and Cows</h1><p>Guess the 4-digit number...</p><p>Your win if the guess is the same as the randomly chosen number.<br>- A score of one bull is accumulated for each digit in your guess that equals the corresponding digit in the randomly chosen initial number.<br>- A score of one cow is accumulated for each digit in your guess that also appears in the randomly chosen number, but in the wrong position.</p>[local(win=false)if($historic_choices->size)=>{withcin$historic_choicesdo=>{^'<p>'+#c->find('choice')+': Bulls: '+#c->find('bulls')+', Cows: '+#c->find('cows')if(#c->find('bulls')==4)=>{^' - YOU WIN!'#win=true^}'</p>'^}}if(not#win)=>{^]<form action="?" method="post"><input name="a" value="[web_request->param('a')->asString]" size="5"><input type="submit" name="guess"><a href="?restart">Restart</a></form>[else'<a href="?restart">Restart</a>'^}]
Game in progress:
Bulls and CowsGuess the 4-digit number...Your win if the guess is the same as the randomly chosen number.- A score of one bull is accumulated for each digit in your guess that equals the corresponding digit in the randomly chosen initial number.- A score of one cow is accumulated for each digit in your guess that also appears in the randomly chosen number, but in the wrong position.4567: Bulls: 0, Cows: 14567: Bulls: 0, Cows: 1(input box) (submit button) Restart
Game in to completion:
Bulls and CowsGuess the 4-digit number...Your win if the guess is the same as the randomly chosen number.- A score of one bull is accumulated for each digit in your guess that equals the corresponding digit in the randomly chosen initial number.- A score of one cow is accumulated for each digit in your guess that also appears in the randomly chosen number, but in the wrong position.1234: Bulls: 0, Cows: 21256: Bulls: 0, Cows: 11789: Bulls: 0, Cows: 11222: Bulls: 0, Cows: 03456: Bulls: 1, Cows: 23564: Bulls: 0, Cows: 33567: Bulls: 0, Cows: 28564: Bulls: 0, Cows: 23564: Bulls: 0, Cows: 34365: Bulls: 0, Cows: 35436: Bulls: 2, Cows: 15478: Bulls: 2, Cows: 05463: Bulls: 3, Cows: 05468: Bulls: 2, Cows: 05493: Bulls: 4, Cows: 0 - YOU WIN!Restart
do while len( secret$) <4 c$ =chr$( int( rnd( 1) *9) +49) if not( instr( secret$, c$)) then secret$ =secret$ +c$ loop print " Secret number has been guessed.... "; secret$ guesses = 0[loop] print " Your guess "; input " "; guess$ guesses = guesses +1 r$ =score$( guess$, secret$) bulls =val( word$( r$, 1, ",")) cows =val( word$( r$, 2, ",")) print " Result: "; bulls; " bulls, and "; cows; " cows" print if guess$ =secret$ then print " You won after "; guesses; " guesses!" print " You guessed it in "; guesses print " Thanks for playing!" wait end if goto [loop]end ' _____________________________________________________________function check( i$) ' check =0 if no digit repeats, else =1 check =0 for i =1 to 3 for j =i +1 to 4 if mid$( i$, i, 1) =mid$( i$, j, 1) then check =1 next j next iend functionfunction score$( a$, b$) ' return as a csv string the number of bulls & cows. bulls = 0: cows = 0 for i = 1 to 4 c$ = mid$( a$, i, 1) if mid$( b$, i, 1) = c$ then bulls = bulls + 1 else if instr( b$, c$) <>0 and instr( b$, c$) <>i then cows = cows + 1 end if end if next i score$ =str$( bulls); ","; str$( cows)end function[quit]close #wend
to ok? :n output (and [number? :n] [4 = count :n] [4 = count remdup :n] [not member? 0 :n])endto init do.until [make "hidden random 10000] [ok? :hidden]endto guess :n if not ok? :n [print [Bad guess! (4 unique digits, 1-9)] stop] localmake "bulls 0 localmake "cows 0 foreach :n [cond [ [[? = item # :hidden] make "bulls 1 + :bulls] [[member? ? :hidden] make "cows 1 + :cows ] ]] (print :bulls "bulls, :cows "cows) if :bulls = 4 [print [You guessed it!]]end
functionShuffleArray(array)fori=1,#array-1dolocalt=math.random(i,#array)array[i],array[t]=array[t],array[i]endendfunctionGenerateNumber()localdigits={1,2,3,4,5,6,7,8,9}ShuffleArray(digits)returndigits[1]*1000+digits[2]*100+digits[3]*10+digits[4]endfunctionIsMalformed(input)localmalformed=falseif#input==4thenlocalalready_used={}fori=1,4dolocaldigit=input:byte(i)-string.byte('0')ifdigit<1ordigit>9oralready_used[digit]thenmalformed=truebreakendalready_used[digit]=trueendelsemalformed=trueendreturnmalformedendmath.randomseed(os.time())math.randomseed(math.random(2^31-1))-- since os.time() only returns secondsprint("\nWelcome to Bulls and Cows!")print("")print("The object of this game is to guess the random 4-digit number that the")print("computer has chosen. The number is generated using only the digits 1-9,")print("with no repeated digits. Each time you enter a guess, you will score one")print("\"bull\" for each digit in your guess that matches the corresponding digit")print("in the computer-generated number, and you will score one\"cow\" for each")print("digit in your guess that appears in the computer-generated number, but is")print("in the wrong position. Use this information to refine your guesses. When")print("you guess the correct number, you win.");print("")quit=falserepeatmagic_number=GenerateNumber()magic_string=tostring(magic_number)-- Easier to do scoring with a stringrepeatio.write("\nEnter your guess (or 'Q' to quit): ")user_input=io.read()ifuser_input=='Q'oruser_input=='q'thenquit=truebreakendifnotIsMalformed(user_input)thenifuser_input==magic_stringthenprint("YOU WIN!!!")elselocalbulls,cows=0,0fori=1,#user_inputdolocalfind_result=magic_string:find(user_input:sub(i,i))iffind_resultandfind_result==ithenbulls=bulls+1elseiffind_resultthencows=cows+1endendprint(string.format("You scored %d bulls, %d cows",bulls,cows))endelseprint("Malformed input. You must enter a 4-digit number with")print("no repeated digits, using only the digits 1-9.")enduntiluser_input==magic_stringifnotquitthenio.write("\nPress <Enter> to play again or 'Q' to quit: ")user_input=io.read()ifuser_input=='Q'oruser_input=='q'thenquit=trueendendifquitthenprint("\nGoodbye!")enduntilquit
Another version:
functioncreateNewNumber()math.randomseed(os.time())localnumbers={1,2,3,4,5,6,7,8,9}localtNumb={}-- list of numbersfori=1,4dotable.insert(tNumb,math.random(#tNumb+1),table.remove(numbers,math.random(#numbers)))endreturntNumbendTNumber=createNewNumber()print('(right number: '..table.concat(TNumber)..')')functionisValueInList(value,list)fori,vinipairs(list)doifv==valuethenreturntrueendendreturnfalseendlocalnGuesses=0whilenotGameOverdonGuesses=nGuesses+1print("Enter your guess (or 'q' to quit): ")localinputwhilenotinputdoinput=io.read()endifinput=="q"thenGameOver=truereturnendlocaltInput={}fori=1,string.len(input)dolocalnumber=tonumber(string.sub(input,i,i))ifnumberandnotisValueInList(number,tInput)thentable.insert(tInput,number)endendlocalmalformed=falseifnot(string.len(input)==4)ornot(#tInput==4)thenprint(nGuesses,'bad input: too short or too long')malformed=trueendifnotmalformedthenprint(nGuesses,'parsed input:',table.concat(tInput,', '))localnBulls,nCows=0,0fori,numberinipairs(tInput)doifTNumber[i]==numberthennBulls=nBulls+1elseifisValueInList(number,TNumber)thennCows=nCows+1endendprint(nGuesses,'Bulls: '..nBulls..' Cows: '..nCows)ifnBulls==4thenprint(nGuesses,'Win!')GameOver=trueendendend
Module Game { Malformed=lambda (a$)->{ =true if len(a$)<>4 then exit n=0 : dummy=val(a$,"int",n) if n<>5 or dummy=0 then exit for i=1 to 9 if len(filter$(a$,str$(i,0)))<3 then break next i =false } BullsAndCows$=lambda$ (a$, b$, &ok) ->{ Def b, c for i=1 to 4 if mid$(a$,i,1)=mid$(b$,i,1) then b++ else.if instr(b$,mid$(a$,i,1))>0 then c++ end if next i ok=b=4 =format$("bulls {0}, cows {1}", b, c) } Random$=lambda$ ->{ def repl$, bank$, c$ bank$="123456789" for i=1 to 4 c$=mid$(bank$,random(1,len(bank$)),1) bank$=filter$(bank$, c$) repl$+=c$ next i =repl$ } target$=Random$() def boolean win=false, a$ do do Input "Next guess ";a% a$=str$(a%,0) if Malformed(a$) then Print "Malformed input, try again" else exit always Print BullsAndCows$(a$, target$, &win) if win then exit Print "Bad guess! (4 unique digits, 1-9)" always Print "You guess it"}Game
BC := proc(n) #where n is the number of turns the user wishes to play before they quitlocal target, win, numGuesses, guess, bulls, cows, i, err; target := [0, 0, 0, 0]: randomize(); #This is a command that makes sure that the numbers are truly randomized each time, otherwise your first time will always give the same result.while member(0, target) or numelems({op(target)}) < 4 do #loop continues to generate random numbers until you get one with no repeating digits or 0starget := [seq(parse(i), i in convert(rand(1234..9876)(), string))]: #a list of random numbersend do:win := false:numGuesses := 0:while win = false and numGuesses < n do #loop allows the user to play until they win or until a set amount of turns have passederr := true;while err do #loop asks for values until user enters a valid numberprintf("Please enter a 4 digit integer with no repeating digits\n");try#catches any errors in user inputguess := [seq(parse(i), i in readline())];if hastype(guess, 'Not(numeric)', 'exclude_container') thenprintf("Postive integers only! Please guess again.\n\n");elif numelems(guess) <> 4 thenprintf("4 digit numbers only! Please guess again.\n\n");elif numelems({op(guess)}) < 4 thenprintf("No repeating digits! Please guess again.\n\n");elif member(0, guess) thenprintf("No 0s! Please guess again.\n\n");else err := false;end if;catch:printf("Invalid input. Please guess again.\n\n");end try;end do:numGuesses := numGuesses + 1;printf("Guess %a: %a\n", numGuesses, guess);bulls := 0;cows := 0;for i to 4 do #loop checks for bulls and cows in the user's guessif target[i] = guess[i] thenbulls := bulls + 1;elif member(target[i], guess) thencows := cows + 1;end if;end do;if bulls = 4 thenwin := true;printf("The number was %a.\n", target);printf(StringTools[FormatMessage]("You won with %1 %{1|guesses|guess|guesses}.", numGuesses));elseprintf(StringTools[FormatMessage]("%1 %{1|Cows|Cow|Cows}, %2 %{2|Bulls|Bull|Bulls}.\n\n", cows, bulls));end if;end do:if win = false and numGuesses >= n then printf("You lost! The number was %a.\n", target); end if;return NULL;end proc:
Please enter a 4 digit integer with no repeating digitsGuess 1: [1, 2, 3, 4]1 Cow, 1 Bull.Please enter a 4 digit integer with no repeating digitsGuess 2: [2, 3, 4, 5]0 Cows, 1 Bull....
digits=Last@FixedPointList[If[Length@Union@#==4,#,Table[Random[Integer,{1,9}],{4}]]&,{}]codes=ToCharacterCode[StringJoin[ToString/@digits]];Module[{r,bulls,cows},While[True,r=InputString[];If[r===$Canceled,Break[],With[{userCodes=ToCharacterCode@r},If[userCodes===codes,Print[r<>": You got it!"];Break[],If[Length@userCodes==Length@codes,bulls=Count[userCodes-codes,0];cows=Length@Intersection[codes,userCodes]-bulls;Print[r<>": "<>ToString[bulls]<>"bull(s), "<>ToString@cows<>"cow(s)."],Print["Guess four digits."]]]]]]]
Output:
{8, 2, 6, 1}3432: 0 bull(s), 1 cow(s).Illegal input.8261: You got it!
functionBullsAndCows% Plays the game Bulls and Cows as the "game master"% Create a secret numbernDigits=4;lowVal=1;highVal=9;digitList=lowVal:highVal;secret=zeros(1,4);fork=1:nDigitsidx=randi(length(digitList));secret(k)=digitList(idx);digitList(idx)=[];end% Give game informationfprintf('Welcome to Bulls and Cows!\n')fprintf('Try to guess the %d-digit number (no repeated digits).\n',nDigits)fprintf('Digits are between %d and %d (inclusive).\n',lowVal,highVal)fprintf('Score: 1 Bull per correct digit in correct place.\n')fprintf(' 1 Cow per correct digit in incorrect place.\n')fprintf('The number has been chosen. Now it''s your moooooove!\n')gs=input('Guess: ','s');% Loop until user guesses right or quits (no guess)nGuesses=1;whilegsgn=str2double(gs);ifisnan(gn)||length(gn)>1% Not a scalarfprintf('Malformed guess. Keep to valid scalars.\n')gs=input('Try again: ','s');elseg=sprintf('%d',gn)-'0';iflength(g)~=nDigits||any(g<lowVal)||any(g>highVal)||...length(unique(g))~=nDigits% Invalid number for gamefprintf('Malformed guess. Remember:\n')fprintf(' %d digits\n',nDigits)fprintf(' Between %d and %d inclusive\n',lowVal,highVal)fprintf(' No repeated digits\n')gs=input('Try again: ','s');elsescore=CountBullsCows(g,secret);ifscore(1)==nDigitsfprintf('You win! Bully for you! Only %d guesses.\n',nGuesses)gs='';elsefprintf('Score: %d Bulls, %d Cows\n',score)gs=input('Guess: ','s');endendendnGuesses=nGuesses+1;% Counts malformed guessesendendfunctionscore=CountBullsCows(guess, correct)% Checks the guessed array of digits against the correct array to find the score% Assumes arrays of same length and valid numbersbulls=guess==correct;cows=ismember(guess(~bulls),correct);score=[sum(bulls)sum(cows)];end
Welcome to Bulls and Cows!Try to guess the 4-digit number (no repeated digits).Digits are between 1 and 9 (inclusive).Score: 1 Bull per correct digit in correct place. 1 Cow per correct digit in incorrect place.The number has been chosen. Now it's your moooooove!Guess: 1234Score: 0 Bulls, 2 CowsGuess: 2156Score: 0 Bulls, 1 CowsGuess: 7819Score: 0 Bulls, 1 CowsGuess: 3457Score: 0 Bulls, 2 CowsGuess: helloMalformed guess. Keep to valid scalars.Try again: 1123Malformed guess. Remember: 4 digits Between 1 and 9 inclusive No repeated digitsTry again: 34567Malformed guess. Remember: 4 digits Between 1 and 9 inclusive No repeated digitsTry again: 4368You win! Bully for you! Only 8 guesses.
numCount = 4 -- number of digits to usedigits = #(1, 2, 3, 4, 5, 6, 7, 8, 9)num = ""while num.count < numCount and digits.count > 0 do(local r = random 1 digits.countappend num (digits[r] as string)deleteitem digits r)digits = undefinednumGuesses = 0inf = "Rules: \n1. Choose only % unique digits in any combination"+\" (0 can't be used).\n2. Only positive integers are allowed."+\"\n3. For each digit that is in it's place, you get a bull,\n"+\"\tand for each digit that is not in it's place, you get a cow."+\"\n4. The game is won when your number matches the number I chose."+\"\n\nPress [esc] to quit the game.\n\n"clearlistener()format inf num.countwhile not keyboard.escpressed do(local userVal = getkbvalue prompt:"\nEnter your number: "if (userVal as string) == num do(format "\nCorrect! The number is %. It took you % moves.\n" num numGuessesexit with OK)local bulls = 0local cows = 0local badInput = falsecase of((classof userVal != integer): (format "\nThe number must be a positive integer.\n"badInput = true)((userVal as string).count != num.count): (format "\nThe number must have % digits.\n" num.countbadInput = true)((makeuniquearray (for i in 1 to (userVal as string).count \collect (userVal as string)[i])).count != (userVal as string).count):(format "\nThe number can only have unique digits.\n"badInput = true))if not badInput do(userVal = userVal as stringi = 1while i <= userVal.count do(for j = 1 to num.count do(if userVal[i] == num[j] do(if i == j then bulls += 1 else cows += 1))i += 1)numGuesses += 1format "\nBulls: % Cows: %\n" bulls cows))
OKRules: 1. Choose only 4 unique digits in any combination (0 can't be used).2. Only positive integers are allowed.3. For each digit that is in it's place, you get a bull,and for each digit that is not in it's place, you get a cow.4. The game is won when your number matches the number I chose.Press [esc] to quit the game.OKEnter your number: 2468Bulls: 0 Cows: 2Enter your number: 2448The number can only have unique digits.Enter your number: 1357Bulls: 0 Cows: 1
secret=range(1,9)secret.shufflesecret=secret[:4].join("")whiletrueguess=input("Your guess? ").split("")ifguess.len!=4thenprint"Please enter 4 numbers, with no spaces."continueendifbulls=0cows=0foriinguess.indexesifsecret[i]==guess[i]thenbulls=bulls+1elseifsecret.indexOf(guess[i])!=nullthencows=cows+1endifendforifbulls==4thenprint"You got it! Great job!"breakendifprint"You score "+bulls+" bull"+"s"*(bulls!=1)+" and "+cows+" cow"+"s"*(cows!=1)+"."endwhile
Your guess? 2385You score 0 bulls and 2 cows.Your guess? 2323You score 0 bulls and 2 cows.Your guess? 2211You score 2 bulls and 1 cow....Your guess? 8542You score 3 bulls and 0 cows.Your guess? 8642You got it! Great job!
BullCowNew bull,cow,guess,guessed,ii,number,pos,xSet number="",x=1234567890For ii=1:1:4 Do. Set pos=$Random($Length(x))+1. Set number=number_$Extract(x,pos). Set $Extract(x,pos)="". QuitWrite !,"The computer has selected a number that consists"Write !,"of four different digits."Write !!,"As you are guessing the number, ""bulls"" and ""cows"""Write !,"will be awarded: a ""bull"" for each digit that is"Write !,"placed in the correct position, and a ""cow"" for each"Write !,"digit that occurs in the number, but in a different place.",!Write !,"For a guess, enter 4 digits."Write !,"Any other input is interpreted as ""I give up"".",!Set guessed=0 For Do Quit:guessed. Write !,"Your guess: " Read guess If guess'?4n Set guessed=-1 Quit. Set (bull,cow)=0,x=guess. For ii=4:-1:1 If $Extract(x,ii)=$Extract(number,ii) Do. . Set bull=bull+1,$Extract(x,ii)="". . Quit. For ii=1:1:$Length(x) Set:number[$Extract(x,ii) cow=cow+1. Write !,"You guessed ",guess,". That earns you ". If 'bull,'cow Write "neither bulls nor cows..." Quit. If bull Write bull," bull" Write:bull>1 "s". If cow Write:bull " and " Write cow," cow" Write:cow>1 "s". Write ".". If bull=4 Set guessed=1 Write !,"That's a perfect score.". QuitIf guessed<0 Write !!,"The number was ",number,".",!QuitDo BullCow The computer has selected a number that consistsof four different digits. As you are guessing the number, "bulls" and "cows"will be awarded: a "bull" for each digit that isplaced in the correct position, and a "cow" for eachdigit that occurs in the number, but in a different place. For a guess, enter 4 digits.Any other input is interpreted as "I give up". Your guess: 1234You guessed 1234. That earns you 1 cow.Your guess: 5678You guessed 5678. That earns you 1 cow.Your guess: 9815You guessed 9815. That earns you 1 cow.Your guess: 9824You guessed 9824. That earns you 2 cows.Your guess: 9037You guessed 9037. That earns you 1 bull and 2 cows.Your guess: 9048You guessed 2789. That earns you 1 bull and 2 cows.Your guess: 2079You guessed 2079. That earns you 1 bull and 3 cows.Your guess: 2709You guessed 2709. That earns you 2 bulls and 2 cows.Your guess: 0729You guessed 0729. That earns you 4 cows.Your guess: 2907You guessed 2907. That earns you 4 bulls.That's a perfect score.
import Nanoquery.Util; random = new(Random)// a function to verify the user's inputdef verify_digits(input)global sizeseen = ""if len(input) != sizereturn falseelsefor char in inputif not char in "0123456789"return falseelse if char in seenreturn falseendseen += charendendreturn trueendsize = 4chosen = ""while len(chosen) < sizedigit = random.getInt(8) + 1if not str(digit) in chosenchosen += str(digit)endendprintln "I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order."println "You need to input a 4 digit, unique digit number as a guess at what I have chosen."guesses = 1won = falsewhile !wonprint "\nNext guess [" + str(guesses) + "]: "guess = input()if !verify_digits(guess)println "Problem, try again. You need to enter 4 unique digits from 1 to 9"elseif guess = chosenwon = trueelsebulls = 0cows = 0for i in range(0, size - 1)if guess[i] = chosen[i]bulls += 1else if guess[i] in chosencows += 1endendprintln format(" %d Bulls\n %d Cows", bulls, cows)guesses += 1endendendprintln "\nCongratulations you guess correctly in " + guesses + " attempts"
I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order.You need to input a 4 digit, unique digit number as a guess at what I have chosen.Next guess [1]: 1234 1 Bulls 2 CowsNext guess [2]: 1324 0 Bulls 3 Cows...Next guess [10]: 2534 2 Bulls 2 CowsNext guess [11]: 4532Congratulations you guess correctly in 11 attempts
importrandom,strutils,strformat,sequtilsrandomize()constDigits="123456789"DigitSet={Digits[0]..Digits[^1]}Size=4procsample(s:string;n:Positive):string=## Return a random sample of "n" characters extracted from string "s".vars=ss.shuffle()result=s[0..<n]procplural(n:int):string=ifn>1:"s"else:""letchosen=Digits.sample(Size)echo&"I have chosen a number from {Size} unique digits from 1 to 9 arranged in a random order."echo&"You need to input a {Size} digit, unique digit number as a guess at what I have chosen."varguesses=0whiletrue:incguessesvarguess=""whiletrue:stdout.write(&"\nNext guess {guesses}: ")guess=stdin.readLine().strip()ifguess.len==SizeandallCharsInSet(guess,DigitSet)andguess.deduplicate.len==Size:breakecho&"Problem, try again. You need to enter {Size} unique digits from 1 to 9."ifguess==chosen:echo&"\nCongratulations! You guessed correctly in {guesses} attempts."breakvarbulls,cows=0foriin0..<Size:ifguess[i]==chosen[i]:incbullselifguess[i]inchosen:inccowsecho&" {bulls} Bull{plural(bulls)}\n {cows} Cow{plural(cows)}"
Sample output:
I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order.You need to input a 4 digit, unique digit number as a guess at what I have chosen.Next guess 1: 1234 2 Bulls 0 CowNext guess 2: 1256 1 Bull 0 CowNext guess 3: 2378 1 Bull 3 CowsNext guess 4: 7238Congratulations! You guessed correctly in 4 attempts.
letrecinput()=lets=read_line()intryifString.lengths<>4thenraiseExit;String.iter(function|'1'..'9'->()|_->raiseExit)s;lett=[s.[0];s.[1];s.[2];s.[3]]inlet_=List.fold_left(* reject entry with duplication *)(funacb->ifList.membacthenraiseExit;(b::ac))[]tinList.map(func->int_of_string(String.make1c))twithExit->prerr_endline"That is an invalid entry. Please try again.";input();;letprint_scoregt=letbull=ref0inList.iter2(funxy->ifx=ythenincrbull)gt;letcow=ref0inList.iter(funx->ifList.memxtthenincrcow)g;cow:=!cow-!bull;Printf.printf"%d bulls, %d cows\n%!"!bull!cow;;let()=Random.self_init();letrecmkgoalacc=function4->acc|i->letn=succ(Random.int9)inifList.memnaccthenmkgoalaccielsemkgoal(n::acc)(succi)inletg=mkgoal[]0inletfound=reffalseinwhilenot!founddolett=input()inift=gthenfound:=trueelseprint_scoregtdone;print_endline"Congratulations you guessed correctly";;;
: bullsAndCows| numbers guess digits bulls cows | ListBuffer new ->numbers while(numbers size 4 <>) [ 9 rand dup numbers include ifFalse: [ numbers add ] else: [ drop ] ] while(true) [ "Enter a number of 4 different digits between 1 and 9 : " print System.Console askln ->digits digits asInteger isNull digits size 4 <> or ifTrue: [ "Number of four digits needed" println continue ] digits map(#asDigit) ->guess guess numbers zipWith(#==) occurrences(true) ->bulls bulls 4 == ifTrue: [ "You won !" println return ] guess filter(#[numbers include]) size bulls - ->cows System.Out "Bulls = " << bulls << ", cows = " << cows << cr ] ;
The solution atRexx Version 2 is a valid ooRexx program.
declare proc {Main} Solution = {PickNUnique 4 {List.number 1 9 1}} proc {Loop} Guess = {EnterGuess} in {System.showInfo {Bulls Guess Solution}#" bulls and "# {Cows Guess Solution}#" cows"} if Guess \= Solution then {Loop} end end in {Loop} {System.showInfo "You have won!"} end fun {Bulls Xs Sol} {Length {Filter {List.zip Xs Sol Value.'=='} Id}} end fun {Cows Xs Sol} {Length {Intersection Xs Sol}} end local class TextFile from Open.file Open.text end StdIn = {New TextFile init(name:stdin)} in fun {EnterGuess} try {System.printInfo "Enter your guess (e.g. \"1234\"): "} S = {StdIn getS($)} in %% verify {Length S} = 4 {All S Char.isDigit} = true {FD.distinct S} %% assert there is no duplicate digit %% convert from digits to numbers {Map S fun {$ D} D-&0 end} catch _ then {EnterGuess} end end end fun {PickNUnique N Xs} {FoldL {MakeList N} fun {$ Z _} {Pick {Diff Xs Z}}|Z end nil} end fun {Pick Xs} {Nth Xs {OS.rand} mod {Length Xs} + 1} end fun {Diff Xs Ys} {FoldL Ys List.subtract Xs} end fun {Intersection Xs Ys} {Filter Xs fun {$ X} {Member X Ys} end} end fun {Id X} X endin {Main}
This simple implementation expects guesses in the form [a,b,c,d].
bc()={ my(u,v,bulls,cows); while(#vecsort(v=vector(4,i,random(9)+1),,8)<4,); while(bulls<4, u=input(); if(type(u)!="t_VEC"|#u!=4,next); bulls=sum(i=1,4,u[i]==v[i]); cows=sum(i=1,4,sum(j=1,4,i!=j&v[i]==u[j])); print("You have "bulls" bulls and "cows" cows") )};
ProgramBullCow;{$mode objFPC}usesMath,SysUtils;typeTFourDigit=array[1..4]ofinteger;ProcedureWriteFourDigit(fd:TFourDigit);{ Write out a TFourDigit with no line break following. }vari:integer;beginfori:=1to4dobeginWrite(fd[i]);end;end;FunctionWellFormed(Tentative:TFourDigit):Boolean;{ Does the TFourDigit avoid repeating digits? }varcurrent,check:integer;beginResult:=True;forcurrent:=1to4dobeginforcheck:=current+1to4dobeginifTentative[check]=Tentative[current]thenbeginResult:=False;end;end;end;end;FunctionMakeNumber():TFourDigit;{ Make a random TFourDigit, keeping trying until it is well-formed. }vari:integer;beginfori:=1to4dobeginResult[i]:=RandomRange(1,9);end;ifnotWellFormed(Result)thenbeginResult:=MakeNumber();end;end;FunctionStrToFourDigit(s:string):TFourDigit;{ Convert an (input) string to a TFourDigit. }vari:integer;beginfori:=1toLength(s)dobeginStrToFourDigit[i]:=StrToInt(s[i]);end;end;FunctionWins(Num,Guess:TFourDigit):Boolean;{ Does the guess win? }vari:integer;beginResult:=True;fori:=1to4dobeginifNum[i]<>Guess[i]thenbeginResult:=False;Exit;end;end;end;FunctionGuessScore(Num,Guess:TFourDigit):string;{ Represent the score of the current guess as a string. }vari,j,bulls,cows:integer;beginbulls:=0;cows:=0;{ Count the cows and bulls. }fori:=1to4dobeginforj:=1to4dobeginif(Num[i]=Guess[j])thenbegin{ If the indices are the same, that would be a bull. }if(i=j)thenbeginbulls:=bulls+1;endelsebegincows:=cows+1;end;end;end;end;{ Format the result as a sentence. }Result:=IntToStr(bulls)+' bulls, '+IntToStr(cows)+' cows.';end;FunctionGetGuess():TFourDigit;{ Get a well-formed user-supplied TFourDigit guess. }varinput:string;beginWriteLn('Enter a guess:');ReadLn(input);{ Must be 4 digits. }ifLength(input)=4thenbeginResult:=StrToFourDigit(input);ifnotWellFormed(Result)thenbeginWriteLn('Four unique digits, please.');Result:=GetGuess();end;endelsebeginWriteLn('Please guess a four-digit number.');Result:=GetGuess();end;end;varNum,Guess:TFourDigit;Turns:integer;begin{ Initialize the randymnity. }Randomize();{ Make the secred number. }Num:=MakeNumber();WriteLn('I have a secret number. Guess it!');Turns:=0;{ Guess until the user gets it. }WhileTruedobeginGuess:=GetGuess();{ Count each guess as a turn. }Turns:=Turns+1;{ If the user won, tell them and ditch. }ifWins(Num,Guess)thenbeginWriteLn('You won in '+IntToStr(Turns)+' tries.');Write('The number was ');WriteFourDigit(Num);WriteLn('!');Exit;endelse{ Otherwise, score it and get a new guess. }beginWriteLn(GuessScore(Num,Guess));end;end;end.
useData::Randomqw(rand_set);useList::MoreUtilsqw(uniq);my$size=4;my$chosen=join"",rand_setset=>["1".."9"],size=>$size;print"I've chosen a number from $size unique digits from 1 to 9; you needto input $size unique digits to guess my number\n";for(my$guesses=1;;$guesses++){my$guess;while(1){print"\nNext guess [$guesses]: ";$guess=<STDIN>;chomp$guess;checkguess($guess)andlast;print"$size digits, no repetition, no 0... retry\n";}if($guesseq$chosen){print"You did it in $guesses attempts!\n";last;}my$bulls=0;my$cows=0;formy$i(0..$size-1){if(substr($guess,$i,1)eqsubstr($chosen,$i,1)){$bulls++;}elsif(index($chosen,substr($guess,$i,1))>=0){$cows++;}}print"$cows cows, $bulls bulls\n";}subcheckguess{my$g=shift;returnuniq(split//,$g)==$size&&$g=~ /^[1-9]{$size}$/;}
---- demo\rosetta\BullsAndCows.exw-- =============================--withjavascript_semantics-- (DEV lots of resizing issues)constantN=4functionmask(integerch)returnpower(2,ch-'1')endfunctionfunctionscore(stringguess,goal)integerbits=0,bulls=0,cows=0,bfori=1toNdob=goal[i]ifguess[i]=bthenbulls+=1elsebits+=mask(b)endifendforfori=1toNdob=mask(guess[i])ifand_bits(bits,b)!=0thencows+=1bits-=bendifendforreturn{bulls,cows}endfunctionincludepGUI.eIhandlelabel,guess,res,dlgstringfmt=" Guess %-2d (%s) bulls:%d cows:%d\n",tgt=shuffle("123456789")[1..N]integerattempt=1functionvaluechanged_cb(Ihandle/*guess*/)stringg=IupGetAttribute(guess,"VALUE")iflength(g)=4andlength(unique(g))=4theninteger{bulls,cows}=score(g,tgt)stringtitle=IupGetAttribute(res,"TITLE")&sprintf(fmt,{attempt,g,bulls,cows})ifbulls=Nthentitle&="\nWell done!"IupSetInt(guess,"ACTIVE",false)elseIupSetAttribute(guess,"VALUE","")endifIupSetStrAttribute(res,"TITLE",title)attempt+=1IupSetAttribute(dlg,"SIZE",NULL)IupRefresh(dlg)endifreturnIUP_DEFAULTendfunctionproceduremain()IupOpen()label=IupLabel(sprintf("Enter %d digits 1 to 9 without duplication",{N}))guess=IupText("VALUECHANGED_CB",Icallback("valuechanged_cb"))res=IupLabel("")dlg=IupDialog(IupVbox({IupHbox({label,guess},"GAP=10,NORMALIZESIZE=VERTICAL"),IupHbox({res})},"MARGIN=5x5"),`TITLE="Bulls and Cows"`)IupShow(dlg)ifplatform()!=JSthenIupMainLoop()IupClose()endifendproceduremain()
(as shown in the res label)
Guess 1 (5739) bulls:0 cows:3 Guess 2 (7193) bulls:2 cows:1 Guess 3 (3495) bulls:0 cows:2 Guess 4 (7983) bulls:3 cows:0 Guess 5 (7963) bulls:3 cows:0 Guess 6 (7923) bulls:4 cows:0Well done!
<?php$size=4;$chosen=implode(array_rand(array_flip(range(1,9)),$size));echo"I've chosen a number from$size unique digits from 1 to 9; you needto input$size unique digits to guess my number\n";for($guesses=1;;$guesses++){while(true){echo"\nNext guess [$guesses]: ";$guess=rtrim(fgets(STDIN));if(!checkguess($guess))echo"$size digits, no repetition, no 0... retry\n";elsebreak;}if($guess==$chosen){echo"You did it in$guesses attempts!\n";break;}else{$bulls=0;$cows=0;foreach(range(0,$size-1)as$i){if($guess[$i]==$chosen[$i])$bulls++;elseif(strpos($chosen,$guess[$i])!==FALSE)$cows++;}echo"$cows cows,$bulls bulls\n";}}functioncheckguess($g){global$size;returncount(array_unique(str_split($g)))==$size&&preg_match("/^[1-9]{{$size}}$/",$g);}?>
main => Digits = to_array("123456789"), Size = 4, random_sample(Size,Size,[],ChosenIndecies), Chosen = {Digits[I] : I in ChosenIndecies}, printf("I have chosen a number from %d unique digits from 1 to 9 arranged in a random order.\n", Size), printf("You need to input a %d digit, unique digit number as a guess at what I have chosen.\n", Size), guess(Chosen,Size,1).guess(Chosen,Size,NGuess) => Input = read_line(), Guess = Input.to_array(), if len(Guess) != Size || len(sort_remove_dups(Input)) != Size || (member(D, Input), (D @< '1' || D @> '9')) then printf("Problem, try again. You need to enter %d unique digits from 1 to 9\n", Size), guess(Chosen,Size,NGuess) elseif Guess == Chosen then printf("\nCongratulations you guessed correctly in %d attempts\n", NGuess) else Bulls = sum([cond(Chosen[I] == Guess[I], 1, 0) : I in 1..Size]), Cows = sum([cond(member(Chosen[I], Input), 1, 0) : I in 1..Size]), printf("%d Bulls\n%d Cows\n", Bulls, Cows), guess(Chosen, Size, NGuess+1) end.random_sample(_N,0,Chosen0,Chosen) => Chosen = Chosen0.random_sample(N,I,Chosen0,Chosen) => R = random() mod N + 1, (not member(R, Chosen0) -> random_sample(N,I-1,[R|Chosen0],Chosen) ; random_sample(N,I,Chosen0,Chosen) ).
(deok?(N)(letD(mapcar'format(chopN))(and(num?N)(not(member0D))(=4(lengthD))(=D(uniqD))D)))(deinit-cows()(until(setq*Hidden(ok?(rand12349876)))))(deguess(N)(letD(ok?N)(ifD(letBulls(cnt'=D*Hidden)(if(=4Bulls)" You guessed it!"(letCows(-(cnt'((N)(memberN*Hidden))D)Bulls)(packBulls" bulls, "Cows" cows"))))" Bad guess! (4 unique digits, 1-9)")))
[int]$guesses=$bulls=$cows=0[string]$guess="none"[string]$digits=""while($digits.Length-lt4){$character=[char](49..57|Get-Random)if($digits.IndexOf($character)-eq-1){$digits+=$character}}Write-Host"`nGuess four digits (1-9) using no digit twice.`n"-ForegroundColorCyanwhile($bulls-lt4){do{$prompt="Guesses={0:0#}, Last='{1,4}', Bulls={2}, Cows={3}; Enter your guess"-f$guesses,$guess,$bulls,$cows$guess=Read-Host$promptif($guess.Length-ne4){Write-Host"`nMust be a four-digit number`n"-ForegroundColorRed}if($guess-notmatch"[1-9][1-9][1-9][1-9]"){Write-Host"`nMust be numbers 1-9`n"-ForegroundColorRed}}until($guess.Length-eq4)$guesses+=1$bulls=$cows=0for($i=0;$i-lt4;$i++){$character=$digits.Substring($i,1)if($guess.Substring($i,1)-eq$character){$bulls+=1}else{if($guess.IndexOf($character)-ge0){$cows+=1}}}}Write-Host"`nYou won after$($guesses-1) guesses."-ForegroundColorCyan
Guess four digits (1-9) using no digit twice.Guesses=00, Last='none', Bulls=0, Cows=0; Enter your guess: 1234Guesses=01, Last='1234', Bulls=0, Cows=3; Enter your guess: 2345Guesses=02, Last='2345', Bulls=1, Cows=2; Enter your guess: 2346Guesses=03, Last='2346', Bulls=1, Cows=1; Enter your guess: 2341Guesses=04, Last='2341', Bulls=1, Cows=2; Enter your guess: 3241Guesses=05, Last='3241', Bulls=0, Cows=3; Enter your guess: 4321Guesses=06, Last='4321', Bulls=1, Cows=2; Enter your guess: 5321Guesses=07, Last='5321', Bulls=2, Cows=2; Enter your guess: 5312You won after 7 guesses.
Produces both a console transcript and a GUI interface to the game.Creates a new game each time the guess is correct; tracks number of games won.
IntDict score;StringList choices;StringList guess;StringList secret;int gamesWon = -1;void setup() { choices = new StringList("0", "1", "2", "3", "4", "5", "6", "7", "8", "9"); newGame();}void newGame() { gamesWon++; choices.shuffle(); secret = new StringList(); for (int i=0; i<4; i++) { // selections secret.append(choices.get(i)); } newGuess(); println("\nsecret:", secret, "\n");}void newGuess() { guess = new StringList(); score = null;}void draw() { background(0); text("Bulls & Cows " + gamesWon, 5, 20); for (int i=0; i<guess.size(); i++) { text(guess.get(i), 20*i+10, height/2); } if (score!=null) { text("bulls:" + score.get("bulls") + " cows:" + score.get("cows"), 10, height-20); }}void keyReleased() { if (score!=null && score.get("bulls")==4) newGame(); if (guess.size()==secret.size()) newGuess(); if (guess.hasValue(str(key))) newGuess(); if (key>=48 && key<=57) guess.append(str(key)); if (guess.size()==secret.size()) { score = checkScore(secret, guess); println("guess: ", guess, "\n", score, "wins:", gamesWon); }}IntDict checkScore(StringList secret, StringList guess) { IntDict result = new IntDict(); result.set("bulls", 0); result.set("cows", 0); for (int i=0; i<guess.size(); i++) { if (guess.get(i).equals(secret.get(i))) { result.add("bulls", 1); } else if (secret.hasValue(guess.get(i))) { result.add("cows", 1); } } return result;}
Works with SWI-Prolog 6.1.8 (for predicatefoldl), module lambda, written byUlrich Neumerkel found therehttp://www.complang.tuwien.ac.at/ulrich/Prolog-inedit/lambda.pl and module clpfd written byMarkus Triska.
:-use_module(library(lambda)).:-use_module(library(clpfd)).% Parameters of the server% length of the guessproposition(4).% Numbers of digits% 0 -> 8digits(8).bulls_and_cows_server:-proposition(LenGuess),length(Solution,LenGuess),choose(Solution),repeat,write('Your guess : '),read(Guess),(study(Solution,Guess,Bulls,Cows)->format('Bulls : ~w Cows : ~w~n',[Bulls,Cows]),Bulls=LenGuess;digits(Digits),MaxisDigits+1,format('Guess must be of ~w digits between 1 and ~w~n',[LenGuess,Max]),fail).choose(Solution):-digits(Digits),MaxisDigits+1,repeat,maplist(\X^(Xisrandom(Max)+1),Solution),all_distinct(Solution),!.study(Solution,Guess,Bulls,Cows):-proposition(LenGuess),digits(Digits),% compute the transformation 1234 => [1,2,3,4]atom_chars(Guess,Chars),maplist(\X^Y^(atom_number(X,Y)),Chars,Ms),% check that the guess is well formedlength(Ms,LenGuess),maplist(\X^(X>0,X=<Digits+1),Ms),% compute the digit in good placefoldl(\X^Y^V0^V1^((X=Y->V1isV0+1;V1=V0)),Solution,Ms,0,Bulls),% compute the digits in bad placefoldl(\Y1^V2^V3^(foldl(\X2^Z2^Z3^(X2=Y1->Z3isZ2+1;Z3=Z2),Ms,0,TT1),V3isV2+TT1),Solution,0,TT),CowsisTT-Bulls.
Define.ssecret,guess,cDefine.ibulls,cows,guesses,iIfOpenConsole()WhileLen(secret)<4c=Chr(Random(8)+49)IfFindString(secret,c,1)=0secret+cEndIfWendRepeatPrint("Guess a 4-digit number with no duplicate digits: ")guess=Input()IfLen(guess)=0Break;breakfromloopEndIfisMalformedGuess=#FalseIfLen(guess)<>4;guessistooshortisMalformedGuess=#TrueElseFori=1To4c=Mid(guess,i,1)IfNotFindString("123456789",c,1)OrCountString(guess,c)<>1;guesscontainseithernon-digitsorduplicatedigitsisMalformedGuess=#TrueBreak;breakfromFor/NextloopEndIfNextEndIfIfisMalformedGuessPrintN("** You should enter 4 different numeric digits that are each from 1 to 9!")Continue;continueloopEndIfbulls=0:cows=0:guesses=guesses+1Fori=1To4c=Mid(secret,i,1)IfMid(guess,i,1)=cbulls+1ElseIfFindString(guess,c,1)cows+1EndIfNextPrint(Str(bulls)+" bull")Ifbulls<>1Print("s")EndIfPrint(", "+Str(cows)+" cow")Ifcows<>1PrintN("s")ElsePrintN("")EndIfIfguess=secretPrintN("You won after "+Str(guesses)+" guesses!")Break;breakfromloopEndIfForEverPrint(#CRLF$+#CRLF$+"Press ENTER to exit")Input()CloseConsole()EndIf
''' Bulls and cows. A game pre-dating, and similar to, Mastermind.'''importrandomdigits='123456789'size=4chosen=''.join(random.sample(digits,size))#print chosen # Debugprint'''I have chosen a number from%s unique digits from 1 to 9 arranged in a random order.You need to input a%i digit, unique digit number as a guess at what I have chosen'''%(size,size)guesses=0whileTrue:guesses+=1whileTrue:# get a good guessguess=raw_input('\nNext guess [%i]: '%guesses).strip()iflen(guess)==sizeand \all(charindigitsforcharinguess) \andlen(set(guess))==size:breakprint"Problem, try again. You need to enter%i unique digits from 1 to 9"%sizeifguess==chosen:print'\nCongratulations you guessed correctly in',guesses,'attempts'breakbulls=cows=0foriinrange(size):ifguess[i]==chosen[i]:bulls+=1elifguess[i]inchosen:cows+=1print'%i Bulls\n%i Cows'%(bulls,cows)
Sample output:
I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order.You need to input a 4 digit, unique digit number as a guess at what I have chosenNext guess [1]: 79Problem, try again. You need to enter 4 unique digits from 1 to 9Next guess [1]: 7983 2 Bulls 2 CowsNext guess [2]: 7938Congratulations you guessed correctly in 2 attempts
Const MaxDigit = 4, Min = 1, Max = 9Dim As String NumberToGuess, NumberToTest, Newdigit, ResultDim As Integer Counter, NumberRandomize TimerDo Counter = Counter + 1 Newdigit = _Trim$(Str$(Int(Rnd * Max) + Min)) If InStr(NumberToGuess, Newdigit) = 0 Then NumberToGuess = NumberToGuess + Newdigit Else Counter = Counter - 1Loop While Counter < MaxDigitPrint NumberToGuess 'debug outputDo While NumberToGuess <> NumberToTest Input "Please enter your guess of 4 digits... ", Number NumberToTest = _Trim$(Str$(Number)) If NumberToGuess <> NumberToTest Then Result = "" For Counter = 1 To 4 Step 1 Newdigit = Mid$(NumberToTest, Counter, 1) If InStr(NumberToGuess, Newdigit) - Counter = 0 Then Result = Result + " Bull " ElseIf InStr(NumberToGuess, Newdigit) > 0 Then Result = Result + " Cow " End If Next Counter Print NumberToTest, Result Else Print "You Win!" End IfLoop
transpose
is defined atMatrix transposition#Quackery.
[ size 4 = dup not if [ say "Must be four digits." cr ] ] is 4chars ( $ --> b ) [ true swap witheach [ char 1 char 9 1+ within not if [ say "Must be 1-9 only." cr not conclude ] ] ] is 1-9 ( $ --> b ) [ 0 9 of swap witheach [ 1 unrot char 1 - poke ] 0 swap witheach + 4 = dup not if [ say "Must all be different." cr ] ] is all-diff ( $ --> b ) [ $ "Guess four digits, 1-9, no duplicates: " input dup 4chars not iff drop again dup 1-9 not iff drop again dup all-diff not iff drop again ] is guess ( $ --> $ ) [ $ "123456789" shuffle 4 split drop ] is rand$ ( --> $ ) [ 2 pack transpose [] swap witheach [ dup unpack != iff [ nested join ] else drop ] dup [] != if [ transpose unpack ] 4 over size - ] is -bulls ( $ $ --> $ $ n ) [ join sort 0 swap behead swap witheach [ tuck = if [ dip 1+ ] ] drop ] is cows ( $ $ --> n ) [ say "Guess the four numbers." cr cr say "They are all different and" say " between 1 and 9 inclusive." cr cr randomise rand$ [ guess over -bulls dup 4 = iff say "Correct." done dup echo 1 = iff [ say " bull." cr ] else [ say " bulls." cr ] cows dup echo 1 = iff [ say " cow." cr ] else [ say " cows." cr ] again ] cr drop 2drop ] is play ( --> )
Guess the four numbers.They are all different and between 1 and 9 inclusive.Guess four digits, 1-9, no duplicates: 12340 bulls.0 cows.Guess four digits, 1-9, no duplicates: 56781 bull.3 cows.Guess four digits, 1-9, no duplicates: 57861 bull.3 cows.Guess four digits, 1-9, no duplicates: 58670 bulls.4 cows.Guess four digits, 1-9, no duplicates: 76582 bulls.2 cows.Guess four digits, 1-9, no duplicates: 76850 bulls.4 cows.Guess four digits, 1-9, no duplicates: 6758Correct.
target<-sample(1:9,4)bulls<-0cows<-0attempts<-0while(bulls!=4){input<-readline("Guess a 4-digit number with no duplicate digits or 0s: ")if(nchar(input)==4){input<-as.integer(strsplit(input,"")[[1]])if((sum(is.na(input)+sum(input==0))>=1)|(length(table(input))!=4)){print("Malformed input!")}else{bulls<-sum(input==target)cows<-sum(input%in%target)-bullscat("\n",bulls," Bull(s) and ",cows," Cow(s)\n")attempts<-attempts+1}}else{print("Malformed input!")}}print(paste("You won in",attempts,"attempt(s)!"))
#langracket; secret : (listof exact-nonnegative-integer?)(definesecret(foldr(λ(nresult)(consn(map(λ(y)(if(>=yn)(add1y)y))result)))'()(maprandom'(10987)))); (count-bulls/cows guess) -> (values exact-nonnegative-integer?; exact-nonnegative-integer?); guess : (listof exact-nonnegative-integer?)(define(count-bulls/cowsguess)(let*([bulls(map=guesssecret)][cow-candidates(filter-map(λ(xy)(if(false?x)y#f))bullssecret)][cows(filter(curryrmembercow-candidates)guess)])(values(length(filter((curryequal?)#t)bulls))(lengthcows)))); (valid-guess guess-str) -> (or/c (listof exact-nonnegative-integer?) #f); guess-str : string?(define(valid-guessguess-str)(define(char->digitc)(-(char->integerc)(char->integer#\0)))(if(regexp-match-exact?#px"[0-9]{4}"guess-str)(let([guess(mapchar->digit(string->listguess-str))])(if(andmap(λ(x)(equal?(count((curryequal?)x)guess)1))guess)guess#f))#f)); Game states(definewin#t)(definegame#f); (main-loop state step) -> void?; state : boolean?; step : exact-nonnegative-integer?(define(main-loopstatestep)(if(equal?statewin)(printf"You won after ~a guesses."step)(begin(let*([guess-str(read-line)][guess(valid-guessguess-str)])(if(false?guess)(begin(displayln"Guess should include exactly four different digits")(main-loopstatestep))(let-values([(bullscows)(count-bulls/cowsguess)])(if(=bulls4)(main-loopwin(add1step))(begin(printf"Bulls: ~a Cows: ~a\n"bullscows)(main-loopstate(add1step))))))))))(main-loopgame0)
Output:
1234Bulls: 0 Cows: 121345Guess should include exactly four different digits2134Bulls: 1 Cows: 02314Bulls: 0 Cows: 15167Bulls: 1 Cows: 15189Bulls: 1 Cows: 20189Bulls: 1 Cows: 28179Bulls: 1 Cows: 37198You won after 8 guesses.
(formerly Perl 6)
my$size =4;my@secret =pick$size,'1' ..'9';for1..* ->$guesses {my@guess;loop {@guess = (prompt("Guess $guesses: ") //exit).comb;lastif@guess ==$sizeandall(@guess)eqone(@guess) &any('1' ..'9');say'Malformed guess; try again.'; }my ($bulls,$cows) =0,0;for ^$size {when@guess[$_]eq@secret[$_] { ++$bulls; }when@guess[$_]eqany@secret { ++$cows; } }lastif$bulls ==$size;say"$bulls bulls, $cows cows.";}say'A winner is you!';
Red[]a:"0123456789"bulls:0random/seednow/timenumber:copy/partrandoma4while[bulls<>4][bulls:0cows:0guess:ask"make a guess: "repeati4[if(pickguess i)=(picknumber i)[bulls:bulls+1]]cows:(length?intersectguess number)-bullsprint["bulls: "bulls" cows: "cows]]print"You won!"
This game is also known as:
See version 2 for a better formatted progtam that also runs on ooRexx.
This REXX version of Bulls and Cows doesn't allow repeated digits (in the computer-generated number),
nor the use of the zero digit.
To allow a zero digit, change the 1 on the 2nd REXX statement for the random BIF invocation.
To allow repeated digits in the computer-generated number, delete the 3rd REXX statement if pos(r, ?)···,
and also change the prompt message.
The REXX statement that contains the translate statement can be removed if repeated digits aren't allowed.
/*REXX program scores the Bulls & Cows game with CBLFs (Carbon Based Life Forms). */?=;dountillength(?)==4;r=random(1,9)/*generate a unique four-digit number. */ifpos(r,?)\==0theniterate;?=?||r/*don't allow a repeated digit/numeral. */end/*until length*//* [↑] builds a unique four-digit number*/$='──────── [Bulls & Cows] '/*a literal that is part of the prompt. */dountilbulls==4;say/*play until guessed or enters "Quit".*/say$'Please enter a 4-digit guess (with no zeroes) [or Quit]:'pulln;n=space(n,0);ifabbrev('QUIT',n,1)thenexit/*user wants to quit?*/q=?;L=length(n);bulls=0;cows=0/*initialize some REXX variables. */doj=1forL;ifsubstr(n,j,1)\==substr(q,j,1)theniterate/*is bull?*/bulls=bulls+1;q=overlay(.,q,j)/*bump the bull count; disallow for cow.*/end/*j*//* [↑] bull count───────────────────────*//*is cow? */dok=1forL;_=substr(n,k,1);ifpos(_,q)==0theniteratecows=cows+1;q=translate(q,,_)/*bump the cow count; allow mult digits.*/end/*k*//* [↑] cow count───────────────────────*/say;@='You got'bullsifL\==0&bulls\==4thensay$@'bull's(bulls)"and"cows'cow's(cows).end/*until bulls*/say" ┌─────────────────────────────────────────┐"say" │ │"say" │ Congratulations, you've guessed it !! │"say" │ │"say" └─────────────────────────────────────────┘"exit/*stick a fork in it, we're all done. *//*──────────────────────────────────────────────────────────────────────────────────────*/s:ifarg(1)==1thenreturn'';return"s"/*this function handles pluralization. */
/*REXX program to play the game of "Bulls & Cows". ******************** Changes from Version 1:* ?= -> qq='' (righthandside mandatory and I never use ? as symbol -* although it is available on all Rexxes)* implemented singular/plural distinction differently* change getRand to avoid invalid digit rejection* check user's input for multiple digits* add feature MM to ease guessing (MM=Mastermind - a similar game)* add feature ? to see the solution (for the impatient player)* program runs as is on ooRexx and on TSO (after changing | to !)* Made source and output more compact* formatted source 'my way' 2 July 2012 Walter Pachl**********************************************************************/ask='<Bulls & Cows game> Please enter a four-digit guess (or QUIT):'b.='bulls';b.1='bull'c.='cows';c.1='cow'qq=getRand()mm=0DoForeverIfget_guess()==qqThenleaveCallscorerSay"You got"bullsb.bulls"and"cowsc.cows"."IfmmThenSaymmsEnd/*forever*/Say" *******************************************"Say" * *"Say" * Congratulations, you've guessed it !! *"Say" * *"Say" *******************************************"Exitget_guess:/*get a guess from the guesser. */doforeverSayaskParsePullguessiguess=translate(guessi)bc=verify(guess,987654321)SelectWhenguess='?'ThenSayqq'is the correct sequence'Whenguess='QUIT'ThenExitWhenguess='MM'ThenDoSay'Mastermind output enabled'mm=1EndWhenguess=''ThenCallser'no argument specified.'Whenwords(guess)>1ThenCallser'too many arguments specified.'Whenverify(0,guess)=0ThenCallser'illegal digit: 0'Whenbc>0ThenCallser'illegal character:'substr(guessi,bc,1)Whenlength(guess)<4ThenCallser'not enough digits'Whenlength(guess)>4ThenCallser'too many digits'Whendups(guess)ThenCallser'4 DIFFERENT digits, please'OtherwiseDo/********** Say guess ************/ReturnguessEndEndEndgetRand:digits='123456789'qq=''Doi=1To4d=random(1,length(digits))d=substr(digits,d,1)qq=qq||ddigits=space(translate(digits,' ',d),0)/************ Say qq digits ************/EndReturnqqscorer:g=qqmms='----'bulls=0Doj=1for4Ifsubstr(guess,j,1)=substr(qq,j,1)ThenDobulls=bulls+1guess=overlay(' ',guess,j)mms=overlay('+',mms,j)EndEndcows=0Doj=1To4Ifpos(substr(guess,j,1),qq)>0ThenDocows=cows+1mms=overlay('.',mms,j)EndEndReturndups:ProcedureParseArgsDoi=1To3Ifpos(substr(s,i,1),substr(s,i+1))>0ThenReturn1EndReturn0ser:Say'*** error ***'arg(1);Return
# Project : Bulls and cowssecret = ""while len(secret) != 4 c = char(48 + random(9)) if substr(secret, c) = 0 secret = secret + c okendsee "guess a four-digit number with no digit used twice."guesses = 0guess = ""while true guess = "" while len(guess) != 4 see "enter your guess: " give guess if len(guess) != 4 see "must be a four-digit number" + nl ok end guesses = guesses + 1 if guess = secret see "you won after " + guesses + " guesses!" exit ok bulls = 0 cows = 0 for i = 1 to 4 c = secret[i] if guess[i] = c bulls = bulls + 1 but substr(guess, c) > 0 cows = cows + 1 ok next see "you got " + bulls + " bull(s) and " + cows + " cow(s)." + nlend
« CLEAR 0 "" 1 4STARTWHILE RAND 9 * CEIL R→I →STR DUP2 POSREPEATDROP END +NEXT → count solution « DO 1 CFDO "Guess? [CONT]" PROMPT →STRCASE DUP SIZE 4 ≠THEN DROP "Not 4 characters" 1 DISP 0.5 WAITEND { 9 } 0 CON 1 4FOR j OVER j DUP SUB STR→IFERR 1 PUTTHEN 3 DROPN "Invalid character" 1 DISP 0.5 WAITENDNEXT DUP 1 CON DOT 4 ≠THEN DROP "Repeated digits" 1 DISP 0.5 WAITEND 1 SFENDUNTIL 1 FS?END " → " + 0 1 4FOR j solution PICK3 j DUP SUB POSIF DUPTHEN IF j ==THEN 1ELSE .1END END +NEXT SWAP OVER + 'count' INCR DROPUNTIL SWAP 4 ==END count "guess" →TAG» » 'BU&CO' ST0
Inspired by Tcl
defgenerate_word(len)[*"1".."9"].shuffle.first(len)# [*"1".."9"].sample(len) ver 1.9+enddefget_guess(len)loopdoprint"Enter a guess: "guess=gets.striperr=casewhenguess.match(/[^1-9]/);"digits only"whenguess.length!=len;"exactly#{len} digits"whenguess.split("").uniq.length!=len;"digits must be unique"elsereturnguess.split("")endputs"the word must be#{len} unique digits between 1 and 9 (#{err}). Try again."endenddefscore(word,guess)bulls=cows=0guess.each_with_indexdo|num,idx|ifword[idx]==numbulls+=1elsifword.include?numcows+=1endend[bulls,cows]endword_length=4puts"I have chosen a number with#{word_length} unique digits from 1 to 9."word=generate_word(word_length)count=0loopdoguess=get_guess(word_length)count+=1breakifword==guessputs"that guess has %d bulls and %d cows"%score(word,guess)endputs"you guessed correctly in#{count} tries."
Inspired by Python
size=4secret=[*'1'..'9'].sample(size)guess=nili=0loopdoi+=1loopdoprint"Guess#{i}: "guess=gets.chomp.charsexitifguess.empty?breakifguess.size==sizeandguess.all?{|x|('1'..'9').include?x}andguess.uniq.size==sizeputs"Problem, try again. You need to enter#{size} unique digits from 1 to 9"endifguess==secretputs"Congratulations you guessed correctly in#{i} attempts"breakendbulls=cows=0size.timesdo|j|ifguess[j]==secret[j]bulls+=1elsifsecret.include?guess[j]cows+=1endendputs"Bulls:#{bulls}; Cows:#{cows}"end
usestd::io;userand::{Rng,thread_rng};externcraterand;constNUMBER_OF_DIGITS:usize=4;staticDIGITS:[char;9]=['1','2','3','4','5','6','7','8','9'];fngenerate_digits()->Vec<char>{letmuttemp_digits:Vec<_>=(&DIGITS[..]).into();thread_rng().shuffle(&muttemp_digits);returntemp_digits.iter().take(NUMBER_OF_DIGITS).map(|&a|a).collect();}fnparse_guess_string(guess:&str)->Result<Vec<char>,String>{letchars:Vec<char>=(&guess).chars().collect();if!chars.iter().all(|c|DIGITS.contains(c)){returnErr("only digits, please".to_string());}ifchars.len()!=NUMBER_OF_DIGITS{returnErr(format!("you need to guess with {} digits",NUMBER_OF_DIGITS));}letmutuniques:Vec<char>=chars.clone();uniques.dedup();ifuniques.len()!=chars.len(){returnErr("no duplicates, please".to_string());}returnOk(chars);}fncalculate_score(given_digits:&[char],guessed_digits:&[char])->(usize,usize){letmutbulls=0;letmutcows=0;foriin0..NUMBER_OF_DIGITS{letpos:Option<usize>=guessed_digits.iter().position(|&a|->bool{a==given_digits[i]});matchpos{None=>(),Some(p)ifp==i=>bulls+=1,Some(_)=>cows+=1}}return(bulls,cows);}fnmain(){letreader=io::stdin();loop{letgiven_digits=generate_digits();println!("I have chosen my {} digits. Please guess what they are",NUMBER_OF_DIGITS);loop{letguess_string:String={letmutbuf=String::new();reader.read_line(&mutbuf).unwrap();buf.trim().into()};letdigits_maybe=parse_guess_string(&guess_string);matchdigits_maybe{Err(msg)=>{println!("{}",msg);continue;},Ok(guess_digits)=>{matchcalculate_score(&given_digits,&guess_digits){(NUMBER_OF_DIGITS,_)=>{println!("you win!");break;},(bulls,cows)=>println!("bulls: {}, cows: {}",bulls,cows)}}}}}}
importscala.util.RandomobjectBullCow{defmain(args:Array[String]):Unit={valnumber=chooseNumbervarguessed=falsevarguesses=0while(!guessed){Console.print("Guess a 4-digit number with no duplicate digits: ")valinput=Console.readIntvaldigits=input.toString.map(_.asDigit).toListif(input>=1111&&input<=9999&&!hasDups(digits)){guesses+=1varbulls,cows=0for(i<-0to3)if(number(i)==digits(i))bulls+=1elseif(number.contains(digits(i)))cows+=1if(bulls==4)guessed=trueelseprintln("%d Cows and %d Bulls.".format(cows,bulls))}}println("You won after "+guesses+" guesses!");}defchooseNumber={vardigits=List[Int]()while(digits.size<4){vald=Random.nextInt(9)+1if(!digits.contains(d))digits=digits:+d}digits}defhasDups(input:List[Int])=input.size!=input.distinct.size}
;generate a random non-repeating list of 4 digits, 1-9 inclusive(define(get-num)(define(genlst)(if(=(lengthlst)4)lst(let((digit(+(random9)1)))(if(memberdigitlst);make sure the new digit isn't in the;list(genlst)(gen(consdigitlst))))))(string->list(applystring-append(mapnumber->string(gen'())))));is g a valid guess (that is, non-repeating, four digits 1-9;inclusive?)(define(valid-guess?g)(let((g-num(string->number(applystringg))));does the same digit appear twice in lst?(define(repeats?lst)(cond((null?lst)#f)((member(carlst)(cdrlst))#t)(else(repeats?(cdrlst)))))(andg-num(>g-num1233)(<g-num9877)(not(repeats?g)))));return '(cows bulls) for the given guess(define(scoreanswerguess);total cows + bulls(define(cows&bullsag)(cond((null?a)0)((member(cara)g)(+1(cows&bulls(cdra)g)))(else(cows&bulls(cdra)g))));bulls only(define(bullsag)(cond((null?a)0)((equal?(cara)(carg))(+1(bulls(cdra)(cdrg))))(else(bulls(cdra)(cdrg)))))(list(-(cows&bullsanswerguess)(bullsanswerguess))(bullsanswerguess)));play the game(define(bull-cowanswer);get the user's guess as a list(define(get-guess)(let((e(read)))(if(number?e)(string->list(number->stringe))(string->list(symbol->stringe)))))(display"Enter a guess: ")(let((guess(get-guess)))(if(valid-guess?guess)(let((bulls(cadr(scoreanswerguess)))(cows(car(scoreanswerguess))))(if(=bulls4)(display"You win!\n")(begin(displaybulls)(display" bulls, ")(displaycows)(display" cows.\n")(bull-cowanswer))))(begin(display"Invalid guess.\n")(bull-cowanswer)))))(bull-cow(get-num))
Enter a guess: 12340 bulls, 1 cows.Enter a guess: 23451 bulls, 0 cows.Enter a guess: 23461 bulls, 1 cows.Enter a guess: 23670 bulls, 1 cows.Enter a guess: 26471 bulls, 1 cows.Enter a guess: 26482 bulls, 1 cows.Enter a guess: 24681 bulls, 2 cows.Enter a guess: 14681 bulls, 2 cows.Enter a guess: 26840 bulls, 3 cows.Enter a guess: 62483 bulls, 0 cows.Enter a guess: 6948You win!
Scratch is a graphical programming language. Follow the link to see an example solution for Bulls and Cows
Scratch - Bulls and Cows
The program "says" the score of the current guess and uses a list to display previous guesses.
Malformed guesses are rejected for the following reasons:
Since Scratch is an educational language, I've included comments in the code to explain what the program is doing.
$ include "seed7_05.s7i";const proc: main is func local const integer: size is 4; var set of char: digits is {'1' .. '9'}; var string: chosen is " " mult size; var integer: guesses is 0; var string: guess is ""; var integer: pos is 0; var integer: bulls is 0; var integer: cows is 0; var boolean: okay is FALSE; begin for pos range 1 to 4 do chosen @:= [pos] rand(digits); excl(digits, chosen[pos]); end for; writeln("I have chosen a number from " <& size <& " unique digits from 1 to 9 arranged in a random order."); writeln("You need to input a " <& size <& " digit, unique digit number as a guess at what I have chosen"); repeat incr(guesses); repeat write("Next guess [" <& guesses <& "]: "); readln(guess); okay := length(guess) = size; for key pos range guess do okay := okay and guess[pos] in {'1' .. '9'} and pos(guess[succ(pos) ..], guess[pos]) = 0; end for; if not okay then writeln("Problem, try again. You need to enter " <& size <& " unique digits from 1 to 9"); end if; until okay; if guess <> chosen then bulls := 0; cows := 0; for key pos range chosen do if guess[pos] = chosen[pos] then incr(bulls); elsif pos(chosen, guess[pos]) <> 0 then incr(cows); end if; end for; writeln(" " <& bulls <& " Bulls"); writeln(" " <& cows <& " Cows"); end if; until guess = chosen; writeln("Congratulations you guessed correctly in " <& guesses <& " attempts"); end func;
I have chosen a number from 4 unique digits from 1 to 9 arranged in a random order.You need to input a 4 digit, unique digit number as a guess at what I have chosenNext guess [1]: 1234 1 Bulls 0 CowsNext guess [2]: 1567 1 Bulls 2 CowsNext guess [3]: 1856 3 Bulls 0 CowsNext guess [4]: 1956Congratulations you guessed correctly in 4 attempts
repeat foreverrepeat foreverput random(1111,9999) into numif character 1 of num is not equal to character 2 of numif character 1 of num is not equal to character 3 of numif character 1 of num is not equal to character 4 of numif character 2 of num is not equal to character 3 of numif character 2 of num is not equal to character 4 of numif character 3 of num is not equal to character 4 of numif num does not contain 0exit repeatend ifend ifend ifend ifend ifend ifend ifend repeatset description to "Guess the 4 digit number" & newline & "- zero's excluded" & newline & "- each digit is unique" & newline & newline & "Receive 1 Bull for each digit that equals the corresponding digit in the random number." & newline & newline & "Receive 1 Cow for each digit that appears in the wrong position." & newlinerepeat foreverrepeat foreverAsk "Guess the number" title "Bulls & Cows" message descriptionput it into guessif number of characters in guess is equal to 4exit repeatelse if guess is ""Answer "" with "Play" or "Quit" title "Quit Bulls & Cows?"put it into myAnswerif myAnswer is "Quit"exit allend ifend ifend repeatset score to {bulls: {qty: 0,values: []},cows: {qty: 0,values: []}}repeat the number of characters in num timesif character the counter of guess is equal to character the counter of numadd 1 to score.bulls.qtyinsert character the counter of guess into score.bulls.valueselseif num contains character the counter of guessif character the counter of guess is not equal to character the counter of numif score.bulls.values does not contain character the counter of guess and score.cows.values does not contain character the counter of guessadd 1 to score.cows.qtyinsert character the counter of guess into score.cows.valuesend ifend ifend ifend ifend repeatset showScores to "Your score is:" & newline & newline & "Bulls:" && score.bulls.qty & newline & newline & "Cows:" && score.cows.qtyif guess is not equal to numAnswer showScores with "Guess Again" or "Quit" title "Score"put it into myAnswerif myAnswer is "Quit"exit allend ifelseset winShowScores to showScores & newline & newline & "Your Guess:" && guess & newline & "Random Number:" && num & newlineAnswer winShowScores with "Play Again" or "Quit" title "You Win!"put it into myAnswerif myAnswer is "Quit"exit allend ifexit repeatend ifend repeatend repeat
program bulls_and_cows; setrandom(0); print("Bulls and cows"); print("--------------"); print; secret := make_secret(); loop do guess := read_guess(); tries +:= 1; bulls := count_bulls(guess, secret); cows := count_cows(guess, secret); print(bulls, "bulls,", cows, "cows."); if bulls = 4 then print("You win! Tries:", tries); exit; end if; end loop; proc make_secret(); digits := []; loop for i in [1..4] do loop until not digit in digits do digit := 1 + random(8); end loop; digits with:= digit; end loop; return digits; end proc; proc read_guess(); loop do putchar("Guess? "); flush(stdout); guess := getline(stdin); if exists d in guess | not d in "123456789" then print("invalid input:", d); elseif #guess /= #{d : d in guess} then print("no duplicates allowed"); elseif #guess /= 4 then print("need 4 digits"); else exit; end if; end loop; return [val d : d in guess]; end proc; proc count_bulls(guess, secret); return #[i : i in [1..4] | guess(i) = secret(i)]; end proc; proc count_cows(guess, secret); return #[d : d in guess | d in secret] - count_bulls(guess, secret); end proc;end program;
Bulls and cows--------------Guess? 12340 bulls, 1 cows.Guess? 56782 bulls, 1 cows.Guess? 59782 bulls, 0 cows.Guess? 59681 bulls, 1 cows.Guess? 59761 bulls, 1 cows.Guess? 69783 bulls, 0 cows.Guess? 69712 bulls, 0 cows.Guess? 69182 bulls, 0 cows.Guess? 19782 bulls, 0 cows.Guess? 61783 bulls, 0 cows.Guess? 62783 bulls, 0 cows.Guess? 63784 bulls, 0 cows.You win! Tries: 12
#!/usr/local/bin/shalemaths libraryfile librarystring libraryn0 varn1 varn2 varn3 varg0 varg1 varg2 varg3 varinit dup var { c guess:: var} =getNum dup var { random maths::() 15 >> 9 % 1 +} =game dup var { haveWon dup var false = ans var i var c var b var c guess:: 0 = n0 getNum() = n1 getNum() = { n1 n0 == } { n1 getNum() = } while n2 getNum() = { n2 n0 == n2 n1 == or } { n2 getNum() = } while n3 getNum() = { n3 n0 == n3 n1 == n3 n2 == or or } { n3 getNum() = } while "New game" println { haveWon not } { "> " print stdin file:: fgets file::() { ans swap atoi string::() = g3 ans 10 % = g2 ans 10 / 10 % = g1 ans 100 / 10 % = g0 ans 1000 / 10 % = g0 0 > g0 10 < and g1 0 > g1 10 < and g2 0 > g2 10 < and g3 0 > g3 10 < and and and and { c 0 = b 0 = g0 n0 == { b++ } { g0 n1 == g0 n2 == g0 n3 == or or { c++ } ifthen } if g1 n1 == { b++ } { g1 n0 == g1 n2 == g1 n3 == or or { c++ } ifthen } if g2 n2 == { b++ } { g2 n0 == g2 n1 == g2 n3 == or or { c++ } ifthen } if g3 n3 == { b++ } { g3 n0 == g3 n1 == g3 n2 == or or { c++ } ifthen } if i c guess:: = i.value guess:: guess:: defined not { i.value guess:: guess:: var i.value cow:: guess:: var i.value bull:: guess:: var } ifthen i.value guess:: guess:: ans = i.value cow:: guess:: c = i.value bull:: guess:: b = c guess::++ "Go Guess Cows Bulls" println i 0 = { i c guess:: < } { i.value bull:: guess:: i.value cow:: guess:: i.value guess:: guess:: i 1 + "%2d %d %4d %5d\n" printf i++ } while b 4 == { haveWon true = } ifthen } { "Illegal input" println } if } { 0 exit } if } while} =play dup var { { true } { game() } while} =init()play()
New game> 1234Go Guess Cows Bulls 1 1234 2 0> 2345Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0> 3456Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0 3 3456 0 2> 4567Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0 3 3456 0 2 4 4567 1 0> 5678Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0 3 3456 0 2 4 4567 1 0 5 5678 1 1> 6789Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0 3 3456 0 2 4 4567 1 0 5 5678 1 1 6 6789 1 0> 3158Go Guess Cows Bulls 1 1234 2 0 2 2345 2 0 3 3456 0 2 4 4567 1 0 5 5678 1 1 6 6789 1 0 7 3158 0 4New game>
varsize=4varnum=@(1..9).shuffle.first(size)for(varguesses=1;true;guesses++){varbulls=0varcows=0varinput=read("Input: ",String).chars\.uniq\.grep(/^[1-9]$/)\.map{.to_n}if(input.len!=size){warn"Invalid input!\n"guesses--next}if(input==num){printf("You did it in %d attempts!\n",guesses)break}fori(^num){if(num[i]==input[i]){bulls++}elsif(num.contains(input[i])){cows++}}"Bulls: %d; Cows: %d\n".printf(bulls,cows)}
Input: 2953Bulls: 1; Cows: 1Input: 9654Bulls: 1; Cows: 1Input: 8924Bulls: 1; Cows: 3Input: 2894You did it in 4 attempts!
Objectsubclass:BullsCows [|number|BullsCowsclass>>new:secretNum [|i|i:=selfbasicNew. (selfisValid:secretNum)ifFalse: [SystemExceptions.InvalidArgumentsignalOn:secretNumreason:'You need 4 unique digits from 1 to 9' ].isetNumber:secretNum.^i ]BullsCowsclass>>new [|b|b:=Setnew. [bsize<4 ]whileTrue: [badd: ((Randombetween:1and:9)displayStringfirst) ].^selfnew: (basString) ]BullsCowsclass>>isValid:num [^ (numasSetsize=4)& ((numasSetincludes:$0)not) ]setNumber:num [number:=num ]check:guess [|bc|bc:=Bagnew.1to:4do: [:i| (numberat:i)= (guessat:i)ifTrue: [bcadd:'bulls' ]ifFalse: [ (numberincludes: (guessat:i))ifTrue: [bcadd:'cows' ] ] ].^bc ]].'Guess the 4-digits number (digits from 1 to 9, no repetition)'displayNl.|guessMe d r tries|[tries:=0.guessMe:=BullsCowsnew. [ ['Write 4 digits: 'display.d:=stdinnextLine. (BullsCowsisValid:d) ]whileFalse: ['Insert 4 digits, no repetition, exclude the digit 0'displayNl ].r:=guessMecheck:d.tries:=tries+1. (roccurrencesOf:'bulls')=4 ]whileFalse: [ ('%1 cows, %2 bulls'% {roccurrencesOf:'cows'.roccurrencesOf:'bulls' })displayNl. ]. ('Good, you guessed it in %1 tries!'% {tries })displayNl.'Do you want to play again? [y/n]'display. ( (stdinnextLine)='y' )]whileTrue: [CharacternldisplayNl ].
'by rbytes, January 2017OPTION BASE 1P(" B U L L S A N D C O W S")!lP("A secret 4-digit number has been created, with")P("no repeats and no zeros. You must guess the number.")P("After each guess, you will be shown how many of your")P("digits are correct and in the matching location (bulls),")P("and how many are correct but in a different location (cows).")p("See how many tries it takes you to get the right answer.")' generate a 4-digit number with no repeatsguesses = 01 WHILE LEN(sec$) <4 c$ =CHR$( INTEG(RND(1) *9) +49) IF INSTR(sec$, c$)=-1 THEN sec$&=c$ENDWHILE!l2 PRINT "Your guess: "INPUT "FOUR DIGITS": guess$!lIF guess$="" THEN ' check if entry is null P("Please enter something!")!l GOTO 2ENDIFP(guess$)!lIF LEN(guess$)<>4 THEN ' check if entry is exactly 4 characters P("Please enter exactly 4 digits.")!l GOTO 2ENDIFFOR t=1 TO 4 ' check if all characters are digits 1 - 9 IF INSTR("123456789",MID$(guess$,t,1))=-1 THEN P("You have entered at least one illegal character")!l GOTO 2 ENDIFNEXT trep = check(guess$) ' check if any digits are repeatedIF check.chk THEN P("Please enter a number with no repeated digits.")!l GOTO 2ENDIFguesses+=1r$=score$(guess$,sec$)P(r$)!l IF guess$=sec$ THEN P("W I N N E R ! ! !")!l IF guesses>1 THEN gs$="guesses!" ELSE gs$="guess!" P("You won after "&guesses&" "&gs$) P("Thanks for playing!")!l PAUSE 2 P("A G A I N with a new secret number")!l guesses=0END IFGOTO 1END ' _____________________________________________________________DEF P(p$) ' function to print a string PRINT p$END DEFDEF L() ' function to print an empty line PRINTEND DEFDEF check(i$) ' check=0 if digit is not repeated, else=1 chk=0 FOR i =1 TO 3 FOR j =i +1 TO 4 IF MID$( i$, i, 1)=MID$( i$, j, 1) THEN chk =1 NEXT j NEXT iEND DEFDEF score$(a$,b$) ' calculate the numbers of bulls & cows. bulls=0!cows=0 FOR i = 1 TO 4 c$ = MID$( a$, i, 1) IF MID$( b$, i, 1)=c$ THEN bulls+=1 ELSE IF INSTR( b$, c$) <>-1 AND INSTR( b$, c$) <>i THEN cows+=1 END IF END IF NEXT i r$ ="Bulls: "&STR$( bulls)& ", "& "Cows: " &STR$( cows) RETURN r$END DEFEND
This is the same as the original solution but takes advantage of Swift 5's richer standard library to clean things up a bit.
funcgenerateRandomNumArray(numDigits:Int=4)->[Character]{guard(1...9).contains(numDigits)else{fatalError("number out of range")}returnArray("123456789".shuffled()[0..<numDigits])}funcparseGuess(_guess:String,numDigits:Int=4)->String?{guardguess.count==numDigitselse{returnnil}// Only digits 0 to 9 allowed, no Unicode fractions or numbers from other languagesletguessArray=guess.filter{$0.isASCII&&$0.isWholeNumber}guardSet(guessArray).count==numDigitselse{returnnil}returnguessArray}funcpluralIfNeeded(_count:Int,_units:String)->String{return"\(count) "+units+(count==1?"":"s")}varguessAgain="y"whileguessAgain=="y"{letnum=generateRandomNumArray()varbulls=0varcows=0print("Please enter a 4 digit number with digits between 1-9, no repetitions: ")ifletguessStr=readLine(strippingNewline:true),letguess=parseGuess(guessStr){for(guess,actual)inzip(guess,num){ifguess==actual{bulls+=1}elseifnum.contains(guess){cows+=1}}print("Actual number: "+num)print("Your score:\(pluralIfNeeded(bulls,"bull")) and\(pluralIfNeeded(cows,"cow"))\n")print("Would you like to play again? (y): ")guessAgain=readLine(strippingNewline:true)?.lowercased()??"n"}else{print("Invalid input")}}
importFoundationfuncgenerateRandomNumArray(numDigits:Int=4)->[Int]{guardnumDigits>0else{return[]}letneeded=min(9,numDigits)varnums=Set<Int>()repeat{nums.insert(.random(in:1...9))}whilenums.count!=neededreturnArray(nums)}funcparseGuess(_guess:String)->[Int]?{guardguess.count==4else{returnnil}letguessArray=guess.map(String.init).map(Int.init).compactMap({$0})guardSet(guessArray).count==4else{returnnil}returnguessArray}whiletrue{letnum=generateRandomNumArray()varbulls=0varcows=0print("Please enter a 4 digit number with digits between 1-9, no repetitions: ")guardletguessStr=readLine(strippingNewline:true),letguess=parseGuess(guessStr)else{print("Invalid input")continue}for(guess,actual)inzip(guess,num){ifguess==actual{bulls+=1}elseifnum.contains(guess){cows+=1}}print("Actual number:\(num.map(String.init).joined())")print("Your score:\(bulls) bulls and\(cows) cows\n")print("Would you like to play again? (y): ")guardreadLine(strippingNewline:true)!.lowercased()=="y"else{exit(0)}}
Please enter a 4 digit number with digits between 1-9, no repetitions: 8496Actual number: 6475Your score: 1 bulls and 1 cowsWould you like to play again? (y): yPlease enter a 4 digit number with digits between 1-9, no repetitions: 5983Actual number: 7846Your score: 0 bulls and 1 cows
procmain{}{fconfigurestdout-bufferingnonesetlength4puts"I have chosen a number from $length unique digits from 1 to 9 arranged in a random order.You need to input a $length digit, unique digit number as a guess at what I have chosen "whiletrue{setword[generateWord$length]setcount1while{[setguess[getGuess$length]]ne$word}{printScore$length$word$guessincrcount}puts"You guessed correctly in $count tries."if{[yn"Play again?"]eq"n"}break}}procgenerateWord{length}{setchars123456789for{seti1}{$i<=$length}{incri}{setidx[expr{int(rand()*[stringlength$chars])}]appendword[stringindex$chars$idx]setchars[stringreplace$chars$idx$idx]}return$word# here's another way to generate word with no duplicationssetword""while{[stringlength$word]<$length}{setchar[expr{int(1+9*rand())}]if{[stringfirst$char$word]==-1}{appendword$char}}}procgetGuess{length}{puts-nonewline"Enter your guess: "whiletrue{getsstdinguessif{[stringmatch[stringrepeat{[1-9]}$length]$guess]}{return$guess}if{[stringtolower[stringtrim$guess]]eq"quit"}{putsByeexit}puts"The word must be $length digits between 1 and 9 inclusive. Try again."}}procprintScore{lengthwordguess}{setbulls0setcows0for{seti0}{$i<$length}{incri}{if{[stringindex$word$i]eq[stringindex$guess$i]}{incrbullssetword[stringreplace$word$i$i+]}}puts" $bulls bulls"for{seti0}{$i<$length}{incri}{if{[setj[stringfirst[stringindex$guess$i]$word]]!=-1}{incrcowssetword[stringreplace$word$j$j-]}}puts" $cows cows"}procyn{msg}{whiletrue{puts-nonewline"$msg \[y/n] "getsstdinanssetchar[stringtolower[stringindex[stringtrim$ans]0]]if{$chareq"y"||$chareq"n"}{return$char}}}main
#langtransdMainModule:{contains-duplicates:(λsString()->Bool()(withstrString(s)(sortstr)(ret(neq(find-adjacentstr)(endstr))))),play:(λlocals:syms"0123456789"len4thenumString()guessString()(shufflesyms)(=thenum(substrsyms0len))(textout"Your guess: ")(while(getlineguess)(if(eqguess"q")break)(if(or(neq(sizeguess)len)(neq(find-first-not-ofguesssyms)-1)(contains-duplicatesguess))(loutguess" is not valid guess")(textout"Your guess: ")continue)(withbulls0cows0pl0(foriinRange(len)do(=pl(index-ofthenum(subnguessi)))(if(eqpli)(+=bulls1)elsif(neqpl-1)(+=cows1)))(lout"bulls: "bulls", cows: "cows)(if(eqbullslen)(lout"Congratulations! You have found out the number!")(retnull)else(textout"Your guess: "))))(lout"You quit the game.")),_start:(λlocals:sString()(lout"Welcome to\"Bulls and cows\"!")(whiletrue(whiletrue(textout"Do you want to play? (yes|no) : ")(getlines)(if(not(sizes))(lout"Didn't receive an answer. Exiting.")(exit)elsif(==(sub(tolowers)01)"n")(lout"Bye!")(exit)elsif(==(sub(tolowers)01)"y")breakelse(lout"(Hint:\"yes\" or\"no\".)")))(play)(lout"Another game?")))}
$$ MODE tuscriptSET nr1=RANDOM_NUMBERS (1,9,1)LOOP SET nr2=RANDOM_NUMBERS (1,9,1) IF (nr2!=nr1) EXITENDLOOPLOOP SET nr3=RANDOM_NUMBERS (1,9,1) IF (nr3!=nr1,nr2) EXITENDLOOPLOOP SET nr4=RANDOM_NUMBERS (1,9,1) IF (nr4!=nr1,nr2,nr3) EXITENDLOOPSET nr=JOIN(nr1,"'",nr2,nr3,nr4), limit=10LOOP r=1,limitSET bulls=cows=0ASK "round {r} insert a number":guessnr=""SET length=LENGTH(guessnr), checknr=STRINGS (guessnr,":>/:") LOOP n=nr,y=checknr IF (length!=4) THEN PRINT "4-letter digit required" EXIT ELSEIF (n==y) THEN SET bulls=bulls+1 ELSEIF (nr.ct.":{y}:") THEN SET cows=cows+1 ENDIF ENDLOOPPRINT "bulls=",bulls," cows=",cows IF (bulls==4) THEN PRINT "BINGO" EXIT ELSEIF (r==limit) THEN PRINT "BETTER NEXT TIME" EXIT ENDIFENDLOOP
Output:
round 1 insert a number >1234bulls=1 cows=1round 2 insert a number >5678bulls=1 cows=1round 3 insert a number >1298bulls=2 cows=0round 4 insert a number >2379bulls=0 cows=0round 5 insert a number >1468bulls=4 cows=0BINGO
Local(2) ' Let's use no globalsProc _Initialize ' Get our secret numberDo ' Repeat until it's guessed Do Input "Enter your guess: ";a@ ' Enter your guess While FUNC(_Invalid(a@)) ' but make sure it's a valid guess Loop a@ = FUNC(_Bulls) ' Count the number of bulls b@ = FUNC(_Cows) ' Count the number of cows ' Now give some feedback Print : Print "\tThere were ";a@;" bulls and ";b@;" cows." : Print Until a@ = 4 ' Until the secret is guessedLoopPrint "You win!" ' Yes, you guessed itEnd_Initialize ' Make a secret Local (1) Do a@ = 1234 + RND(8643) ' Get a valid number While FUNC(_Invalid(a@)) ' and accept it unless invalid Loop For a@ = 0 to 3 ' Now save it at the proper place @(a@+4) = @(a@) NextReturn_Invalid Param(1) ' Check whether a number is valid Local(2) ' Ok, these can't be right at all If (a@ < 1234) + (a@ > 9876) Then Return (1) ' Now break 'em up in different digits For b@ = 3 To 0 Step -1 @(b@) = a@ % 10 ' A digit of zero can't be right If @(b@) = 0 Then Unloop : Return (1) a@ = a@ / 10 Next For b@ = 0 To 2 ' Now compare all digits For c@ = b@ + 1 To 3 ' The others were already compared If @(b@) = @(c@) Then Unloop : Unloop : Return (1) Next ' Wrong, we found similar digits NextReturn (0) ' All digits are different_Bulls ' Count the number of valid guesses Local (2) b@ = 0 ' Start with zero For a@ = 0 to 3 ' Increment with each valid guess If @(a@) = @(a@+4) Then b@ = b@ + 1 NextReturn (b@) ' Return number of valid guesses_Cows Local (3) ' Count the number of proper digits c@ = 0 ' Start with zero For a@ = 0 To 3 ' All the players guesses For b@ = 4 To 7 ' All the computers secrets If (a@+4) = b@ Then Continue ' Skip the bulls If @(a@) = @(b@) Then c@ = c@ + 1 Next ' Increment with valid digits NextReturn (c@) ' Return number of valid digits
The addition of strings allows for much simpler code.
Do s = Str(1234 + RND(8643)) Until FUNC(_Check(s))NextDo Do g = Ask("Enter your guess: ") If (Val(g) = Info("nil")) + (Len(g) # 4) Then Continue Until FUNC(_Check(g)) Loop b = 0 : c = 0 For i = 0 To 3 For j = 0 to 3 If Peek(s, i) = Peek(g, j) Then If i = j Then b = b + 1 Else c = c + 1 EndIf EndIf Next Next Print "You scored ";b;" bulls and ";c; " cows.\n" Until b = 4LoopEnd_Check Param (1) Local (2) b@ = 0 For c@ = 0 To 3 If Peek(a@, c@) = Ord ("0") Then Unloop : Return (0) If And(b@, 2^(Peek(a@, c@) - Ord ("0"))) Then Unloop : Return (0) b@ = b@ + 2^(Peek(a@, c@) - Ord ("0")) NextReturn (1)
#!/bin/bashrand(){localmin=${1:-0}localmax=${2:-32767}[${min}-gt${max}]&&min=$((min^max))&&max=$((min^max))&&min=$((min^max))echo-n$((($RANDOM%$max)+$min))}in_arr(){localquandry="${1}"shiftlocalarr=($@)locali=''foriin${arr[*]}do["${quandry}"=="${i}"]&&return0&&breakdonereturn1}delete_at(){localidx="$(($1+1))"shiftlocalarr=("sentinel"$@)echo-n"${arr[@]:1:$((idx-1))}${arr[@]:$((idx+1)):$((${#arr[@]}-idx-1))}"}delete_first(){localmeanie="${1}"shiftlocalarr=($@)locali=0for((i=0;i<${#arr[@]};i++))do["${arr[${i}]}"=="${meanie}"]&&arr=($(delete_at${i}${arr[*]}))doneecho-n"${arr[*]}"}to_arr(){localstring="${1}"localarr=()while["${#string}"-gt0]doarr=(${arr[*]}${string:0:1})string="${string:1}"doneecho-n"${arr[*]}"}choose_idx(){localarr=($@)echo-n"$(rand0$((${#arr[@]}-1)))"}locate_bulls(){localsecret=($(to_arr"${1}"))localguess=($(to_arr"${2}"))localhits=()locali=0for((i=0;i<4;i++))do["${secret[${i}]}"-eq"${guess[${i}]}"]&&hits=(${hits[*]}${i})doneecho-n"${hits[*]}"}bulls(){localsecret="${1}"localguess="${2}"localbulls=($(locate_bulls"${secret}""${guess}"))echo-n"${#bulls[@]}"}cows(){localsecret=($(to_arr"${1}"))localguess=($(to_arr"${2}"))localbulls=($(locate_bulls"${1}""${2}"))localhits=0locali=''# Avoid double-counting bullsforiin${bulls[*]}dosecret=($(delete_at${i}${secret[*]}))done# Process the guess against what's left of the secretforiin${guess[*]}doin_arr"${i}"${secret[*]}&&secret=($(delete_first"${i}"${secret[*]}))&&((hits++))doneecho-n${hits}}malformed(){localguess=($(to_arr"${1}"))locali=''[${#guess[@]}-ne4]&&return0foriin${guess[*]}doif!in_arr${i}123456789thenreturn0breakfidonereturn1}candidates=(123456789)secret=''while["${#secret}"-lt4]docidx=$(choose_idx${candidates[*]})secret="${secret}${candidates[${cidx}]}"candidates=($(delete_at${cidx}${candidates[*]}))donewhileread-p"Enter a four-digit guess: "guessdomalformed"${guess}"&&echo"Malformed guess"&&continue["${guess}"=="${secret}"]&&echo"You win!"&&exitecho"Score:$(bulls"${secret}""${guess}") Bulls,$(cows"${secret}""${guess}") Cows"done
OptionExplicitSubMain_Bulls_and_cows()DimstrNumberAsString,strInputAsString,strMsgAsString,strTempAsStringDimboolEndAsBooleanDimlngCptAsLongDimiAsByte,bytCowAsByte,bytBullAsByteConstNUMBER_OF_DIGITSAsByte=4ConstMAX_LOOPSAsByte=25'the max of lines supported by MsgBoxstrNumber=Create_Number(NUMBER_OF_DIGITS)DobytBull=0:bytCow=0:lngCpt=lngCpt+1IflngCpt>MAX_LOOPSThenstrMsg="Max of loops... Sorry you loose!":ExitDostrInput=AskToUser(NUMBER_OF_DIGITS)IfstrInput="Exit Game"ThenstrMsg="User abort":ExitDoFori=1ToLen(strNumber)IfMid(strNumber,i,1)=Mid(strInput,i,1)ThenbytBull=bytBull+1ElseIfInStr(strNumber,Mid(strInput,i,1))>0ThenbytCow=bytCow+1EndIfNextiIfbytBull=Len(strNumber)ThenboolEnd=True:strMsg="You win in "&lngCpt&" loops!"ElsestrTemp=strTemp&vbCrLf&"With : "&strInput&" ,you have : "&bytBull&" bulls,"&bytCow&" cows."MsgBoxstrTempEndIfLoopWhileNotboolEndMsgBoxstrMsgEndSubFunctionCreate_Number(NbDigitsAsByte)AsStringDimmyCollAsNewCollectionDimstrTempAsStringDimbytAleaAsByteRandomizeDobytAlea=Int((Rnd*9)+1)OnErrorResumeNextmyColl.AddCStr(bytAlea),CStr(bytAlea)IfErr<>0ThenOnErrorGoTo0ElsestrTemp=strTemp&CStr(bytAlea)EndIfLoopWhileLen(strTemp)<NbDigitsCreate_Number=strTempEndFunctionFunctionAskToUser(NbDigitsAsByte)AsStringDimboolGoodAsBoolean,strInAsString,iAsByte,NbDiffAsByteDoWhileNotboolGoodstrIn=InputBox("Enter your number ("&NbDigits&" digits)","Number")IfStrPtr(strIn)=0ThenstrIn="Exit Game":ExitDoIfstrIn<>""ThenIfLen(strIn)=NbDigitsThenNbDiff=0Fori=1ToLen(strIn)IfLen(Replace(strIn,Mid(strIn,i,1),""))<NbDigits-1ThenNbDiff=1ExitForEndIfNextiIfNbDiff=0ThenboolGood=TrueEndIfEndIfLoopAskToUser=strInEndFunction
VBS functions return variants. I use t to return a single error value or a pair bulls, cows on result
VBS does'nt have a continue so i used the classic do loop inside do loop in the main program
randomizetimerfail=array("Wrong number of chars","Only figures 0 to 9 allowed","Two or more figures are the same")p=dopuzzle()wscript.echo"Bulls and Cows. Guess my 4 figure number!"dodowscript.stdout.writevbcrlf&"your move ":s=trim(wscript.stdin.readline)c=checkinput(s)ifnotisarray(c)thenwscript.stdout.writefail(c):exitdobu=c(0)wscript.stdout.write"bulls: "&c(0)&" | cows: "&c(1)loopwhile0loopuntilbu=4wscript.stdout.writevbcrlf&"You won! "functiondopuzzle()dimb(10)fori=1to4dor=fix(rnd*10)loopuntilb(r)=0b(r)=1:dopuzzle=dopuzzle+chr(r+48)nextendfunctionfunctioncheckinput(s)dimc(10)bu=0:co=0iflen(s)<>4thencheckinput=0:exitfunctionfori=1to4b=mid(s,i,1)ifinstr("0123456789",b)=0thencheckinput=1:exitfunctionifc(asc(b)-48)<>0thencheckinput=2:exitfunctionc(asc(b)-48)=1forj=1to4ifasc(b)=asc(mid(p,j,1))thenifi=jthenbu=bu+1elseco=co+1endifnextnextcheckinput=array(bu,co)endfunction
Buf_Switch(Buf_Free)#90 = Time_Tick // seed for random number generator#91 = 10 // random numbers in range 0 to 9while (EOB_pos < 4) { // 4 digits needed Call("RANDOM") BOF Ins_Char(Return_Value + '0') Replace("(.)(.*)\1", "\1\2", REGEXP+BEGIN+NOERR) // remove any duplicate}#3 = 0repeat (99) { Get_Input(10, "Guess a 4-digit number with no duplicate digits: ", NOCR) if (Reg_Size(10) == 0) { Break } // empty string = exit Num_Eval_Reg(10) // check for numeric digits if (Chars_Matched != 4) { M("You should enter 4 numeric digits\n") Continue } Goto_Pos(4) // count bulls Reg_Ins(10, OVERWRITE) #1 = Search("(.)...\1", REGEXP+BEGIN+ALL+NOERR) RS(10, "[", INSERT) // count cows RS(10, "]", APPEND) #2 = Search_Block(@10, 0, 4, REGEXP+BEGIN+ALL+NOERR) - #1 #3++ NT(#1, NOCR) M(" bulls,") NT(#2, NOCR) M(" cows\n") if (#1 == 4) { M("You won after") NT(#3, NOCR) M(" guesses!\n") Break }}Buf_Quit(OK)Return//--------------------------------------------------------------// Generate random numbers in range 0 <= Return_Value < #91// #90 = Seed (0 to 0x7fffffff)// #91 = Scaling (0 to 0x10000):RANDOM:#92 = 0x7fffffff / 48271#93 = 0x7fffffff % 48271#90 = (48271 * (#90 % #92) - #93 * (#90 / #92)) & 0x7fffffffReturn ((#90 & 0xffff) * #91 / 0x10000)
ImportsSystemImportsSystem.Text.RegularExpressionsModuleBulls_and_CowsFunctionCreateNumber()AsStringDimrandomAsNewRandom()DimsequenceAsChar()={"1"c,"2"c,"3"c,"4"c,"5"c,"6"c,"7"c,"8"c,"9"c}ForiAsInteger=0Tosequence.Length-1DimjAsInteger=random.Next(sequence.Length)DimtempAsChar=sequence(i):sequence(i)=sequence(j):sequence(j)=tempNextReturnNewString(sequence,0,4)EndFunctionFunctionIsFourDigitNumber(ByValnumberAsString)AsBooleanReturnRegex.IsMatch(number,"^[1-9]{4}$")EndFunctionSubMain()DimchosenNumberAsString=CreateNumber()DimattemptAsInteger=0Console.WriteLine("Number is chosen")DimgameOverAsBoolean=FalseDoattempt+=1Console.WriteLine("Attempt #{0}. Enter four digit number: ",attempt)DimnumberAsString=Console.ReadLine()DoWhileNotIsFourDigitNumber(number)Console.WriteLine("Invalid number: type four characters. Every character must digit be between '1' and '9'.")number=Console.ReadLine()LoopDimbullsAsInteger=0DimcowsAsInteger=0ForiAsInteger=0Tonumber.Length-1DimjAsInteger=chosenNumber.IndexOf(number(i))Ifi=jThenbulls+=1ElseIfj>=0Thencows+=1EndIfNextIfbulls<chosenNumber.LengthThenConsole.WriteLine("The number '{0}' has {1} bulls and {2} cows",_number,bulls,cows)ElsegameOver=TrueEndIfLoopUntilgameOverConsole.WriteLine("The number was guessed in {0} attempts. Congratulations!",attempt)EndSubEndModule
import randimport osfn main() {valid := ['1','2','3','4','5','6','7','8','9']mut value := []string{}mut guess, mut elem := '', ''mut cows, mut bulls := 0, 0println('Cows and Bulls')println('Guess four digit numbers of unique digits in the range 1 to 9.')println('A correct digit, but not in the correct place is a cow.')println('A correct digit, and in the correct place is a bull.')// generate patternfor value.len < 4 {elem = rand.string_from_set('123456789', 1)if value.any(it == elem) == false {value << elem }}// start gameinput: for _ in 0..3 {guess = os.input('Guess: ').str()// deal with malformed guessesif guess.len != 4 {println('Please input a four digit number.') continue input}for val in guess {if valid.contains(val.ascii_str()) == false {{println('Please input a number between 1 to 9.') continue input}}if guess.count(val.ascii_str()) > 1 {{println('Please do not repeat the same digit.') continue input}}}// score guessesfor idx, gval in guess {match true {gval.ascii_str() == value[idx] {bulls++ println('${gval.ascii_str()} was correctly guessed, and in the correct location! ')}gval.ascii_str() in value {cows++ println('${gval.ascii_str()} was correctly quessed, but not in the exact location! ')}else {}}if bulls == 4 {println('You are correct and have won!!! Congratulations!!!') exit(0)}}println('score: bulls: $bulls cows: $cows')}println('Only 3 guesses allowed. The correct value was: $value') println('Sorry, you lost this time, try again.')}
Cows and BullsGuess four digit numbers of unique digits in the range 1 to 9.A correct digit, but not in the correct place is a cow.A correct digit, and in the correct place is a bull.Guess: 26736 was correctly quessed, but not in the exact location! score: bulls: 0 cows: 1Guess: 16586 was correctly quessed, but not in the exact location! 5 was correctly quessed, but not in the exact location! 8 was correctly quessed, but not in the exact location! score: bulls: 0 cows: 4Guess: 68596 was correctly quessed, but not in the exact location! 8 was correctly guessed, and in the correct location! 5 was correctly quessed, but not in the exact location! score: bulls: 1 cows: 6Only 3 guesses allowed. The correct value was: ['5', '8', '4', '6']Sorry, you lost this time, try again.
10 I=120 J=130 :I)='/10*0+%40 #=:I)=0*30+(0<:I)*7050 #=:I)=:J)*2060 J=J+170 #=J<I*5080 I=I+190 #=4>I*20100 ?="BULLS AND COWS"110 ?="--------------"120 ?=""125 T=0130 T=T+1140 ?="GUESS? ";150 G=?160 #=G<1234+(G>9877)*510170 I=8180 G=G/10190 :I)=%200 I=I-1210 #=4<I*180220 #=:5)*:6)*:7)*:8)=0*510230 I=6240 J=5250 #=:I)=:J)*510260 J=J+1270 #=J<I*250280 I=I+1290 #=I<9*240300 B=0310 C=0320 I=1330 B=:I)=:I+4)+B340 J=1350 C=(I=J=0)*(:I)=:J+4))+C360 J=J+1370 #=4>J*350380 I=I+1390 #=4>I*330400 ?="BULLS: ";410 ?=B420 ?=", COWS: ";430 ?=C440 ?=""450 #=B<4*130460 ?=""470 ?="YOU GOT IT IN ";480 ?=T490 ?=" TRIES!"500 #=1000510 ?="BAD GUESS - GUESS NEEDS TO BE 4 UNIQUE DIGITS WITHOUT ZEROES"520 #=140
BULLS AND COWS--------------GUESS? 1234BULLS: 0, COWS: 1GUESS? 5678BULLS: 0, COWS: 2GUESS? 1978BULLS: 1, COWS: 2GUESS? 2978BULLS: 1, COWS: 2GUESS? 3978BULLS: 1, COWS: 2GUESS? 4978BULLS: 1, COWS: 3GUESS? 7984BULLS: 1, COWS: 3GUESS? 8947BULLS: 4, COWS: 0YOU GOT IT IN 8 TRIES!
import"random"forRandomimport"./set"forSetimport"./ioutil"forInputvarMAX_GUESSES=20// sayvarr=Random.new()varnum// generate a 4 digit random number from 1234 to 9876 with no zeros or repeated digitswhile(true){num=(1234+r.int(8643)).toStringif(!num.contains("0")&&Set.new(num).count==4)break}System.print("All guesses should have exactly 4 distinct digits excluding zero.")System.print("Keep guessing until you guess the chosen number (maximum%(MAX_GUESSES) valid guesses).\n")varguesses=0while(true){varguess=Input.text("Enter your guess : ")if(guess==num){System.print("You've won with%(guesses+1) valid guesses!")return}varn=Num.fromString(guess)if(!n){System.print("Not a valid number")}elseif(guess.contains("-")||guess.contains("+")||guess.contains(".")){System.print("Can't contain a sign or decimal point")}elseif(guess.contains("e")||guess.contains("E")){System.print("Can't contain an exponent")}elseif(guess.contains("0")){System.print("Can't contain zero")}elseif(guess.count!=4){System.print("Must have exactly 4 digits")}elseif(Set.new(guess).count<4){System.print("All digits must be distinct")}else{varbulls=0varcows=0vari=0for(cinguess){if(num[i]==c){bulls=bulls+1}elseif(num.contains(c)){cows=cows+1}i=i+1}System.print("Your score for this guess: Bulls =%(bulls) Cows =%(cows)")guesses=guesses+1if(guesses==MAX_GUESSES){System.print("You've now had%(guesses) valid guesses, the maximum allowed")return}}}
Sample game:
All guesses should have exactly 4 distinct digits excluding zero.Keep guessing until you guess the chosen number (maximum 20 valid guesses).Enter your guess : 1234Your score for this guess: Bulls = 1 Cows = 1Enter your guess : 1567Your score for this guess: Bulls = 0 Cows = 1Enter your guess : 8239Your score for this guess: Bulls = 2 Cows = 1Enter your guess : 8294Your score for this guess: Bulls = 2 Cows = 0Enter your guess : 8273Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 8275Your score for this guess: Bulls = 2 Cows = 1Enter your guess : 8263Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 8213Your score for this guess: Bulls = 3 Cows = 0Enter your guess : 8253You've won with 9 valid guesses!
int Bulls, Cows, Secret(4), Guess(4), Guesses, Used, I, J, Done, Digit, Okay;[Used:= 0; \generate secret random number using digitsfor I:= 0 to 3 do \ 1 to 9 without any repeated digits [repeat Digit:= Ran(9)+1; until (Used & 1<<Digit) = 0; Used:= Used ! 1<<Digit; Secret(I):= Digit + ^0; ];Text(0, "Guess the secret number.^m^j");Text(0, "Guesses must be four different digits, 1 to 9.^m^j");Guesses:= 0;loop [Done:= false; \main game loop repeat Text(0, "Enter your guess: "); \get valid 4-digits from player OpenI(0); Used:= 0; I:= 0; loop [Digit:= ChIn(0); Okay:= Digit>=^1 and Digit<=^9; Digit:= Digit & $0F; \convert ASCII to binary if not Okay or Used & 1<<Digit then [Text(0, "Please enter four distinct digits, 1 thru 9.^m^j"); quit; ]; Guess(I):= Digit + ^0; Used:= Used ! 1<<Digit; I:= I+1; if I = 4 then [Done:= true; quit]; ]; until Done; Guesses:= Guesses+1; Bulls:= 0; Cows:= 0; for I:= 0 to 3 do for J:= 0 to 3 do if Guess(I) = Secret(J) then if I=J then Bulls:= Bulls+1 else Cows:= Cows+1; Text(0, "Bulls: "); IntOut(0, Bulls); Text(0, " Cows: "); IntOut(0, Cows); CrLf(0); if Bulls = 4 then quit; ];Text(0, "Congratulations! You won in "); IntOut(0, Guesses); Text(0, " guesses.^m^j");]
Guess the secret number.Guesses must be four different digits, 1 to 9.Enter your guess: 1234Bulls: 1 Cows: 1Enter your guess: 3345Please enter four distinct digits, 1 thru 9.Enter your guess: 0987Please enter four distinct digits, 1 thru 9.Enter your guess: 1357Bulls: 1 Cows: 0Enter your guess:
Play one game:
d:=Dictionary(); do{ d[(1).random(10)]=True }while(d.len()<4);abcd:=d.keys.shuffle();while(1){ guess:=ask("4 digits: ")-" ,"; if(guess.len()!=4 or guess.unique().len()!=4) continue; bulls:=abcd.zipWith('==,guess).sum(0); cows:=guess.split("").enumerate() .reduce('wrap(s,[(n,c)]){ s + (d.find(c,False) and abcd[n]!=c) },0); if(bulls==4) { println("You got it!"); break; } "%d bull%s and %d cow%s".fmt(bulls,s(bulls),cows,s(cows)).println();}fcn s(n){ (n!=1) and "s" or "" }
4 digits: 4,5,6,71 bull and 0 cows4 digits: 12340 bulls and 2 cows4 digits: 3528You got it!