Playing cards: Difference between revisions

From Rosetta Code
Content added Content deleted
m (→‎{{header|ALGOL 68}}: Just pre tags)
Line 228: Line 228:
</pre>
</pre>
Example output:<br>
Example output:<br>
((King OF Clubs), (6 OF Hearts), (7 OF Diamonds), (Ace OF Hearts), (9 OF Spades), (10 OF Clubs), (Ace OF Spades), (8 OF Clubs), (4 OF Spades), (8 OF Hearts), (Jack OF Hearts), (3 OF Clubs), (7 OF Hearts), (10 OF Hearts), (Jack OF Clubs), (Ace OF Clubs), (King OF Spades), (9 OF Clubs), (7 OF Spades), (5 OF Spades), (7 OF Clubs), (Queen OF Clubs), (9 OF Diamonds), (2 OF Spades), (6 OF Diamonds), (Ace OF Diamonds), (Queen OF Diamonds), (5 OF Hearts), (4 OF Clubs), (5 OF Clubs), (4 OF Hearts), (3 OF Diamonds), (4 OF Diamonds), (3 OF Hearts), (King OF Diamonds), (2 OF Clubs), (Jack OF Spades), (2 OF Diamonds), (5 OF Diamonds), (Queen OF Spades), (10 OF Diamonds), (King OF Hearts), (Jack OF Diamonds), (Queen OF Hearts), (8 OF Spades), (2 OF Hearts), (8 OF Diamonds), (10 OF Spades), (9 OF Hearts), (6 OF Clubs), (3 OF Spades), (6 OF Spades))
<pre>((King OF Clubs), (6 OF Hearts), (7 OF Diamonds), (Ace OF Hearts), (9 OF Spades), (10 OF Clubs), (Ace OF Spades), (8 OF Clubs), (4 OF Spades), (8 OF Hearts), (Jack OF Hearts), (3 OF Clubs), (7 OF Hearts), (10 OF Hearts), (Jack OF Clubs), (Ace OF Clubs), (King OF Spades), (9 OF Clubs), (7 OF Spades), (5 OF Spades), (7 OF Clubs), (Queen OF Clubs), (9 OF Diamonds), (2 OF Spades), (6 OF Diamonds), (Ace OF Diamonds), (Queen OF Diamonds), (5 OF Hearts), (4 OF Clubs), (5 OF Clubs), (4 OF Hearts), (3 OF Diamonds), (4 OF Diamonds), (3 OF Hearts), (King OF Diamonds), (2 OF Clubs), (Jack OF Spades), (2 OF Diamonds), (5 OF Diamonds), (Queen OF Spades), (10 OF Diamonds), (King OF Hearts), (Jack OF Diamonds), (Queen OF Hearts), (8 OF Spades), (2 OF Hearts), (8 OF Diamonds), (10 OF Spades), (9 OF Hearts), (6 OF Clubs), (3 OF Spades), (6 OF Spades))</pre>


=={{header|C++}}==
=={{header|C++}}==

Revision as of 20:43, 23 October 2008

Task
Playing cards
You are encouraged to solve this task according to the task description, using any language you may know.

Create a data structure and the associated methods to define and manipulate a deck of playing cards. The deck should contain 52 unique cards. The methods must include the ability to make a new deck, shuffle (randomize) the deck, deal from the deck, and print the current contents of a deck. Each card must have a pip value and a suit value which constitute the unique value of the card.

Ada

Here is the package specification for a deck of playing cards. <ada> package Playing_Cards is

  pragma Elaborate_Body(Playing_Cards);
  type Card is private;
  procedure Print(The_Card : Card);
  type Deck is private;
  procedure Print(the_Deck : Deck);
  procedure Deal(From : in out Deck; The_Card : out Card);
  procedure Shuffle(The_Deck : in out Deck);
  function New_Deck return Deck;
  Deck_Empty : exception;

private

  type Pips is (Two, Three, Four, Five, Six, Seven,
     Eight, Nine, Ten, Jack, Queen, King, Ace);
  type Suits is (Diamonds, Spades, Hearts, Clubs);
  type Card is record
     Pip : Pips;
     Suit : Suits;
  end record;
  type Index is range 1..53;
  subtype Deck_Index is Index range 1..52;
  type Deck_Reference is array(Deck_Index) of Deck_Index;
  type Deck is record
     Next_Card : Index;
     Deck_Offsets : Deck_Reference;
  end record;

end Playing_Cards; </ada> Here is the package body for that same playing card package. This implementation stores one array of cards in sorted order. Each deck contains an array of indices into that one array of cards. Shuffling the deck actually results in randomizing the order of those indices into the array of cards. This approach maximizes shuffling efficiency by only exchanging indices. It also maximizes memory efficiency since an array of cards requires more memory than an array of indices. <ada> with Ada.Numerics.Discrete_Random; With Ada.Text_IO;

package body Playing_Cards is

  type Internal_Deck is array(Deck_Index) of Card;
  Base_Deck : Internal_Deck;
  Base_Index : Index;
  ----------
  -- Deal --
  ----------
  procedure Deal (From : in out Deck; The_Card : out Card) is
  begin
     if From.Next_Card not in Deck_Index then
        raise Deck_Empty;
     end if;
     The_Card := Base_Deck(From.Deck_Offsets(From.Next_Card));
     From.Next_Card := From.Next_Card + 1;
  end Deal;
  --------------
  -- New_Deck --
  --------------
  function New_Deck return Deck is
     Temp : Deck;
  begin
     for I in Base_Deck'range loop
        Temp.Deck_Offsets(I) := I;
     end loop;
     Temp.Next_Card := 1;
     return Temp;
  end New_Deck;
  -----------
  -- Print --
  -----------
  
  procedure Print(The_Card : Card) is
     package Pip_Io is new Ada.Text_Io.Enumeration_Io(Pips);
     use Pip_Io;
     package Suit_Io is new Ada.Text_Io.Enumeration_Io(Suits);
     use Suit_Io;
  begin
     Put(Item => The_Card.Pip, Width => 1);
     Ada.Text_Io.Put(" of ");
     Put(Item => The_Card.Suit, Width => 1);
     Ada.Text_Io.New_Line;
  end Print;
  
  -----------
  -- Print --
  -----------
  
  procedure Print(The_Deck : Deck) is
  begin
     for I in The_Deck.Next_Card..Deck_Index'Last loop
        Print(Base_Deck(The_Deck.Deck_Offsets(I)));
     end loop;
  end Print;
  
  -------------
  -- Shuffle --
  -------------
  procedure Shuffle (The_Deck : in out Deck) is
     procedure Swap(Left, Right : in out Deck_Index) is
        Temp : Deck_Index := Left;
     begin
        Left := Right;
        Right := Temp;
     end Swap;
     Swap_Index : Deck_Index;
  begin
     for I in Deck_Index'First..Deck_Index'Pred(Deck_Index'Last) loop
        declare
           subtype Remaining_Indices is Deck_Index range I..Deck_Index'Last;
           package Rand_Card is new Ada.Numerics.Discrete_Random(Remaining_Indices);
           use Rand_Card;
           Seed : Generator;
        begin
           Reset(Seed);
           Swap_Index := Random(Seed);
           Swap(The_Deck.deck_Offsets(I), The_Deck.Deck_Offsets(Swap_Index));
        end;
     end loop;
     The_Deck.Next_Card := 1;
  end Shuffle;
  

begin

  Base_Index := 1;
  for Suit in Suits'range loop
     for Pip in Pips'range loop
        Base_Deck(Base_Index) := (Pip, Suit);
        Base_Index := Base_Index + 1;
     end loop;
  end loop;

end Playing_Cards; </ada>

ALGOL 68

The scoping rules of ALGOL 68 tend to make object oriented coding in ALGOL 68 difficult. Also as invoking PROC is done before members of a STRUCT are extracted the programmer one quickly finds it is necessary to use numerous brackets.

e.g. compare "(shuffle OF deck class)(deck)" with python's simple "deck.shuffle()"

For further details:

# class members & attributes #
MODE CLASSCARD = STRUCT(
  PROC(REF CARD, STRING, STRING)VOID init, 
  FORMAT format,
  PROC(REF CARD)STRING repr,
  FLEX[1:0]STRING suits, pips
);

CLASSCARD class card = (
# PROC init = # (REF CARD self, STRING pip, suit)VOID:(
    pip OF self:=pip;
    suit OF self :=suit
  ),
# format = # $"("g" OF "g")"$,
# PROC repr = # (REF CARD self)STRING: ( 
    HEAP STRING out; putf(BOOK out,(format OF class card,self)); out
  ),
# suits = # ("Clubs","Hearts","Spades","Diamonds"),
# pips = # ("2","3","4","5","6","7","8","9","10","Jack","Queen","King","Ace")
);

MODE CARD = STRUCT(STRING pip, suit); # instance attributes #

# class members & attributes #
MODE CLASSDECK = STRUCT( 
  PROC(REF DECK)VOID init, shuffle, 
  PROC(REF DECK)STRING repr, 
  PROC(REF DECK)CARD deal
);

CLASSDECK class deck = (

# PROC init = # (REF DECK self)VOID:(
    HEAP[ UPB suits OF class card * UPB pips OF class card ]CARD new;
    FOR suit TO UPB suits OF class card DO
      FOR pip TO UPB pips OF class card DO
        new[(suit-1)*UPB pips OF class card + pip] :=
           ((pips OF class card)[pip], (suits OF class card)[suit])
      OD
    OD;
    deck OF self := new
  ),

# PROC shuffle = # (REF DECK self)VOID:
    FOR card TO UPB deck OF self DO
      CARD this card = (deck OF self)[card];
      INT random card = random int(LWB deck OF self,UPB deck OF self);
      (deck OF self)[card] := (deck OF self)[random card];
      (deck OF self)[random card] := this card
    OD,

# PROC repr = # (REF DECK self)STRING: (
    FORMAT format = $"("n(UPB deck OF self-1)(f(format OF class card)", ")f(format OF class card)")"$;
    HEAP STRING out; putf(BOOK out,(format, deck OF self)); out
  ),

# PROC deal = # (REF DECK self)CARD: (
    (shuffle OF class deck)(self);
    (deck OF self)[UPB deck OF self]
  )
);

MODE DECK = STRUCT(REF[]CARD deck); # instance attributes #

# associate a STRING with a FILE for easy text manipulation #
OP BOOK = (REF STRING string)REF FILE:(
  HEAP FILE book;
  associate(book, string);
  book
);

# Pick a random integer between from [lwb..upb] #
PROC random int = (INT lwb, upb)INT: 
  ENTIER(random * (upb - lwb + 1) + lwb);

DECK deck;
(init OF class deck)(deck);
(shuffle OF class deck)(deck);
print (((repr OF class deck)(deck), new line))

Example output:

((King OF Clubs), (6 OF Hearts), (7 OF Diamonds), (Ace OF Hearts), (9 OF Spades), (10 OF Clubs), (Ace OF Spades), (8 OF Clubs), (4 OF Spades), (8 OF Hearts), (Jack OF Hearts), (3 OF Clubs), (7 OF Hearts), (10 OF Hearts), (Jack OF Clubs), (Ace OF Clubs), (King OF Spades), (9 OF Clubs), (7 OF Spades), (5 OF Spades), (7 OF Clubs), (Queen OF Clubs), (9 OF Diamonds), (2 OF Spades), (6 OF Diamonds), (Ace OF Diamonds), (Queen OF Diamonds), (5 OF Hearts), (4 OF Clubs), (5 OF Clubs), (4 OF Hearts), (3 OF Diamonds), (4 OF Diamonds), (3 OF Hearts), (King OF Diamonds), (2 OF Clubs), (Jack OF Spades), (2 OF Diamonds), (5 OF Diamonds), (Queen OF Spades), (10 OF Diamonds), (King OF Hearts), (Jack OF Diamonds), (Queen OF Hearts), (8 OF Spades), (2 OF Hearts), (8 OF Diamonds), (10 OF Spades), (9 OF Hearts), (6 OF Clubs), (3 OF Spades), (6 OF Spades))

C++

Works with: g++ version 4.1.2 20061115 (prerelease) (SUSE Linux)

Since all the functions are quite simple, they are all defined inline <cpp>

  1. ifndef CARDS_H_INC
  2. define CARDS_H_INC
  1. include <deque>
  2. include <algorithm>
  3. include <ostream>
  4. include <iterator>

namespace cards {

 class card
 {
 public:
   enum pip_type { two, three, four, five, six, seven, eight, nine, ten,
                   jack, queen, king, ace };
   enum suite_type { hearts, spades, diamonds, clubs };
   // construct a card of a given suite and pip
   card(suite_type s, pip_type p): value(s + 4*p) {}
   // construct a card directly from its value
   card(unsigned char v = 0): value(v) {}
   // return the pip of the card
   pip_type pip() { return pip_type(value/4); }
   // return the suit of the card
   suite_type suite() { return suite_type(value%4); }
 private:
   // there are only 52 cards, therefore unsigned char suffices
   unsigned char value;
 };
 char const* const pip_names[] =
   { "two", "three", "four", "five", "six", "seven", "eight", "nine", "ten",
     "jack", "queen", "king", "ace" };
 // output a pip
 std::ostream& operator<<(std::ostream& os, card::pip_type pip)
 {
   return os << pip_names[pip];
 };
 char const* const suite_names[] =
   { "hearts", "spades", "diamonds", "clubs" };
 // output a suite
 std::ostream& operator<<(std::ostream& os, card::suite_type suite)
 {
   return os << suite_names[suite];
 }
 // output a card
 std::ostream& operator<<(std::ostream& os, card c)
 {
   return os << c.pip() << " of " << c.suite();
 }
 class deck
 {
 public:
   // default constructor: construct a default-ordered deck
   deck()
   {
     for (int i = 0; i < 52; ++i)
       cards.push_back(card(i));
   }
   // shuffle the deck
   void shuffle() { std::random_shuffle(cards.begin(), cards.end()); }
   // deal a card from the top
   card deal() { card c = cards.front(); cards.pop_front(); return c; }
   // iterators (only reading access is allowed)
   typedef std::deque<card>::const_iterator const_iterator;
   const_iterator begin() const { return cards.begin(); }
   const_iterator end() const { return cards.end(); }
 private:
   // the cards
   std::deque<card> cards;
 };
 // output the deck
 inline std::ostream& operator<<(std::ostream& os, deck const& d)
 {
   std::copy(d.begin(), d.end(), std::ostream_iterator<card>(os, "\n"));
   return os;
 }

}

  1. endif

</cpp>

D

Works with: D version 2.008+

The shuffle algorithm is simplified from Fisher-Yates shuffle The random number generator used is a better generator added at 2.008 release.
Added support for 'extra' card, for example, the Joker, or Major Arcana in Tarot. <d>module deck ; import std.random, std.string, std.algorithm, std.stdio ; import std.format : Format = format;

int maxlen(T)(T[] s) { return reduce!(max)(0, map!("a.length")(cast(T[])null,s)) ; }

template DCFG(string s, string p, string x, string c, string d) {

 static const string[] suits = mixin(s) ; 
 static const string[] pips = mixin(p) ;
 static const string[] extras = mixin(x) ;   
 static const string connect = c ;
 static const string dg = d ;
 const int fmtp = maxlen(pips), fmts = maxlen(suits) ;
 const int fmtall = max(fmtp + connect.length + fmts, maxlen(extras)) ;
   
 bool invalid(int p, int s) {
   return (!(p < pips.length && s >= 0 && s < suits.length) && 
     !(s == -1 &&  p - 1 < extras.length)) || p < 0 ;
 }
 string to_s(int p, int s) {
   auto fmt2 = Format("%%%ds", fmtall) ;
   if(s == -1) return Format(fmt2, extras[p - 1]) ;
   auto fmt1 = Format("%%%ds%s%%-%ds",fmtp, connect, fmts) ;
   return Format(fmt2, Format(fmt1, pips[p],suits[s])) ;
 }

}

class Card(alias D : DCFG) {

 const int NSuit = D.suits.length ;
 const int NPip = D.pips.length ;
 const int NExtra = D.extras.length ;
 
 const int pip, suit ; // suit == -1 for extra card
 this(int c) { if(c < 0) this(-c, -1) ;  else this(c % NPip, (c / NPip) % NSuit) ; }
 this(int p, int s) { 
   if(D.invalid(p,s)) throw new Exception("Invalid Card") ;
   pip = p ; suit = s ; 
 }
 string toString() { return D.to_s(pip, suit) ; }
 int order() { mixin(D.dg) ; }
 int opCmp(Card rhs) { return order - rhs.order ; }

}

class Deck(C) {

 alias Deck!(C) DK ;
 private C[] deck ;
 private Mt19937 rnd ; // A MersenneTwisterEngine Random Number Generator
 this(int pack = 1) {
   foreach(p ; 0..pack)
     foreach(int c; -C.NExtra..C.NPip*C.NSuit) addCard(new C(c)) ;
   rnd.seed(unpredictableSeed) ; // default unpredictable seed
 }
 DK addCard(C card) {deck ~= card ; return this ; }
 C peekCard(int deckLoc) { return deck[deckLoc] ; }
 DK dealCard(int deckLoc, Deck toDeck = null) {
   if(!(toDeck is null)) toDeck.addCard(deck[deckLoc]) ;// just discard if no target deck
   foreach(i ; deckLoc..deck.length - 1 ) deck[i] = deck[i+1] ;  // shift 
   deck.length = deck.length - 1 ;
   return this ;
 }
 DK dealTop(Deck toDeck = null) { return dealCard(deck.length - 1, toDeck) ; }
 DK showDeck() { writefln(this.toString) ; return this ; }
 int length() { return deck.length ; }
 string toString() { return Format("%s", deck) ; } 
 DK shuffle() { // Fisher-Yates shuffle algorithm, simplified
   for(int n = length ; n > 1 ; n--) swap(deck[uniform(rnd, 0, n)], deck[n - 1]) ;
   return this ;
 } 
 DK sortDeck() { std.algorithm.sort(deck) ; return this ; }

}

alias DCFG!( // It can be changed to a Tarot config, for example.

 `["Diamond", "Heart", "Club","Spade"]`,
 `["Ace","2","3","4","5","6","7","8","9","Ten","Jack","Queen","King"]`,
 `["*** Joker ***"]`,
 " of ",
 ` if(suit < 0) return suit*pip ;
   int p = pip == 0 ? NPip - 1 : pip - 1 ;
   return p*NSuit + suit ;`) Poker ;

alias Card!(Poker) GameCard ; alias Deck!(GameCard) GameDeck ;

void main() {

 GameDeck[9] guests ; 
 foreach(i,inout g ; guests) g = new GameDeck(0);
 
 GameDeck host = (new GameDeck).addCard(new GameCard(-1)). // add one more Joker
   showDeck.shuffle.showDeck ; // shuffle
 
 while(host.length > 0) 
   foreach(inout g ; guests) if(host.length > 0) host.dealTop(g) ; // deal cards
 foreach(g ; guests) g.sortDeck.showDeck ; // show decks

}</d>

Forth

Works with: GNU Forth
require random.fs   \ RANDOM ( n -- 0..n-1 ) is called CHOOSE in other Forths

create pips  s" A23456789TJQK" mem,
create suits s" DHCS"          mem, \ diamonds, hearts, clubs, spades
: .card ( c -- )
  13 /mod swap
  pips  + c@ emit
  suits + c@ emit ;

create deck 52 allot
variable dealt

: new-deck
  52 0        do i deck i + c!             loop  0 dealt ! ;
: .deck
  52 dealt @ ?do   deck i + c@ .card space loop  cr ;
: shuffle
  51 0 do
    52 i - random i + ( rand-index ) deck +
    deck i + c@  over c@
    deck i + c!  swap c!
  loop ;
: cards-left ( -- n ) 52 dealt @ - ;
: deal-card ( -- c )
  cards-left 0= abort" Deck empty!"
  deck dealt @ + c@  1 dealt +! ;
: .hand ( n -- )
  0 do deal-card .card space loop cr ;

new-deck shuffle .deck
5 .hand
cards-left .  \ 47

Fortran

Works with: Fortran version 90 and later
MODULE Cards

IMPLICIT NONE

  TYPE Card
    CHARACTER(5) :: value
    CHARACTER(8) :: suit
  END TYPE Card

  TYPE(Card) :: deck(52), hand(52)
  TYPE(Card) :: temp

  CHARACTER(5) :: pip(13) = (/"Two  ", "Three", "Four ", "Five ", "Six  ", "Seven", "Eight", "Nine ", "Ten  ", &
                              "Jack ", "Queen", "King ", "Ace  "/)
  CHARACTER(8) :: suits(4) = (/"Clubs   ", "Diamonds", "Hearts  ", "Spades  "/)
  INTEGER :: i, j, n, rand, dealt = 0
  REAL :: x

CONTAINS
 
  SUBROUTINE Init_deck
  ! Create deck
    DO i = 1, 4
      DO j = 1, 13
        deck((i-1)*13+j) = Card(pip(j), suits(i))
      END DO
    END DO
  END SUBROUTINE Init_deck
 
  SUBROUTINE Shuffle_deck
  ! Shuffle deck using Fisher-Yates algorithm
    DO i = 52-dealt, 1, -1
      CALL RANDOM_NUMBER(x)
      rand = INT(x * i) + 1
      temp = deck(rand)
      deck(rand) = deck(i)
      deck(i) = temp
    END DO
  END SUBROUTINE Shuffle_deck

  SUBROUTINE Deal_hand(number)
  ! Deal from deck to hand
    INTEGER :: number
    DO i = 1, number
      hand(i) = deck(dealt+1)
      dealt = dealt + 1
    END DO
  END SUBROUTINE

  SUBROUTINE Print_hand
  ! Print cards in hand
    DO i = 1, dealt
      WRITE (*, "(3A)") TRIM(deck(i)%value), " of ", TRIM(deck(i)%suit)
    END DO
    WRITE(*,*)
  END SUBROUTINE Print_hand
 
  SUBROUTINE Print_deck
  ! Print cards in deck
    DO i = dealt+1, 52
      WRITE (*, "(3A)") TRIM(deck(i)%value), " of ", TRIM(deck(i)%suit)
    END DO
    WRITE(*,*)
  END SUBROUTINE Print_deck

END MODULE Cards

Example use:

PROGRAM Playing_Cards
 
  USE Cards
 
  CALL Init_deck
  CALL Shuffle_deck
  CALL Deal_hand(5)
  CALL Print_hand
  CALL Print_deck
  
END PROGRAM

This creates a new deck, shuffles it, deals five cards to hand, prints the cards in hand and then prints the cards remaining in the deck.

Haskell

Straightforward implementation with explicit names for pips and suits. A deck is just a list of cards. Dealing consists of splitting off cards from the beginning of the list by the usual pattern matching (not shown). Printing is automatic. Purely functional shuffling is a bit tricky, so here we just do the naive quadratic version. This also works for other than full decks.

import System.Random

data Pip = Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten | 
           Jack | Queen | King | Ace 
  deriving (Ord, Enum, Bounded, Eq, Show)

data Suit = Diamonds | Spades | Hearts | Clubs
  deriving (Ord, Enum, Bounded, Eq, Show)

type Card = (Pip, Suit)

fullRange :: (Bounded a, Enum a) => [a]
fullRange = [minBound..maxBound]

fullDeck :: [Card]
fullDeck = [(pip, suit) | pip <- fullRange, suit <- fullRange]

insertAt :: Int -> a -> [a] -> [a]
insertAt 0 x ys     = x:ys
insertAt n _ []     = error "insertAt: list too short"
insertAt n x (y:ys) = y : insertAt (n-1) x ys

shuffle :: RandomGen g => g -> [a] -> [a]
shuffle g xs = shuffle' g xs 0 [] where
  shuffle' g []     _ ys = ys
  shuffle' g (x:xs) n ys = shuffle' g' xs (n+1) (insertAt k x ys) where
    (k,g') = randomR (0,n) g

J

Note 'playingcards.ijs'
This is a class script.
Multiple decks may be used, one for each instance of this class.
)

coclass 'rcpc'   NB. Rosetta Code playing cards class

create=: 3 : 0
 N0=: > ;:'Ace Two Three Four Five Six Seven Eight Nine Ten Jack Queen King'
 N1=: > ;:'Spades Hearts Diamonds Clubs'
 DeckPrototype=: |. ,/(i.#N0),."1 0 i.#N1
 sayCards=: ((N0{~{.),' of ',(N1{~{:))"1
 startNewDeck''
)

destroy=: codestroy

startNewDeck=: 3 : 0
 1: TheDeck=: DeckPrototype
)

shuffle=: 3 : 0
 1: TheDeck=: TheDeck {~ ?~ # TheDeck
)

dealCards=: 3 : 0
 {. 1 dealCards y
:
 assert. (# TheDeck) >: ToBeDealt=. x*y
 CardsOffTop=. ToBeDealt {. TheDeck
 TheDeck    =: ToBeDealt }. TheDeck
 (1 0 2)|:(y,x)$ CardsOffTop
)
Note 'dealCards'
Left parameter (x) is number of players, with default to one.
Right parameter (y) is number of cards to be dealt to each player.
Used monadically, the player-axis is omitted from output.
)

pcc=: 3 : 0   NB. "Print" current contents of the deck.
 sayCards TheDeck
)

Example use:

   load 'coutil'
   load 'c:\documents and settings\user_name\j602-user\playingcards.ijs'
   pc=: '' conew 'rcpc'
   $TheDeck__pc
52 2
   shuffle__pc''
1
   sayCards__pc 2 dealCards__pc 5   NB. deal two hands of five cards
Nine  of Hearts  
Three of Clubs   
Seven of Clubs   
Ten   of Hearts  
Three of Diamonds

Seven of Diamonds
Nine  of Spades  
King  of Diamonds
Queen of Hearts  
Six   of Clubs   
   $TheDeck__pc   NB. deck size has been reduced by the ten cards dealt
42 2
   destroy__pc ''
1

Java

Works with: Java version 1.5+

<java>public enum Pip { Two, Three, Four, Five, Six, Seven,

   Eight, Nine, Ten, Jack, Queen, King, Ace }</java>

<java>public enum Suit { Diamonds, Spades, Hearts, Clubs }</java>

The card: <java>public class Card {

   private final Suit suit;
   private final Pip value;
   public Card(Suit s, Pip v) {
       suit = s;
       value = v;
   }
   public String toString() {
       return value + " of " + suit;
   }

}</java> The deck: <java>import java.util.Collections; import java.util.LinkedList;

public class Deck {

   private final LinkedList<Card> deck= new LinkedList<Card>();
   public Deck() {
       for (Suit s : Suit.values())
           for (Pip v : Pip.values())
               deck.add(new Card(s, v));
   }
   public Card deal() {
       return deck.poll();
   }
   public void shuffle() {
       Collections.shuffle(deck); // I'm such a cheater
   }
   public String toString(){
       return deck.toString();
   }

}</java>

OCaml

Straightforward implementation with algebraic types for the pips and suits, and lists of their values. A deck is an array of cards. <ocaml>type pip = Two | Three | Four | Five | Six | Seven | Eight | Nine | Ten |

          Jack | Queen | King | Ace 

let pips = [Two; Three; Four; Five; Six; Seven; Eight; Nine; Ten;

           Jack; Queen; King; Ace]

type suit = Diamonds | Spades | Hearts | Clubs let suits = [Diamonds; Spades; Hearts; Clubs]

type card = pip * suit

let full_deck = Array.of_list (List.concat (List.map (fun pip -> List.map (fun suit -> (pip, suit)) suits) pips))

(* Fisher-Yates shuffle *) let shuffle deck =

 for i = Array.length deck - 1 downto 1 do
   let j = Random.int (i+1) in
   (* swap deck.(i) and deck.(j) *)
   let temp = deck.(i) in
   deck.(i) <- deck.(j);
   deck.(j) <- temp
 done</ocaml>

Python

<python>import random

class Card(object):

   suits = ("Clubs","Hearts","Spades","Diamonds")
   pips = ("2","3","4","5","6","7","8","9","10","Jack","Queen","King","Ace")
   def __init__(self, pip,suit):
       self.pip=pip
       self.suit=suit
   def __str__(self):
       return "%s %s"%(self.pip,self.suit)

class Deck(object):

   def __init__(self):
       self.deck = [Card(pip,suit) for suit in Card.suits for pip in Card.pips]
   def __str__(self):
       return "[%s]"%", ".join( (str(card) for card in self.deck))
   def shuffle(self):
       random.shuffle(self.deck)
   def deal(self):
       self.shuffle()  # Can't tell what is next from self.deck
       return self.deck.pop(0)

</python>

Perl

<perl>package Playing_Card_Deck;

use strict;

@Playing_Card_Deck::suits = qw

  [Diamonds Clubs Hearts Spades];

@Playing_Card_Deck::pips = qw

  [Two Three Four Five Six Seven Eight Nine Ten
   Jack King Queen Ace];
  1. I choose to fully qualify these names rather than declare them
  2. with "our" to keep them from escaping into the scope of other
  3. packages in the same file. Another possible solution is to use
  4. "our" or "my", but to enclose this entire package in a bare block.

sub new

  1. Creates a new deck-object. The cards are initially neatly ordered.
{my $invocant = shift;
 my $class = ref($invocant) || $invocant;
 my @cards = ();
 foreach my $suit (@Playing_Card_Deck::suits)
    {foreach my $pip (@Playing_Card_Deck::pips)
        {push(@cards, {suit => $suit, pip => $pip});}}
 return bless([@cards], $class);}

sub deal

  1. Removes the top card of the given deck and returns it as a hash
  2. with the keys "suit" and "pip".
{return %{ shift( @{shift(@_)} ) };}

sub shuffle

  1. Randomly permutes the cards in the deck. It uses the algorithm
  2. described at:
  3. http://en.wikipedia.org/wiki/Fisher-Yates_shuffle#The_modern_algorithm
{our @deck; local *deck = shift;
   # @deck is now an alias of the invocant's referent.
 for (my $n = $#deck ; $n ; --$n)
    {my $k = int rand($n + 1);
     @deck[$k, $n] = @deck[$n, $k] if $k != $n;}}

sub print_cards

  1. Prints out a description of every card in the deck, in order.
{print "$_->{pip} of $_->{suit}\n" foreach @{shift(@_)};}</perl>

Some examples of use: <perl>my $deck = new Playing_Card_Deck; $deck->shuffle; my %card = $deck->deal; print uc("$card{pip} OF $card{suit}\n"); $deck->print_cards;</perl> This creates a new deck, shuffles it, removes the top card, prints out that card's name in all caps, and then prints the rest of the deck.