Stack

From Rosetta Code
Task
Stack
You are encouraged to solve this task according to the task description, using any language you may know.

Data Structure
This illustrates a data structure, a means of storing data within a program.

You may see other such structures in the Data Structures category.

A stack is a container of elements with   last in, first out   access policy.   Sometimes it also called LIFO.

The stack is accessed through its top.

The basic stack operations are:

  •   push   stores a new element onto the stack top;
  •   pop   returns the last pushed stack element, while removing it from the stack;
  •   empty   tests if the stack contains no elements.


Sometimes the last pushed stack element is made accessible for immutable access (for read) or mutable access (for write):

  •   top   (sometimes called peek to keep with the p theme) returns the topmost element without modifying the stack.


Stacks allow a very simple hardware implementation.

They are common in almost all processors.

In programming, stacks are also very popular for their way (LIFO) of resource management, usually memory.

Nested scopes of language objects are naturally implemented by a stack (sometimes by multiple stacks).

This is a classical way to implement local variables of a re-entrant or recursive subprogram. Stacks are also used to describe a formal computational framework.

See stack machine.

Many algorithms in pattern matching, compiler construction (e.g. recursive descent parsers), and machine learning (e.g. based on tree traversal) have a natural representation in terms of stacks.


Task

Create a stack supporting the basic operations: push, pop, empty.


See also



11l

Translation of: Crystal
[Int] stack

L(i) 1..10
   stack.append(i)

L 10
   print(stack.pop())
Output:
10
9
8
7
6
5
4
3
2
1

6502 Assembly

The 6502 has a built-in stack, which is located at memory addresses $0100-$01FF. The first thing most boot ROMs will do is set the stack to equal $FF. Only the X register can interact with the stack pointer's value directly, and it does so using TSX (transfer stack to X) and TXS (transfer X to stack.) Each push will decrement S by 1 and write that byte to the stack memory. On the original 6502, only the accumulator could be pushed to the stack, so programs running on those CPUs would often use sequences such as TXA PHA and TYA PHA to save the X and Y registers. This had the nasty habit of destroying the accumulator, which made saving these registers difficult. Fortunately, the 65c02 and its later revisions can push/pop X and Y directly without having to go through the accumulator first.

Push:

PHA

Pop:

PLA

Empty:

TSX
CPX $FF
BEQ stackEmpty

Peek:

TSX
LDA $0101,x

68000 Assembly

The 68000 is well-suited to stack data structures. Register A7 contains the stack pointer, however any address register can be used for a similar purpose. Any register from A0-A6 can be pointed to work RAM and used as a stack.

Push

You can push the contents of one or more variables.

LEA userStack,A0                        ;initialize the user stack, points to a memory address in user RAM. Only do this once!
MOVEM.L D0-D3,-(A0)   ;moves the full 32 bits of registers D0,D1,D2,D3 into the address pointed by A0, with pre-decrement

Unlike the "true" stack (A7), you can push a single byte onto the user stack and it won't get automatically padded with a trailing null byte.

Pop

The pop is just a reverse push.

MOVEM.L (A0)+,D0-D3 ;returns the four longs stored in the stack back to where they came from.

Empty

The stack is empty if and only if the stack pointer equals its initialized value. This is only true provided you have never adjusted the stack pointer except by pushing and popping.

CMPA.L #userStack,A0
BEQ StackIsEmpty

Manually adjusting the stack

You can offset the user stack (and the real stack) as follows:

LEA (4,SP),SP ;does the same thing to the stack as popping 4 bytes, except those bytes are not retrieved.

Peek

If you know the intended length of the last item on the stack (1, 2, or 4 bytes), you can load it into memory without popping it. This applies to both the real stack and a user stack you may have created. Since this operation doesn't alter the value of the stack pointer, you don't have to worry about misaligning the stack, but the value you peek at should be of the correct size or you'll be "peeking" at more than one item at the same time.

MOVE.W (SP),D0 ;load the top two bytes of the stack into D0
MOVE.W (A0),D0 ;load the top two bytes of A0 into D0

8086 Assembly

The 8086's hardware stack is very similar to that of Z80 Assembly. This is no coincidence, as the Z80 was based on the predecessor to the 8086.

push ax ;push ax onto the stack
pop ax  ; pop the top two bytes of the stack into ax

The "high" byte is pushed first, then the low byte. Popping does the opposite.

Depending on your assembler, the stack's initial value may be set using the .stack directive.

Like the Z80, the 8086 can only push or pop 2 bytes at a time. It's not possible to push AH without pushing AL alongside it. The stack can be used to exchange values of registers that even the XCHG command can't work with. This is done by deliberately pushing two registers and popping them in the "wrong" order.

The easiest way to "peek" is to pop then push that same register again.

;get the top item of the stack
pop ax
push ax

The stack need not be accessed using these push and pop commands, it can also be read like any other area of memory. This is actually how C programs store and recall local variables and function arguments.


ABAP

This works for ABAP Version 7.40 and above

report z_stack.

interface stack.
  methods:
    push
      importing
        new_element      type any
      returning
        value(new_stack) type ref to stack,

    pop
      exporting
        top_element      type any
      returning
        value(new_stack) type ref to stack,

    empty
      returning
        value(is_empty) type abap_bool,

    peek
      exporting
        top_element type any,

    get_size
      returning
        value(size) type int4,

    stringify
      returning
        value(stringified_stack) type string.
endinterface.


class character_stack definition.
  public section.
    interfaces:
      stack.


    methods:
      constructor
        importing
          characters type string optional.


  private section.
    data:
      characters type string.
endclass.


class character_stack implementation.
  method stack~push.
    characters = |{ new_element }{ characters }|.

    new_stack = me.
  endmethod.


  method stack~pop.
    if not me->stack~empty( ).
      top_element = me->characters(1).

      me->characters = me->characters+1.
    endif.

    new_stack = me.
  endmethod.


  method stack~empty.
    is_empty = xsdbool( strlen( me->characters ) eq 0 ).
  endmethod.


  method stack~peek.
    check not me->stack~empty( ).

    top_element = me->characters(1).
  endmethod.


  method stack~get_size.
    size = strlen( me->characters ).
  endmethod.


  method stack~stringify.
    stringified_stack = cond string(
      when me->stack~empty( )
      then `empty`
      else me->characters ).
  endmethod.


  method constructor.
    check characters is not initial.

    me->characters = characters.
  endmethod.
endclass.


class integer_stack definition.
  public section.
    interfaces:
      stack.


    methods:
      constructor
        importing
          integers type int4_table optional.


  private section.
    data:
      integers type int4_table.
endclass.


class integer_stack implementation.
  method stack~push.
    append new_element to me->integers.

    new_stack = me.
  endmethod.


  method stack~pop.
    if not me->stack~empty( ).
      top_element = me->integers[ me->stack~get_size( ) ].

      delete me->integers index me->stack~get_size( ).
    endif.

    new_stack = me.
  endmethod.


  method stack~empty.
    is_empty = xsdbool( lines( me->integers ) eq 0 ).
  endmethod.


  method stack~peek.
    check not me->stack~empty( ).

    top_element = me->integers[ lines( me->integers ) ].
  endmethod.


  method stack~get_size.
    size = lines( me->integers ).
  endmethod.


  method stack~stringify.
    stringified_stack = cond string(
      when me->stack~empty( )
      then `empty`
      else reduce string(
        init stack = ``
        for integer in me->integers
        next stack = |{ integer }{ stack }| ) ).
  endmethod.


  method constructor.
    check integers is not initial.

    me->integers = integers.
  endmethod.
endclass.


start-of-selection.
  data:
    stack1        type ref to stack,
    stack2        type ref to stack,
    stack3        type ref to stack,

    top_character type char1,
    top_integer   type int4.

  stack1 = new character_stack( ).
  stack2 = new integer_stack( ).
  stack3 = new integer_stack( ).

  write: |Stack1 = { stack1->stringify( ) }|, /.
  stack1->push( 'a' )->push( 'b' )->push( 'c' )->push( 'd' ).
  write: |push a, push b, push c, push d -> Stack1 = { stack1->stringify( ) }|, /.
  stack1->pop( )->pop( importing top_element = top_character ).
  write: |pop, pop and return element -> { top_character }, Stack1 = { stack1->stringify( ) }|, /, /.

  write: |Stack2 = { stack2->stringify( ) }|, /.
  stack2->push( 1 )->push( 2 )->push( 3 )->push( 4 ).
  write: |push 1, push 2, push 3, push 4 -> Stack2 = { stack2->stringify( ) }|, /.
  stack2->pop( )->pop( importing top_element = top_integer ).
  write: |pop, pop and return element -> { top_integer }, Stack2 = { stack2->stringify( ) }|, /, /.

  write: |Stack3 = { stack3->stringify( ) }|, /.
  stack3->pop( ).
  write: |pop -> Stack3 = { stack3->stringify( ) }|, /, /.
Output:
Stack1 = empty

push a, push b, push c, push d -> Stack1 = dcba

pop, pop and return element -> c, Stack1 = ba


Stack2 = empty

push 1, push 2, push 3, push 4 -> Stack2 = 4321

pop, pop and return element -> 3, Stack2 = 21


Stack3 = empty

pop -> Stack3 = empty

Action!

Static memory

DEFINE MAXSIZE="200"
BYTE ARRAY stack(MAXSIZE)
BYTE stacksize=[0]

BYTE FUNC IsEmpty()
  IF stacksize=0 THEN
    RETURN (1)
  FI
RETURN (0)

PROC Push(BYTE v)
  IF stacksize=maxsize THEN
    PrintE("Error: stack is full!")
    Break()
  FI
  stack(stacksize)=v
  stacksize==+1
RETURN

BYTE FUNC Pop()
  IF IsEmpty() THEN
    PrintE("Error: stack is empty!")
    Break()
  FI
  stacksize==-1
RETURN (stack(stacksize))

PROC TestIsEmpty()
  IF IsEmpty() THEN
    PrintE("Stack is empty")
  ELSE
    PrintE("Stack is not empty")
  FI
RETURN

PROC TestPush(BYTE v)
  PrintF("Push: %B%E",v)
  Push(v)
RETURN

PROC TestPop()
  BYTE v

  Print("Pop: ")
  v=Pop()
  PrintBE(v)
RETURN

PROC Main()
  TestIsEmpty()
  TestPush(10)
  TestIsEmpty()
  TestPush(31)
  TestPop()
  TestIsEmpty()
  TestPush(5)
  TestPop()
  TestPop()
  TestPop()
RETURN

Dynamic memory

The user must type in the monitor the following command after compilation and before running the program!
SET EndProg=*
CARD EndProg ;required for ALLOCATE.ACT

INCLUDE "D2:ALLOCATE.ACT" ;from the Action! Tool Kit. You must type 'SET EndProg=*' from the monitor after compiling, but before running this program!

DEFINE PTR="CARD"
DEFINE NODE_SIZE="3"
TYPE StackNode=[BYTE data PTR nxt]

StackNode POINTER stack

BYTE FUNC IsEmpty()
  IF stack=0 THEN
    RETURN (1)
  FI
RETURN (0)

PROC Push(BYTE v)
  StackNode POINTER node

  node=Alloc(NODE_SIZE)
  node.data=v
  node.nxt=stack
  stack=node
RETURN

BYTE FUNC Pop()
  StackNode POINTER node
  BYTE v
  
  IF IsEmpty() THEN
    PrintE("Error stack is empty!")
    Break()
  FI

  node=stack
  v=node.data
  stack=node.nxt
  Free(node,NODE_SIZE)
RETURN (v)

PROC TestIsEmpty()
  IF IsEmpty() THEN
    PrintE("Stack is empty")
  ELSE
    PrintE("Stack is not empty")
  FI
RETURN

PROC TestPush(BYTE v)
  PrintF("Push: %B%E",v)
  Push(v)
RETURN

PROC TestPop()
  BYTE v

  Print("Pop: ")
  v=Pop()
  PrintBE(v)
RETURN

PROC Main()
  AllocInit(0)
  stack=0

  Put(125) PutE() ;clear screen

  TestIsEmpty()
  TestPush(10)
  TestIsEmpty()
  TestPush(31)
  TestPop()
  TestIsEmpty()
  TestPush(5)
  TestPop()
  TestPop()
  TestPop()
RETURN
Output:

Error at the end of program is intentional.

Screenshot from Atari 8-bit computer

Stack is empty
Push: 10
Stack is not empty
Push: 31
Pop: 31
Stack is not empty
Push: 5
Pop: 5
Pop: 10
Pop: Error: stack is empty!

RETURN
Error: 128

ActionScript

In ActionScript an Array object provides stack functionality.

var stack:Array = new Array();
stack.push(1);
stack.push(2);
trace(stack.pop()); // outputs "2"
trace(stack.pop()); // outputs "1"

Ada

This is a generic stack implementation.

generic
   type Element_Type is private; 
package Generic_Stack is
   type Stack is private; 
   procedure Push (Item : Element_Type; Onto : in out Stack); 
   procedure Pop (Item : out Element_Type; From : in out Stack); 
   function Create return Stack;
   Stack_Empty_Error : exception;
private
   type Node; 
   type Stack is access Node; 
   type Node is record 
      Element : Element_Type;  
      Next    : Stack        := null;  
   end record; 
end Generic_Stack;
with Ada.Unchecked_Deallocation;

package body Generic_Stack is
   
   ------------
   -- Create --
   ------------
   
   function Create return Stack is
   begin
      return (null);
   end Create;

   ----------
   -- Push --
   ----------

   procedure Push(Item : Element_Type; Onto : in out Stack) is
      Temp : Stack := new Node;
   begin
      Temp.Element := Item;
      Temp.Next := Onto;
      Onto := Temp; 
   end Push;

   ---------
   -- Pop --
   ---------

   procedure Pop(Item : out Element_Type; From : in out Stack) is
      procedure Free is new Ada.Unchecked_Deallocation(Node, Stack);
      Temp : Stack := From;
   begin
      if Temp = null then
         raise Stack_Empty_Error;
      end if;
      Item := Temp.Element;
      From := Temp.Next;
      Free(Temp);
   end Pop;

end Generic_Stack;

ALGOL 68

ALGOL 68: Using linked list

ALGOL 68 uses "HEAP" variables for new LINKs in a linked list. Generally ALGOL 68's garbage collector should recover the LINK memory some time after a value is popped.

Works with: ALGOL 68 version Revision 1 - one extension to language used - PRAGMA READ - a non standard feature similar to C's #include directive.
Works with: ALGOL 68G version Any - tested with release algol68g-2.7.
File: prelude/next_link.a68
# -*- coding: utf-8 -*- #
CO REQUIRES:
  MODE OBJVALUE = ~ # Mode/type of actual obj to be stacked #
END CO

MODE OBJNEXTLINK = STRUCT(
  REF OBJNEXTLINK next,
  OBJVALUE value # ... etc. required #
);

PROC obj nextlink new = REF OBJNEXTLINK:
  HEAP OBJNEXTLINK;

PROC obj nextlink free = (REF OBJNEXTLINK free)VOID:
  next OF free := obj stack empty # give the garbage collector a BIG hint #
File: prelude/stack_base.a68
# -*- coding: utf-8 -*- #
CO REQUIRES:
  MODE OBJNEXTLINK = STRUCT(
    REF OBJNEXTLINK next,
    OBJVALUE value
  );
  PROC obj nextlink new = REF OBJNEXTLINK: ~,
  PROC obj nextlink free = (REF OBJNEXTLINK free)VOID: ~
END CO

# actually a pointer to the last LINK, there ITEMs are ADDED, pushed & popped #
MODE OBJSTACK = REF OBJNEXTLINK; 

OBJSTACK obj stack empty = NIL;

BOOL obj stack par = FALSE; # make code thread safe #
SEMA obj stack sema = LEVEL ABS obj stack par;
# Warning: 1 SEMA for all stacks of type obj, i.e. not 1 SEMA per stack #

PROC obj stack init = (REF OBJSTACK self)REF OBJSTACK:
  self := obj stack empty;

# see if the program/coder wants the OBJ problem mended... #
PROC (REF OBJSTACK #self#)BOOL obj stack index error mended
  := (REF OBJSTACK self)BOOL: (abend("obj stack index error"); stop);

PROC on obj stack index error = (REF OBJSTACK self, PROC(REF OBJSTACK #self#)BOOL mended)VOID:
  obj stack index error mended := mended;

PROC obj stack push = (REF OBJSTACK self, OBJVALUE obj)REF OBJSTACK:(
  IF obj stack par THEN DOWN obj stack sema FI;
  self := obj nextlink new := (self, obj);
  IF obj stack par THEN UP obj stack sema FI;
  self
);

# aliases: define a useful put (+=:) operator... #
OP +=: = (OBJVALUE obj, REF OBJSTACK self)REF OBJSTACK: obj stack push(self, obj);

PROC obj stack pop = (REF OBJSTACK self)OBJVALUE: (
# DOWN obj stack sema; #
  IF self IS obj stack empty THEN
    IF NOT obj stack index error mended(self) THEN abend("obj stack index error") FI FI;

  OBJNEXTLINK old head := self;
  OBJSTACK new head := next OF self;
  OBJVALUE out := value OF old head;
  obj nextlink free(old head); # freeing nextlink, NOT queue! #
  self := new head;
#;UP obj stack sema; #
  out
);

PROC obj stack is empty = (REF OBJSTACK self)BOOL:
  self IS obj stack empty;

SKIP
File: test/data_stigler_diet.a68
# -*- coding: utf-8 -*- #
MODE DIETITEM = STRUCT(
  STRING food, annual quantity, units, REAL cost
);

# Stigler's 1939 Diet ... #
FORMAT diet item fmt = $g": "g" "g" = $"zd.dd$;
[]DIETITEM stigler diet = (
  ("Cabbage",           "111","lb.",  4.11),
  ("Dried Navy Beans",  "285","lb.", 16.80),
  ("Evaporated Milk",    "57","cans", 3.84),
  ("Spinach",            "23","lb.",  1.85),
  ("Wheat Flour",       "370","lb.", 13.33),
  ("Total Annual Cost",    "","",    39.93)
)
File: test/stack.a68
#!/usr/bin/a68g --script #
# -*- coding: utf-8 -*- #

MODE OBJVALUE = DIETITEM;
PR read "prelude/next_link.a68" PR;
PR read "prelude/stack_base.a68" PR;

PR read "test/data_stigler_diet.a68" PR;
OBJSTACK example stack; obj stack init(example stack);

FOR i TO UPB stigler diet DO
#  obj stack push(example stack, stigler diet[i]) #
  stigler diet[i] +=: example stack
OD;

printf($"Items popped in reverse:"l$);
WHILE NOT obj stack is empty(example stack) DO
# OR example stack ISNT obj stack empty #
  printf((diet item fmt, obj stack pop(example stack), $l$))
OD
Output:
Items popped in reverse:
Total Annual Cost:   = $39.93
Wheat Flour: 370 lb. = $13.33
Spinach: 23 lb. = $ 1.85
Evaporated Milk: 57 cans = $ 3.84
Dried Navy Beans: 285 lb. = $16.80
Cabbage: 111 lb. = $ 4.11

See also: Queue

ALGOL 68: Using FLEX array

An alternative to using a linked list is to use a FLEX array.

MODE DIETITEM = STRUCT (
  STRING food, annual quantity, units, REAL cost
);
 
MODE OBJVALUE = DIETITEM;

# PUSH element to stack #
OP +:= = (REF FLEX[]OBJVALUE stack, OBJVALUE item) VOID:
   BEGIN
      FLEX[UPB stack + 1]OBJVALUE newstack;
      newstack[2:UPB newstack] := stack;
      newstack[1] := item;
      stack := newstack
   END;

OP POP = (REF FLEX[]OBJVALUE stack) OBJVALUE:
   IF UPB stack > 0 THEN
      OBJVALUE result = stack[1];
      stack := stack[2:UPB stack];
      result
   ELSE
      # raise index error; # SKIP 
   FI;

# Stigler's 1939 Diet ... #
FORMAT diet item fmt = $g": "g" "g" = $"zd.dd$;
[]DIETITEM stigler diet = (
  ("Cabbage",           "111","lb.",  4.11),
  ("Dried Navy Beans",  "285","lb.", 16.80),
  ("Evaporated Milk",    "57","cans", 3.84),
  ("Spinach",            "23","lb.",  1.85),
  ("Wheat Flour",       "370","lb.", 13.33),
  ("Total Annual Cost",    "","",    39.93)
);

FLEX[0]DIETITEM example stack;
 
FOR i TO UPB stigler diet DO
   example stack +:= stigler diet[i]
OD;
 
printf($"Items popped in reverse:"l$);
WHILE UPB example stack > 0 DO
  printf((diet item fmt, POP example stack, $l$))
OD
Output:
Items popped in reverse:
Total Annual Cost:   = $39.93
Wheat Flour: 370 lb. = $13.33
Spinach: 23 lb. = $ 1.85
Evaporated Milk: 57 cans = $ 3.84
Dried Navy Beans: 285 lb. = $16.80
Cabbage: 111 lb. = $ 4.11

ALGOL W

begin
    % define a Stack type that will hold StringStackElements     %
    % and the StringStackElement type                            %
    % we would need separate types for other element types       %
    record StringStack ( reference(StringStackElement) top );
    record StringStackElement ( string(8)                     element
                              ; reference(StringStackElement) next
                              );
    % adds e to the end of the StringStack s                     %
    procedure pushString ( reference(StringStack) value s
                         ; string(8)              value e
                         ) ;
        top(s) := StringStackElement( e, top(s) );
    % removes and returns the top element from the StringStack s %
    % asserts the Stack is not empty, which will stop the        %
    % program if it is                                           %
    string(8) procedure popString ( reference(StringStack) value s ) ;
    begin
        string(8) v;
        assert( not isEmptyStringStack( s ) );
        v     := element(top(s));
        top(s):= next(top(s));
        v
    end popStringStack ;
    % returns the top element of the StringStack s               %
    % asserts the Stack is not empty, which will stop the        %
    % program if it is                                           %
    string(8) procedure peekStringStack ( reference(StringStack) value s ) ;
    begin
        assert( not isEmptyStringStack( s ) );
        element(top(s))
    end popStringStack ;
    % returns true if the StringStack s is empty, false otherwise %
    logical procedure isEmptyStringStack ( reference(StringStack) value s ) ; top(s) = null;
 
    begin % test the StringStack operations %
        reference(StringStack) s;
        s := StringStack( null );
        pushString( s, "up"      );
        pushString( s, "down"    );
        pushString( s, "strange" );
        pushString( s, "charm"   );
        while not isEmptyStringStack( s ) do write( popString( s )
                                                  , if isEmptyStringStack( s ) then "(empty)"
                                                                               else peekStringStack( s )
                                                  )
    end
end.
Output:
charm   strange
strange down
down    up
up      (empty)

Applesoft BASIC

100  DIM STACK$(1000)
110  DATA "(2*A)","PI","","TO BE OR","NOT TO BE"
120  FOR I = 1 TO 5
130  READ ELEMENT$
140  GOSUB 500_PUSH
150  NEXT 
200  GOSUB 400 POP  AND  PRINT 
210  GOSUB 300_EMPTY AND  PRINT 
220  FOR I = 1 TO 4
230  GOSUB 400 POP  AND  PRINT 
240  NEXT 
250  GOSUB 300_EMPTY AND  PRINT 
260  END 
300  GOSUB 700_EMPTY
310  PRINT "STACK IS ";
320  IF  NOT EMPTY THEN  PRINT "NOT ";
330  PRINT "EMPTY"
340  RETURN 
400  GOSUB 600 POP 
410  PRINT ELEMENT$
420  RETURN 
500  REM 
510  REM PUSH
520  REM 
530  LET STACK$(SP) = ELEMENT$
540  LET SP = SP + 1
550  RETURN 
600  REM 
610  REM POP
620  REM 
630  IF SP THEN SP = SP - 1
640  LET ELEMENT$ = STACK$(SP)
650  LET STACK$(SP) = ""
660  RETURN 
700  REM 
710  REM EMPTY
720  REM 
730  LET EMPTY = SP = 0
740  RETURN
Output:
NOT TO BE
STACK IS NOT EMPTY
TO BE OR

PI
(2*A)
STACK IS EMPTY

ARM Assembly

The stack is held in register 13, or r13 but more commonly referred to as SP for clarity.

Pushing and popping multiple values is very similar to 68000 Assembly.

STMFD sp!,{r0-r12,lr} ;push r0 thru r12 and the link register
LDMFD sp!,{r0-r12,pc} ;pop r0 thru r12, and the value that was in the link register is put into the program counter. 
                      ;This acts as a pop and return command all-in-one. (Most programs use bx lr to return.)

Like in 68000 Assembly, you are not limited to using SP as the source/destination for these commands; any register can fulfill that role. If you wish to have multiple stacks, then so be it.

The stack pointer will work with any operation the other registers can. As such, a peek can be done by using an LDR with the stack pointer as the address register:

LDR r0,[sp] ;load the top of the stack into r0

The order in which registers are pushed/popped is always the same, no matter which order you list the registers in your source code. If you want to push some registers and purposefully pop them into different registers, you'll need to push/pop them separately.

A check if the stack is empty is also very simple, provided the initial value of the stack pointer was saved at the start of the program, or (more likely) was loaded from a nearby memory location.

;this example uses VASM syntax which considers a "word" to be 16-bit regardless of the architecture
InitStackPointer:    .long 0x3FFFFFFF   ;other assemblers would call this a "word"

MOV R1,#InitStackPointer
LDR SP,[R1]  ;set up the stack pointer
LDR R2,[R1]  ;also load it into R2
;There's no point in checking since we haven't pushed/popped anything but just for demonstration purposes we'll check now
CMP SP,R2
BEQ StackIsEmpty

In THUMB mode, the PUSH and POP commands replace STMFD and LDMFD. They work in a similar fashion, but are limited to just the stack unlike the real STMFD and LDMFD commands which can use any register as the "stack pointer."

Arturo

Stack: $[]-> []

pushTo:     function [st val]-> 'st ++ val
popStack:   function [st]     [
    result: last st
    remove 'st .index (size st)-1 
    return result
]
emptyStack: function [st]-> empty 'st
printStack: function [st]-> print st

st: new Stack

pushTo st "one"
pushTo st "two"
pushTo st "three"
printStack st

print popStack st
printStack st

emptyStack st
print ["finally:" st]
Output:
one two three 
three
one two 
finally: []

ATS

(* Stacks implemented as linked lists. *)

(* A nonlinear stack type of size n, which is good for when you are
   using a garbage collector or can let the memory leak. *)
typedef stack_t (t : t@ype+, n : int) = list (t, n)
typedef stack_t (t : t@ype+) = [n : int] stack_t (t, n)

(* A linear stack type of size n, which requires (and will enforce)
   explicit freeing. (Note that a "peek" function for a linear stack
   is a complicated topic. But the task avoids this issue.) *)
viewtypedef stack_vt (vt : vt@ype+, n : int) = list_vt (vt, n)
viewtypedef stack_vt (vt : vt@ype+) = [n : int] stack_vt (vt, n)

(* Proof that a given nonlinear stack does not have a nonnegative
   size. *)
prfn
lemma_stack_t_param {n : int} {t : t@ype}
                    (stack : stack_t (t, n)) :<prf>
    [0 <= n] void =
  lemma_list_param stack

(* Proof that a given linear stack does not have a nonnegative
   size. *)
prfn
lemma_stack_vt_param {n : int} {vt : vt@ype}
                     (stack : !stack_vt (vt, n)) :<prf>
    [0 <= n] void =
  lemma_list_vt_param stack

(* Create an empty nonlinear stack. *)
fn {}
stack_t_nil {t : t@ype} () :<> stack_t (t, 0) =
  list_nil ()

(* Create an empty linear stack. *)
fn {}
stack_vt_nil {vt : vt@ype} () :<> stack_vt (vt, 0) =
  list_vt_nil ()

(* Is a nonlinear stack empty? *)
fn {}
stack_t_is_empty {n : int} {t : t@ype}
                 (stack : stack_t (t, n)) :<>
    [empty : bool | empty == (n == 0)]
    bool empty =
  case+ stack of
  | list_nil _ => true
  | list_cons _ => false

(* Is a linear stack empty? *)
fn {}
stack_vt_is_empty {n : int} {vt : vt@ype}
                  (* ! = pass by value; stack is preserved. *)
                  (stack : !stack_vt (vt, n)) :<>
    [empty : bool | empty == (n == 0)]
    bool empty =
  case+ stack of
  | list_vt_nil _ => true
  | list_vt_cons _ => false

(* Push to a nonlinear stack that is stored in a variable. *)
fn {t : t@ype}
stack_t_push {n : int}
             (stack : &stack_t (t, n) >> stack_t (t, m),
              x     : t) :<!wrt>
    (* It is proved that the stack is raised one higher. *)
    #[m : int | 1 <= m; m == n + 1]
    void =
  let
    prval _ = lemma_stack_t_param stack
    prval _ = prop_verify {0 <= n} ()
  in
    stack := list_cons (x, stack)
  end

(* Push to a linear stack that is stored in a variable. Beware: if x
   is linear, it is consumed. *)
fn {vt : vt@ype}
stack_vt_push {n : int}
              (stack : &stack_vt (vt, n) >> stack_vt (vt, m),
               x     : vt) :<!wrt>
    (* It is proved that the stack is raised one higher. *)
    #[m : int | 1 <= m; m == n + 1]
    void =
  let
    prval _ = lemma_stack_vt_param stack
    prval _ = prop_verify {0 <= n} ()
  in
    stack := list_vt_cons (x, stack)
  end

(* Pop from a nonlinear stack that is stored in a variable. It is
   impossible (unless you cheat the typechecker) to pop from an empty
   stack. *)
fn {t : t@ype}
stack_t_pop {n : int | 1 <= n}
            (stack : &stack_t (t, n) >> stack_t (t, m)) :<!wrt>
    (* It is proved that the stack is lowered by one. *)
    #[m : int | m == n - 1]
    t =
  case+ stack of
  | list_cons (x, tail) =>
    begin
      stack := tail;
      x
    end

(* Pop from a linear stack that is stored in a variable. It is
   impossible (unless you cheat the typechecker) to pop from an empty
   stack. *)
fn {vt : vt@ype}
stack_vt_pop {n : int | 1 <= n}
             (stack : &stack_vt (vt, n) >> stack_vt (vt, m)) :<!wrt>
    (* It is proved that the stack is lowered by one. *)
    #[m : int | m == n - 1]
    vt =
  case+ stack of
  | ~ list_vt_cons (x, tail) => (* ~ = the top node is consumed. *)
    begin
      stack := tail;
      x
    end

(* A linear stack has to be consumed. *)
extern fun {vt : vt@ype}
stack_vt_free$element_free (x : vt) :<> void
fn {vt : vt@ype}
stack_vt_free {n : int}
              (stack : stack_vt (vt, n)) :<> void =
  let
    fun
    loop {m : int | 0 <= m}
         .<m>. (* <-- proof of loop termination *)
         (stk : stack_vt (vt, m)) :<> void =
      case+ stk of
      | ~ list_vt_nil () => begin end
      | ~ list_vt_cons (x, tail) =>
        begin
          stack_vt_free$element_free x;
          loop tail
        end

    prval _ = lemma_stack_vt_param stack
  in
    loop stack
  end

implement
main0 () =
  let
    var nonlinear_stack : stack_t (int) = stack_t_nil ()
    var linear_stack : stack_vt (int) = stack_vt_nil ()
    implement stack_vt_free$element_free<int> x = begin end

    overload is_empty with stack_t_is_empty
    overload is_empty with stack_vt_is_empty

    overload push with stack_t_push
    overload push with stack_vt_push

    overload pop with stack_t_pop
    overload pop with stack_vt_pop
  in
    println! ("nonlinear_stack is empty? ", is_empty nonlinear_stack);
    println! ("linear_stack is empty? ", is_empty linear_stack);

    println! ("pushing 3, 2, 1...");
    push (nonlinear_stack, 3);
    push (nonlinear_stack, 2);
    push (nonlinear_stack, 1);
    push (linear_stack, 3);
    push (linear_stack, 2);
    push (linear_stack, 1);

    println! ("nonlinear_stack is empty? ", is_empty nonlinear_stack);
    println! ("linear_stack is empty? ", is_empty linear_stack);

    println! ("popping nonlinear_stack: ", (pop nonlinear_stack) : int);
    println! ("popping nonlinear_stack: ", (pop nonlinear_stack) : int);
    println! ("popping nonlinear_stack: ", (pop nonlinear_stack) : int);

    println! ("popping linear_stack: ", (pop linear_stack) : int);
    println! ("popping linear_stack: ", (pop linear_stack) : int);
    println! ("popping linear_stack: ", (pop linear_stack) : int);

    println! ("nonlinear_stack is empty? ", is_empty nonlinear_stack);
    println! ("linear_stack is empty? ", is_empty linear_stack);

    stack_vt_free<int> linear_stack
  end
Output:
$ patscc -O2 -DATS_MEMALLOC_LIBC stack-postiats.dats && ./a.out
nonlinear_stack is empty? true
linear_stack is empty? true
pushing 3, 2, 1...
nonlinear_stack is empty? false
linear_stack is empty? false
popping nonlinear_stack: 1
popping nonlinear_stack: 2
popping nonlinear_stack: 3
popping linear_stack: 1
popping linear_stack: 2
popping linear_stack: 3
nonlinear_stack is empty? true
linear_stack is empty? true

AutoHotkey

msgbox % stack("push", 4)
msgbox % stack("push", 5)
msgbox % stack("peek")
msgbox % stack("pop")
msgbox % stack("peek")
msgbox % stack("empty")
msgbox % stack("pop")
msgbox % stack("empty")
return 

stack(command, value = 0)
{
  static 
if !pointer 
pointer = 10000
  if (command = "push")
  {
  _p%pointer% := value
  pointer -= 1 
  return value
  }
  if (command = "pop")
  {
    pointer += 1
    return _p%pointer%
  }
  if (command = "peek")
{
next := pointer + 1    
return _p%next%
}
  if (command = "empty")
  {
   if (pointer == 10000)
    return "empty"
else
return 0
  }
}

AWK

function deque(arr) {
    arr["start"] = 0
    arr["end"] = 0
}

function dequelen(arr) {
    return arr["end"] - arr["start"]
}

function empty(arr) {
    return dequelen(arr) == 0
}

function push(arr, elem) {
    arr[++arr["end"]] = elem
}

function pop(arr) {
    if (empty(arr)) {
        return
    }
    return arr[arr["end"]--]
}

function unshift(arr, elem) {
    arr[arr["start"]--] = elem
}

function shift(arr) {
    if (empty(arr)) {
        return
    }
    return arr[++arr["start"]]
}

function peek(arr) {
    if (empty(arr)) {
        return
    }
    return arr[arr["end"]]
}

function printdeque(arr,    i, sep) {
    printf("[")
    for (i = arr["start"] + 1; i <= arr["end"]; i++) {
        printf("%s%s", sep, arr[i])
        sep = ", "
    }
    printf("]\n")
}

BEGIN {
    deque(q)
    for (i = 1; i <= 10; i++) {
        push(q, i)
    }
    printdeque(q)
    for (i = 1; i <= 10; i++) {
        print pop(q)
    }
    printdeque(q)
}

Axe

0→S
Lbl PUSH
r₁→{L₁+S}ʳ
S+2→S
Return

Lbl POP
S-2→S
{L₁+S}ʳ
Return

Lbl EMPTY
S≤≤0
Return

Babel

main : 
    { (1 2 3) foo set     -- foo = (1 2 3)
    4 foo push            -- foo = (1 2 3 4)
    0 foo unshift         -- foo = (0 1 2 3 4)
    foo pop               -- foo = (0 1 2 3)
    foo shift             -- foo = (1 2 3)
    check_foo
    { foo pop } 4 times   -- Pops too many times, but this is OK and Babel won't complain
    check_foo }

empty? : nil?   -- just aliases 'empty?' to the built-in operator 'nil?'

check_foo! : 
    { "foo is " 
    {foo empty?) {nil} {"not " .} ifte 
    "empty" . 
    cr << }
Output:
foo is not empty
foo is empty

Batch File

This implementation uses an environment variable naming convention to implement a stack as a pseudo object containing a pseudo dynamic array and top attribute, as well as an empty "method" that is a sort of macro. The implementation depends on delayed expansion being enabled at the time of each call to a stack function. More complex variations can be written that remove this limitation.

@echo off
setlocal enableDelayedExpansion

:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
:: LIFO stack usage

:: Define the stack
call :newStack myStack

:: Push some values onto the stack
for %%A in (value1 value2 value3) do call :pushStack myStack %%A

:: Test if stack is empty by examining the top "attribute"
if myStack.top==0 (echo myStack is empty) else (echo myStack is NOT empty)

:: Peek at the top stack value
call:peekStack myStack val && echo a peek at the top of myStack shows !val!

:: Pop the top stack value
call :popStack myStack val && echo popped myStack value=!val!

:: Push some more values onto the stack
for %%A in (value4 value5 value6) do call :pushStack myStack %%A

:: Process the remainder of the stack
:processStack
call :popStack myStack val || goto :stackEmpty
echo popped myStack value=!val!
goto :processStack
:stackEmpty

:: Test if stack is empty using the empty "method"/"macro". Use of the
:: second IF statement serves to demonstrate the negation of the empty
:: "method". A single IF could have been used with an ELSE clause instead.
if %myStack.empty% echo myStack is empty
if not %myStack.empty% echo myStack is NOT empty
exit /b

:::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::::
:: LIFO stack definition

:newStack stackName
set /a %~1.top=0
:: Define an empty "method" for this stack as a sort of macro
set "%~1.empty=^!%~1.top^! == 0"
exit /b

:pushStack stackName value
set /a %~1.top+=1
set %~1.!%~1.top!=%2
exit /b

:popStack stackName returnVar
:: Sets errorlevel to 0 if success
:: Sets errorlevel to 1 if failure because stack was empty
if !%~1.top! equ 0 exit /b 1
for %%N in (!%~1.top!) do (
  set %~2=!%~1.%%N!
  set %~1.%%N=
)
set /a %~1.top-=1
exit /b 0

:peekStack stackName returnVar
:: Sets errorlevel to 0 if success
:: Sets errorlevel to 1 if failure because stack was empty
if !%~1.top! equ 0 exit /b 1
for %%N in (!%~1.top!) do set %~2=!%~1.%%N!
exit /b 0

BASIC

BBC BASIC

      STACKSIZE = 1000
      
      FOR n = 3 TO 5
        PRINT "Push ";n : PROCpush(n)
      NEXT
      PRINT "Pop " ; FNpop
      PRINT "Push 6" : PROCpush(6)
      REPEAT
        PRINT "Pop " ; FNpop
      UNTIL FNisempty
      PRINT "Pop " ; FNpop
      END
      
      DEF PROCpush(n) : LOCAL f%
      DEF FNpop : LOCAL f% : f% = 1
      DEF FNisempty : LOCAL f% : f% = 2
      PRIVATE stack(), sptr%
      DIM stack(STACKSIZE-1)
      CASE f% OF
        WHEN 0:
          IF sptr% = DIM(stack(),1) ERROR 100, "Error: stack overflowed"
          stack(sptr%) = n
          sptr% += 1
        WHEN 1:
          IF sptr% = 0 ERROR 101, "Error: stack empty"
          sptr% -= 1
          = stack(sptr%)
        WHEN 2:
          = (sptr% = 0)
      ENDCASE
      ENDPROC
Output:
Push 3
Push 4
Push 5
Pop 5
Push 6
Pop 6
Pop 4
Pop 3
Pop
Error: stack empty

beeswax

Beeswax is a stack-based language. The instruction pointers (bees) carry small local stacks (lstacks) of fixed length 3 that can interact with the global stack (gstack) of unrestricted length. The local stacks do not behave exactly like the stack specified in this task, but the global stack does.

Push (1): f pushes the topmost value of lstack on gstack.

     instruction: _f

     gstack:      UInt64[0]•         (at the beginning of a program lstack is initialized to [0 0 0]

Push (2): e pushes all three lstack values on gstack, in reversed order.

     instruction: _e

     gstack:      UInt64[0 0 0]•         (at the beginning of a program lstack is initialized to [0 0 0]

Push (3): i pushes an integer from STDIN as UInt64 value on gstack.

     instruction: _i
     input:       i123

     gstack:      UInt64[123]•

Push (4): c pushes the Unicode codepoint value of a character from STDIN as UInt64 value on gstack.

     instruction: _c
     input:       cH

     gstack:      UInt64[72]•

Push (5): V pushes the Unicode codepoint values of the characters of a string given at STDIN as UInt64 values on gstack, last character, followed by newline on top.

     instruction: _V
     input:       sHello, α∀

     gstack:      UInt64[72 101 108 108 111 44 32 945 8704 10]•

Pop: g{? reads the top value of gstack and stores it on top of lstack. Then outputs top value of lstack to STDOUT and finally pops gstack.

Empty: Ag?';`gstack is empty` pushes length of gstack on gstack, reads top value of gstack, stores it as top value of lstack and prints gstack is empty if lstack top=0.

Top: g{ reads the top value of gstack, stores it on top of lstack. Then outputs top value of lstack to STDOUT. If gstack is empty, this instruction does not do anything but return the topmost value of lstack.

To make sure that there is any value on gstack, you would need to check for gstack length first, using the method shown in the “Empty” example above:

*Ag'{`gstack empty, no value to return`

This method returns the top value of gstack only if gstack is not empty, otherwise it outputs gstack empty, no value to return to STDOUT.

BQN

Representing the stack as an array, pushing is appending, popping is removing the last element, and checking emptiness is checking the length.

    Push  

   Pop  ¯1
¯1
   Empty  0=≠
0=≠
   123 Push 4
 1 2 3 4 
   Pop 123
 1 2 
   Empty 123
0
   Empty ⟨⟩
1

Bracmat

A stack is easiest implemented as a dotted list top.top-1.top-2.[...].. In the example below we also introduce a 'class' stack, instantiated in the 'object' Stack. The class has a member variable S and methods push,pop, top and empty. As a side note, . is to .. as C's . is to ->. In a method's body, its refers to the object itself. (Analogous to (*this) in C++.)

( ( stack
  =   (S=)
      (push=.(!arg.!(its.S)):?(its.S))
      ( pop
      = top.!(its.S):(%?top.?(its.S))&!top
      )
      (top=top.!(its.S):(%?top.?)&!top)
      (empty=.!(its.S):)
  )
& new$stack:?Stack
& (Stack..push)$(2*a)
& (Stack..push)$pi
& (Stack..push)$
& (Stack..push)$"to be or"
& (Stack..push)$"not to be"
& out$((Stack..pop)$|"Cannot pop (a)")
& out$((Stack..top)$|"Cannot pop (b)")
& out$((Stack..pop)$|"Cannot pop (c)")
& out$((Stack..pop)$|"Cannot pop (d)")
& out$((Stack..pop)$|"Cannot pop (e)")
& out$((Stack..pop)$|"Cannot pop (f)")
& out$((Stack..pop)$|"Cannot pop (g)")
& out$((Stack..pop)$|"Cannot pop (h)")
&   out
  $ ( str
    $ ( "Stack is "
        ((Stack..empty)$&|not)
        " empty"
      )
    )
& 
);
Output:
not to be
to be or
to be or

pi
2*a
Cannot pop (g)
Cannot pop (h)
Stack is  empty

Brat

Built in arrays have push, pop, and empty? methods:

stack = []
stack.push 1
stack.push 2
stack.push 3

until { stack.empty? } { p stack.pop }
Output:
3
2
1

C

Macro expanding to type flexible stack routines.

#include <stdio.h>
#include <stdlib.h>

/* to read expanded code, run through cpp | indent -st */
#define DECL_STACK_TYPE(type, name)					\
typedef struct stk_##name##_t{type *buf; size_t alloc,len;}*stk_##name;	\
stk_##name stk_##name##_create(size_t init_size) {			\
	stk_##name s; if (!init_size) init_size = 4;			\
	s = malloc(sizeof(struct stk_##name##_t));			\
	if (!s) return 0;						\
	s->buf = malloc(sizeof(type) * init_size);			\
	if (!s->buf) { free(s); return 0; }				\
	s->len = 0, s->alloc = init_size;				\
	return s; }							\
int stk_##name##_push(stk_##name s, type item) {			\
	type *tmp;							\
	if (s->len >= s->alloc) {					\
		tmp = realloc(s->buf, s->alloc*2*sizeof(type));		\
		if (!tmp) return -1; s->buf = tmp;			\
		s->alloc *= 2; }					\
	s->buf[s->len++] = item;					\
	return s->len; }						\
type stk_##name##_pop(stk_##name s) {					\
	type tmp;							\
	if (!s->len) abort();						\
	tmp = s->buf[--s->len];						\
	if (s->len * 2 <= s->alloc && s->alloc >= 8) {			\
		s->alloc /= 2;						\
		s->buf = realloc(s->buf, s->alloc * sizeof(type));}	\
	return tmp; }							\
void stk_##name##_delete(stk_##name s) {				\
	free(s->buf); free(s); }

#define stk_empty(s) (!(s)->len)
#define stk_size(s) ((s)->len)

DECL_STACK_TYPE(int, int)

int main(void)
{
	int i;
	stk_int stk = stk_int_create(0);

	printf("pushing: ");
	for (i = 'a'; i <= 'z'; i++) {
		printf(" %c", i);
		stk_int_push(stk, i);
	}

	printf("\nsize now: %d", stk_size(stk));
	printf("\nstack is%s empty\n", stk_empty(stk) ? "" : " not");

	printf("\npoppoing:");
	while (stk_size(stk))
		printf(" %c", stk_int_pop(stk));
	printf("\nsize now: %d", stk_size(stk));
	printf("\nstack is%s empty\n", stk_empty(stk) ? "" : " not");

	/* stk_int_pop(stk); <-- will abort() */
	stk_int_delete(stk);
	return 0;
}

Or

#include <stdio.h>
#include <stdlib.h>
#include <stddef.h>
#include <stdbool.h>

#define check_pointer(p) if (!p) {puts("Out of memory."); exit(EXIT_FAILURE);}

#define MINIMUM_SIZE 1
 /* Minimal stack size (expressed in number of elements) for which
 space is allocated. It should be at least 1. */
#define GROWTH_FACTOR 2
 /* How much more memory is allocated each time a stack grows
 out of its allocated segment. */
typedef int T;
 // The type of the stack elements.

typedef struct
 {T *bottom;
  T *top;
  T *allocated_top;} stack;

stack * new(void)
/* Creates a new stack. */
 {stack *s = malloc(sizeof(stack));
  check_pointer(s);
  s->bottom = malloc(MINIMUM_SIZE * sizeof(T));
  check_pointer(s->bottom);
  s->top = s->bottom - 1;
  s->allocated_top = s->bottom + MINIMUM_SIZE - 1;
  return s;}

void destroy(stack *s)
/* Frees all the memory used for a stack. */
 {free(s->bottom);
  free(s);}

bool empty(stack *s)
/* Returns true iff there are no elements on the stack. This
is different from the stack not having enough memory reserved
for even one element, which case is never allowed to arise. */
 {return s->top < s->bottom ? true : false;}

void push(stack *s, T x)
/* Puts a new element on the stack, enlarging the latter's
memory allowance if necessary. */
 {if (s->top == s->allocated_top)
     {ptrdiff_t qtty = s->top - s->bottom + 1;
      ptrdiff_t new_qtty = GROWTH_FACTOR * qtty;
      s->bottom = realloc(s->bottom, new_qtty * sizeof(T));
      check_pointer(s->bottom);
      s->top = s->bottom + qtty - 1;
      s->allocated_top = s->bottom + new_qtty - 1;}
  *(++s->top) = x;}

T pop(stack *s)
/* Removes and returns the topmost element. The result of popping
an empty stack is undefined. */
 {return *(s->top--);}

void compress(stack *s)
/* Frees any memory the stack isn't actually using. The
allocated portion still isn't allowed to shrink smaller than
MINIMUM_SIZE. If all the stack's memory is in use, nothing
happens. */
 {if (s->top == s->allocated_top) return;
  ptrdiff_t qtty = s->top - s->bottom + 1;
  if (qtty < MINIMUM_SIZE) qtty = MINIMUM_SIZE;
  size_t new_size = qtty * sizeof(T);
  s->bottom = realloc(s->bottom, new_size);
  check_pointer(s->bottom);
  s->allocated_top = s->bottom + qtty - 1;}

C#

// Non-Generic Stack
System.Collections.Stack stack = new System.Collections.Stack();
stack.Push( obj );
bool isEmpty = stack.Count == 0;
object top = stack.Peek(); // Peek without Popping.
top = stack.Pop();

// Generic Stack
System.Collections.Generic.Stack<Foo> stack = new System.Collections.Generic.Stack<Foo>();
stack.Push(new Foo());
bool isEmpty = stack.Count == 0;
Foo top = stack.Peek(); // Peek without Popping.
top = stack.Pop();

C++

Library: STL

The C++ standard library already provides a ready-made stack class. You get it by writing

#include <stack>

and then using the std::stack class.

An example of an explicit implementation of a stack class (which actually implements the standard stack class, except that the standard one is in namespace std):

#include <deque>
template <class T, class Sequence = std::deque<T> >
class stack {
  friend bool operator== (const stack&, const stack&);
  friend bool operator<  (const stack&, const stack&);
public:
  typedef typename Sequence::value_type      value_type;
  typedef typename Sequence::size_type       size_type;
  typedef          Sequence                  container_type;
  typedef typename Sequence::reference       reference;
  typedef typename Sequence::const_reference const_reference;
protected:
  Sequence seq;
public:
  stack() : seq() {}
  explicit stack(const Sequence& s0) : seq(s0) {}
  bool empty() const { return seq.empty(); }
  size_type size() const { return seq.size(); }
  reference top() { return seq.back(); }
  const_reference top() const { return seq.back(); }
  void push(const value_type& x) { seq.push_back(x); }
  void pop() { seq.pop_back(); }
};

template <class T, class Sequence>
bool operator==(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return x.seq == y.seq;
}
template <class T, class Sequence>
bool operator<(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return x.seq < y.seq;
}

template <class T, class Sequence>
bool operator!=(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return !(x == y);
}
template <class T, class Sequence>
bool operator>(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return y < x;
}
template <class T, class Sequence>
bool operator<=(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return !(y < x);
}
template <class T, class Sequence>
bool operator>=(const stack<T,Sequence>& x, const stack<T,Sequence>& y)
{
  return !(x < y);
}

Clojure

As is mentioned in the Common Lisp example below, built in cons-based lists work just fine. In this implementation, the list is wrapped in a datatype, providing a stateful solution.

(deftype Stack [elements])

(def stack (Stack (ref ())))

(defn push-stack
  "Pushes an item to the top of the stack."
  [x] (dosync (alter (:elements stack) conj x)))

(defn pop-stack
  "Pops an item from the top of the stack."
  [] (let [fst (first (deref (:elements stack)))] 
       (dosync (alter (:elements stack) rest)) fst))

(defn top-stack
  "Shows what's on the top of the stack."
  [] (first (deref (:elements stack))))

(defn empty-stack?
  "Tests whether or not the stack is empty."
  [] (= () (deref (:elements stack))))

We can make this a bit smaller and general by using defprotocol along with deftype. Here is a revised version using defprotocol.

(defprotocol StackOps
  (push-stack [this x] "Pushes an item to the top of the stack.")
  (pop-stack [this] "Pops an item from the top of the stack.")
  (top-stack [this] "Shows what's on the top of the stack.")
  (empty-stack? [this] "Tests whether or not the stack is empty."))
(deftype Stack [elements]
  StackOps
   (push-stack [x] (dosync (alter elements conj x)))
   (pop-stack [] (let [fst (first (deref elements))]
		   (dosync (alter elements rest)) fst))
   (top-stack [] (first (deref elements)))
   (empty-stack? [] (= () (deref elements))))

(def stack (Stack (ref ())))

CLU

% Stack 
stack = cluster [T: type] is new, push, pop, peek, empty
    rep = array[T]
    
    new = proc () returns (cvt)
        return (rep$new())
    end new
    
    empty = proc (s: cvt) returns (bool)
        return (rep$size(s) = 0)
    end empty;
    
    push = proc (s: cvt, val: T)
        rep$addh(s, val)
    end push;
    
    pop = proc (s: cvt) returns (T) signals (empty)
        if rep$empty(s)
            then signal empty
            else return(rep$remh(s))
        end
    end pop
    
    peek = proc (s: cvt) returns (T) signals (empty)
        if rep$empty(s)
            then signal empty
            else return(s[rep$high(s)])
        end
    end peek
end stack 

start_up = proc () 
    po: stream := stream$primary_output()
    
    % Make a stack
    s: stack[int] := stack[int]$new()
    
    % Push 1..10 onto the stack 
    for i: int in int$from_to(1, 10) do
        stack[int]$push(s, i)
    end
    
    % Pop items off the stack until the stack is empty 
    while ~stack[int]$empty(s) do
        stream$putl(po, int$unparse(stack[int]$pop(s)))
    end
    
    % Trying to pop off the stack now should raise 'empty'
    begin
        i: int := stack[int]$pop(s)
        stream$putl(po, "Still here! And I got: " || int$unparse(i))
    end except when empty:
        stream$putl(po, "The stack is empty.")
    end
end start_up
Output:
10
9
8
7
6
5
4
3
2
1
The stack is empty.

COBOL

Works with: COBOL version 2002
Works with: OpenCOBOL version 1.1

Based loosely on the C stack implementation in Evangel Quiwa's Data Structures.

This example (ab)uses the COPY procedure to ensure that there is a consistently-defined stack type, node type, node information type, p(redicate) type, and set of stack-utilities.

stack.cbl

       01  stack.
         05  head USAGE IS POINTER VALUE NULL.

node.cbl

       01  node BASED.
         COPY node-info REPLACING
           01 BY 05
           node-info BY info.
         05  link USAGE IS POINTER VALUE NULL.

node-info.cbl

       01  node-info PICTURE X(10) VALUE SPACES.

p.cbl

       01  p PICTURE 9.
         88 nil VALUE ZERO WHEN SET TO FALSE IS 1.
         88 t   VALUE 1 WHEN SET TO FALSE IS ZERO.

stack-utilities.cbl

       IDENTIFICATION DIVISION.
       PROGRAM-ID. push.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node.
       LINKAGE SECTION.
       COPY stack.
       01  node-info-any PICTURE X ANY LENGTH.
       PROCEDURE DIVISION USING stack node-info-any.
         ALLOCATE node
         CALL "pointerp" USING
           BY REFERENCE ADDRESS OF node
           BY REFERENCE p
         END-CALL
         IF nil
           CALL "stack-overflow-error" END-CALL
         ELSE
           MOVE node-info-any TO info OF node
           SET link OF node TO head OF stack
           SET head OF stack TO ADDRESS OF node
         END-IF
         GOBACK.
       END PROGRAM push.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. pop.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node.
       LINKAGE SECTION.
       COPY stack.
       COPY node-info.
       PROCEDURE DIVISION USING stack node-info.
         CALL "empty" USING
           BY REFERENCE stack
           BY REFERENCE p
         END-CALL
         IF t
           CALL "stack-underflow-error" END-CALL
         ELSE
           SET ADDRESS OF node TO head OF stack
           SET head OF stack TO link OF node
           MOVE info OF node TO node-info
         END-IF
         FREE ADDRESS OF node
         GOBACK.
       END PROGRAM pop.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. empty.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       LINKAGE SECTION.
       COPY stack.
       COPY p.
       PROCEDURE DIVISION USING stack p.
         CALL "pointerp" USING
           BY CONTENT head OF stack
           BY REFERENCE p
         END-CALL
         IF t
           SET t TO FALSE
         ELSE
           SET t TO TRUE
         END-IF
         GOBACK.
       END PROGRAM empty.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. head.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node.
       LINKAGE SECTION.
       COPY stack.
       COPY node-info.
       PROCEDURE DIVISION USING stack node-info.
         CALL "empty" USING
           BY REFERENCE stack
           BY REFERENCE p
         END-CALL
         IF t
           CALL "stack-underflow-error" END-CALL
         ELSE
           SET ADDRESS OF node TO head OF stack
           MOVE info OF node TO node-info
         END-IF
         GOBACK.
       END PROGRAM head.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. peek.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       LINKAGE SECTION.
       COPY stack.
       COPY node-info.
       PROCEDURE DIVISION USING stack node-info.
         CALL "head" USING
           BY CONTENT stack
           BY REFERENCE node-info
         END-CALL
         GOBACK.
       END PROGRAM peek.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. pointerp.
       DATA DIVISION.
       LINKAGE SECTION.
       01  test-pointer USAGE IS POINTER.
       COPY p.
       PROCEDURE DIVISION USING test-pointer p.
         IF test-pointer EQUAL NULL
           SET nil TO TRUE
         ELSE
           SET t TO TRUE
         END-IF
         GOBACK.
       END PROGRAM pointerp.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. stack-overflow-error.
       PROCEDURE DIVISION.
         DISPLAY "stack-overflow-error" END-DISPLAY
         STOP RUN.
       END PROGRAM stack-overflow-error.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. stack-underflow-error.
       PROCEDURE DIVISION.
         DISPLAY "stack-underflow-error" END-DISPLAY
         STOP RUN.
       END PROGRAM stack-underflow-error.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. copy-stack.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node-info.
       LINKAGE SECTION.
       COPY stack.
       COPY stack REPLACING stack BY new-stack.
       PROCEDURE DIVISION USING stack new-stack.
         CALL "empty" USING
           BY REFERENCE stack
           BY REFERENCE p
         END-CALL
         IF nil
           CALL "pop" USING
             BY REFERENCE stack
             BY REFERENCE node-info
           END-CALL
           CALL "copy-stack" USING
             BY REFERENCE stack
             BY REFERENCE new-stack
           END-CALL
           CALL "push" USING
             BY REFERENCE stack
             BY REFERENCE node-info
           END-CALL
           CALL "push" USING
             BY REFERENCE new-stack
             BY REFERENCE node-info
           END-CALL
         END-IF
         GOBACK.
       END PROGRAM copy-stack.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. reverse-stack.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node-info.
       LINKAGE SECTION.
       COPY stack.
       COPY stack REPLACING stack BY new-stack.
       PROCEDURE DIVISION USING stack new-stack.
         CALL "empty" USING
           BY REFERENCE stack
           BY REFERENCE p
         END-CALL
         IF nil
           CALL "pop" USING
             BY REFERENCE stack
             BY REFERENCE node-info
           END-CALL
           CALL "push" USING
             BY REFERENCE new-stack
             BY REFERENCE node-info
           END-CALL
           CALL "reverse-stack" USING
             BY REFERENCE stack
             BY REFERENCE new-stack
           END-CALL
           CALL "push" USING
             BY REFERENCE stack
             BY REFERENCE node-info
           END-CALL
         END-IF
         GOBACK.
       END PROGRAM reverse-stack.

       IDENTIFICATION DIVISION.
       PROGRAM-ID. traverse-stack.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY p.
       COPY node-info.
       COPY stack REPLACING stack BY new-stack.
       LINKAGE SECTION.
       COPY stack.
       PROCEDURE DIVISION USING stack.
         CALL "copy-stack" USING
           BY REFERENCE stack
           BY REFERENCE new-stack
         END-CALL
         CALL "empty" USING
           BY REFERENCE new-stack
           BY REFERENCE p
         END-CALL
         IF nil
           CALL "head" USING
             BY CONTENT new-stack
             BY REFERENCE node-info
           END-CALL
           DISPLAY node-info END-DISPLAY
           CALL "peek" USING
             BY CONTENT new-stack
             BY REFERENCE node-info
           END-CALL
           DISPLAY node-info END-DISPLAY
           CALL "pop" USING
             BY REFERENCE new-stack
             BY REFERENCE node-info
           END-CALL
           DISPLAY node-info END-DISPLAY
           CALL "traverse-stack" USING
             BY REFERENCE new-stack
           END-CALL
         END-IF
         GOBACK.
       END PROGRAM traverse-stack.

stack-test.cbl

       IDENTIFICATION DIVISION.
       PROGRAM-ID. stack-test.
       DATA DIVISION.
       LOCAL-STORAGE SECTION.
       COPY stack.
       COPY stack REPLACING stack BY new-stack.
       PROCEDURE DIVISION.
         CALL "push" USING
           BY REFERENCE stack
           BY CONTENT "daleth"
         END-CALL
         CALL "push" USING
           BY REFERENCE stack
           BY CONTENT "gimel"
         END-CALL
         CALL "push" USING
           BY REFERENCE stack
           BY CONTENT "beth"
         END-CALL
         CALL "push" USING
           BY REFERENCE stack
           BY CONTENT "aleph"
         END-CALL
         CALL "traverse-stack" USING
           BY REFERENCE stack
         END-CALL
         CALL "reverse-stack" USING
           BY REFERENCE stack
           BY REFERENCE new-stack
         END-CALL
         CALL "traverse-stack" USING
           BY REFERENCE new-stack
         END-CALL
         STOP RUN.
       END PROGRAM stack-test.

       COPY stack-utilities.
Output:
aleph
aleph
beth
beth
beth
gimel
gimel
gimel
daleth
daleth
daleth
daleth
daleth
daleth
gimel
gimel
gimel
beth
beth
beth
aleph
aleph
aleph

CoffeeScript

stack = []
stack.push 1
stack.push 2
console.log stack
console.log stack.pop()
console.log stack

Common Lisp

It's a bit unusual to write a wrapper for a stack in Common Lisp; built-in cons-based lists work just fine. Nonetheless, here's an implementation where the list is wrapped in a structure, providing a stateful solution.

(defstruct stack
  elements)

(defun stack-push (element stack)
  (push element (stack-elements stack)))

(defun stack-pop (stack)(deftype Stack [elements])

(defun stack-empty (stack)
  (endp (stack-elements stack)))

(defun stack-top (stack)
  (first (stack-elements stack)))

(defun stack-peek (stack)
  (stack-top stack))

Component Pascal

Works with BlackBox Component Builder

MODULE Stacks;
IMPORT StdLog;

TYPE
	(* some pointers to records *)
	Object* = POINTER TO ABSTRACT RECORD END;
	
	Integer = POINTER TO RECORD (Object)
		i: INTEGER
	END;
	
	Point = POINTER TO RECORD (Object)
		x,y: REAL
	END;

	Node = POINTER TO LIMITED RECORD
		next- : Node;
		data-: ANYPTR;
	END;

	(* Stack *)
	Stack* = POINTER TO RECORD  
		top- : Node;
	END;
	
	PROCEDURE (dn: Object) Show*, NEW, ABSTRACT;
	
	PROCEDURE (i: Integer) Show*;
	BEGIN
		StdLog.String("Integer(");StdLog.Int(i.i);StdLog.String(");");StdLog.Ln
	END Show;
	
	PROCEDURE (p: Point) Show*;
	BEGIN
		StdLog.String("Point(");StdLog.Real(p.x);StdLog.Char(',');
		StdLog.Real(p.y);StdLog.String(");");StdLog.Ln
	END Show;
	
	PROCEDURE (s: Stack) Init, NEW;
	BEGIN
		s.top := NIL;
	END Init;
	
	PROCEDURE (s: Stack) Push*(data: ANYPTR), NEW;
	VAR
		n: Node;
	BEGIN 
		NEW(n);n.next := NIL;n.data := data;
		IF s.top = NIL THEN
			s.top := n
		ELSE
			n.next := s.top;
			s.top := n
		END
	END Push;
	
	PROCEDURE (s: Stack) Pop*(): ANYPTR, NEW;
	VAR
		x: ANYPTR;
	BEGIN
		IF s.top # NIL THEN
			x := s.top.data;
			s.top := s.top.next
		ELSE
			x := NIL
		END;
		RETURN x
	END Pop;
	
	PROCEDURE (s: Stack) Empty*(): BOOLEAN, NEW;
	BEGIN
		RETURN s.top = NIL
	END Empty;
	
	PROCEDURE NewStack*(): Stack;
	VAR
		s: Stack;
	BEGIN
		NEW(s);s.Init;
		RETURN s
	END NewStack;
	
	PROCEDURE NewInteger*(data: INTEGER): Integer;
	VAR
		i: Integer;
	BEGIN
		NEW(i);i.i := data;
		RETURN i
	END NewInteger;
	
	PROCEDURE NewPoint*(x,y: REAL): Point;
	VAR
		p: Point;
	BEGIN
		NEW(p);p.x := x;p.y := y;
		RETURN p
	END NewPoint;
	
	PROCEDURE TestStack*;
	VAR
		s: Stack;
	BEGIN 
		s := NewStack();
		s.Push(NewInteger(1));
		s.Push(NewPoint(2.0,3.4));
		s.Pop()(Object).Show();
		s.Pop()(Object).Show();
	END TestStack;
	
END Stacks.

Execute: ^Q Stacks.TestStack

Output:
Point( 2.0, 3.4);
Integer( 1);

Crystal

stack = [] of Int32
(1..10).each do |x|
  stack.push x
end

10.times do
  puts stack.pop
end

Output:

10
9
8
7
6
5
4
3
2
1

D

Generic stack class implemented with a dynamic array.

import std.array;

class Stack(T) {
    private T[] items;

    @property bool empty() { return items.empty(); }

    void push(T top) { items ~= top; }

    T pop() {
        if (this.empty)
            throw new Exception("Empty Stack.");
        auto top = items.back;
        items.popBack();
        return top;
    }
}

void main() {
    auto s = new Stack!int();
    s.push(10);
    s.push(20);
    assert(s.pop() == 20);
    assert(s.pop() == 10);
    assert(s.empty());
}

Delphi

program Stack;

{$APPTYPE CONSOLE}

uses Generics.Collections;

var
  lStack: TStack<Integer>;
begin
  lStack := TStack<Integer>.Create;
  try
    lStack.Push(1);
    lStack.Push(2);
    lStack.Push(3);
    Assert(lStack.Peek = 3); // 3 should be at the top of the stack

    Writeln(lStack.Pop); // 3
    Writeln(lStack.Pop); // 2
    Writeln(lStack.Pop); // 1
    Assert(lStack.Count = 0); // should be empty
  finally
    lStack.Free;
  end;
end.

DWScript

Dynamic arrays have pseudo-methods that allow to treat them as a stack.

var stack: array of Integer;

stack.Push(1);
stack.Push(2);
stack.Push(3);

PrintLn(stack.Pop); // 3
PrintLn(stack.Pop); // 2
PrintLn(stack.Pop); // 1

Assert(stack.Length = 0); // assert empty

Dyalect

Translation of: Swift
type Stack() {
    var xs = []
}
 
func Stack.IsEmpty() => this!xs.Length() == 0
 
func Stack.Peek() => this!xs[this!xs.Length() - 1]
 
func Stack.Pop() {
    var e = this!xs[this!xs.Length() - 1]
    this!xs.RemoveAt(this!xs.Length() - 1)
    return e
}
 
func Stack.Push(item) => this!xs.Add(item)
 
var stack = Stack()
stack.Push(1)
stack.Push(2)
print(stack.Pop())
print(stack.Peek())
stack.Pop()
print(stack.IsEmpty())
Output:
2
1
true

Déjà Vu

local :stack [] #lists used to be stacks in DV

push-to stack 1
push-to stack 2
push-to stack 3

!. pop-from stack #prints 3
!. pop-from stack #prints 2
!. pop-from stack #prints 1

if stack: #empty lists are falsy
    error #this stack should be empty now!

Diego

Diego has a stack object and posit:

set_ns(rosettacode)_me();

    add_stack({int},a)_values(1..4);    // 1,2,3,4 (1 is first/bottom, 4 is last/top)
    with_stack(a)_pop();                // 1,2,3
    with_stack(a)_push()_v(5,6);        // 1,2,3,5,6

    add_var({int},b)_value(7);
    with_stack(a)_push[b];              // 1,2,3,5,6,7

    with_stack(a)_pluck()_at(2);        // callee will return `with_stack(a)_err(pluck invalid with stack);`

    me_msg()_stack(a)_top();            // "7"    
    me_msg()_stack(a)_last();           // "7"    
    me_msg()_stack(a)_peek();           // "7"  

    me_msg()_stack(a)_bottom();         // "1"    
    me_msg()_stack(a)_first();          // "1"    
    me_msg()_stack(a)_peer();           // "1"  

    me_msg()_stack(a)_isempty();            // "false"
    with_stack(a)_empty();
    with_stack(a)_msg()_isempty()_me();     // "true" (alternative syntax)

    me_msg()_stack(a)_history()_all();      // returns th entire history of stack 'a' since its creation    

reset_ns[];

stack is a derivative of array, so arrays can also be used as stacks.

E

The standard FlexList data structure provides operations for use as a stack.

? def l := [].diverge()
# value: [].diverge()

? l.push(1)
? l.push(2)
? l
# value: [1, 2].diverge()

? l.pop()
# value: 2

? l.size().aboveZero()
# value: true

? l.last()
# value: 1

? l.pop()
# value: 1

? l.size().aboveZero()
# value: false

Here's a stack implemented out of a reference to a linked list:

def makeStack() {
    var store := null
    def stack {
        to push(x) { store := [x, store] }
        to pop() { def [x, next] := store; store := next; return x }
        to last() { return store[0] }
        to empty() { return (store == null) }
    }
    return stack
}

? def s := makeStack()
# value: <stack>

? s.push(1)
? s.push(2)
? s.last()
# value: 2

? s.pop()
# value: 2

? s.empty()
# value: false

? s.pop()
# value: 1

? s.empty()
# value: true

EasyLang

stack[] = [ ]
proc push v . .
   stack[] &= v
.
func pop .
   lng = len stack[]
   if lng = 0
      return 0
   .
   r = stack[lng]
   len stack[] -1
   return r
.
func empty .
   return if len stack[] = 0
.
push 2
push 11
push 34
while empty = 0
   print pop
.

EchoLisp

Named stacks are native objects. The following demonstrates the available operations :

; build stack [0 1 ... 9 (top)] from a list
(list->stack (iota 10) 'my-stack)
(stack-top 'my-stack)  9
(pop 'my-stack)   9
(stack-top 'my-stack)  8
(push 'my-stack '🐸) ; any kind of lisp object in the stack
(stack-empty? 'my-stack)  #f
(stack->list 'my-stack) ; convert stack to list
     (0 1 2 3 4 5 6 7 8 🐸)
(stack-swap 'my-stack) ; swaps two last items 
     8 ; new top
(stack->list 'my-stack)
      (0 1 2 3 4 5 6 7 🐸 8) ; swapped
(while (not (stack-empty? 'my-stack)) (pop 'my-stack)) ; pop until empty
(stack-empty? 'my-stack)   #t ; true

(push 'my-stack 7)
my-stack ; a stack is not a variable, nor a symbol - cannot be evaluated
    error: #|user| : unbound variable : my-stack
(stack-top 'my-stack)  → 7

Eiffel

class
	STACK_ON_ARRAY

create
	make

feature -- Implementation

	empty: BOOLEAN
		do
			Result := stack.is_empty
		ensure
			empty: Result = (stack.count = 0)
		end

	push (item: ANY)
		do
			stack.force (item, stack.count)
		ensure
			pushed: stack [stack.upper] = item
			growth: stack.count = old stack.count + 1
		end

	pop: ANY
		require
			not_empty: not empty
		do
			Result := stack.at (stack.upper)
			stack.remove_tail (1)
		ensure
			reduction: stack.count = old stack.count - 1
		end

feature {NONE} -- Initialization

	stack: ARRAY [ANY]

	make
		do
			create stack.make_empty
		end

end

Elena

public program()
{
    var stack := new system'collections'Stack();
 
    stack.push(2);
 
    var isEmpty := stack.Length == 0;
 
    var item := stack.peek(); // Peek without Popping.
 
    item := stack.pop()
}

Elisa

This is a generic Stack component based on arrays. See how in Elisa generic components are defined.

 component GenericStack ( Stack, Element );
 type Stack;
      Stack (MaxSize = integer) -> Stack;
      Empty ( Stack )           -> boolean;
      Full ( Stack )            -> boolean;
      Push ( Stack, Element)    -> nothing;
      Pull ( Stack )            -> Element;
begin
      Stack(MaxSize) =
             Stack:[ MaxSize; index:=0; area=array (Element, MaxSize) ];
      Empty( stack ) = (stack.index <= 0);
      Full ( stack ) = (stack.index >= stack.MaxSize);
      Push ( stack, element ) = 
                   [ exception (Full (stack), "Stack Overflow");
                     stack.index:=stack.index + 1; 
                     stack.area[stack.index]:=element ];
      Pull ( stack ) = 
                   [ exception (Empty (stack), "Stack Underflow");
                     stack.index:=stack.index - 1; 
                     stack.area[stack.index + 1] ];
end component GenericStack;

Another example of a generic Stack component is based on an unlimited sequence. A sequence is a uni-directional list. See how Elisa defines sequences. The component has the same interface as the array based version.

component GenericStack ( Stack, ElementType );
 type Stack;
      Stack(MaxSize = integer)  -> Stack;
      Empty( Stack )            -> boolean;
      Full ( Stack )            -> boolean;
      Push ( Stack, ElementType)-> nothing;
      Pull ( Stack )            -> ElementType;
begin
      type sequence = term;
      ElementType & sequence => sequence;
      nil = null (sequence);

      head (sequence) -> ElementType;
      head (X & Y) = ElementType:X;

      tail (sequence) -> sequence;
      tail (X & Y) = Y;

      Stack (Size) = Stack:[ list = nil ];
      Empty ( stack ) = (stack.list == nil);
      Full ( stack ) = false;
      Push ( stack, ElementType ) = [ stack.list:= ElementType & stack.list ];
      Pull ( stack ) = [ exception (Empty (stack), "Stack Underflow");
                         Head = head(stack.list); stack.list:=tail(stack.list); Head];
end component GenericStack;

Both versions give the same answers to the following tests:

use GenericStack (StackofBooks, Book);
type Book = text;
BookStack = StackofBooks(50);

Push (BookStack, "Peter Pan");
Push (BookStack, "Alice in Wonderland");

Pull (BookStack)?
"Alice in Wonderland"

Pull (BookStack)?
"Peter Pan"

Pull (BookStack)?
***** Exception: Stack Underflow

Elixir

Translation of: Erlang
defmodule Stack do
  def new, do: []
  
  def empty?([]), do: true
  def empty?(_), do: false
  
  def pop([h|t]), do: {h,t}
  
  def push(h,t), do: [h|t]
  
  def top([h|_]), do: h
end

Example:

iex(2)> stack = Stack.new
[]
iex(3)> Stack.empty?(stack)
true
iex(4)> newstack = List.foldl([1,2,3,4,5], stack, fn x,acc -> Stack.push(x,acc) end)
[5, 4, 3, 2, 1]
iex(5)> Stack.top(newstack)
5
iex(6)> {popped, poppedstack} = Stack.pop(newstack)
{5, [4, 3, 2, 1]}
iex(7)> Stack.empty?(newstack)
false

Erlang

Erlang has no built-in stack, but its lists behave basically the same way. A stack module can be implemented as a simple wrapper around lists:

-module(stack).
-export([empty/1, new/0, pop/1, push/2, top/1]).

new() -> [].

empty([]) -> true;
empty(_) -> false.

pop([H|T]) -> {H,T}.

push(H,T) -> [H|T].

top([H|_]) -> H.

Note that as Erlang doesn't have mutable data structure (destructive updates), pop returns the popped element and the new stack as a tuple.

The module is tested this way:

1> c(stack).
{ok,stack}
2> Stack = stack:new().
[]
3> NewStack = lists:foldl(fun stack:push/2, Stack, [1,2,3,4,5]).
[5,4,3,2,1]
4> stack:top(NewStack).
5
5> {Popped, PoppedStack} = stack:pop(NewStack).
{5,[4,3,2,1]}
6> stack:empty(NewStack).
false
7> stack:empty(stack:new()).
true

F#

.NET provides a mutable stack type in System.Collections.Generic.Stack.

A list-based immutable stack type could be implemented like this:

type Stack<'a> //'//(workaround for syntax highlighting problem)
  (?items) =
  let items = defaultArg items []

  member x.Push(A) = Stack(A::items)

  member x.Pop() =
    match items with
      | x::xr ->  (x, Stack(xr))
      | [] -> failwith "Stack is empty."

  member x.IsEmpty() = items = []

// example usage
let anEmptyStack = Stack<int>()
let stack2 = anEmptyStack.Push(42)
printfn "%A" (stack2.IsEmpty())
let (x, stack3) = stack2.Pop()
printfn "%d" x
printfn "%A" (stack3.IsEmpty())

Factor

Factor is a stack based language, but also provides stack "objects", because all resizable sequences can be treated as stacks (see docs). Typically, a vector is used:

 V{ 1 2 3 } {
 [ 6 swap push ]
 [ "hi" swap push ]
 [ "Vector is now: " write . ]
 [ "Let's pop it: " write pop . ]
 [ "Vector is now: " write . ]
 [ "Top is: " write last . ] } cleave

 Vector is now: V{ 1 2 3 6 "hi" }
 Let's pop it: "hi"
 Vector is now: V{ 1 2 3 6 }
 Top is: 6

Forth

: stack ( size -- )
  create here cell+ ,  cells allot ;

: push ( n st -- ) tuck @ !  cell swap +! ;
: pop ( st -- n ) -cell over +!  @ @ ;
: empty? ( st -- ? ) dup @ - cell+ 0= ;

10 stack st

1 st push
2 st push
3 st push
st empty? .  \ 0 (false)
st pop . st pop . st pop .  \ 3 2 1
st empty? .  \ -1 (true)

Fortran

This solution can easily be adapted to data types other than floating point numbers.

module mod_stack

  implicit none
  type node
    ! data entry in each node
    real*8, private :: data
    ! pointer to the next node of the linked list
    type(node), pointer, private :: next
  end type node
  private node

  type stack
    ! pointer to first element of stack.
    type(node), pointer, private :: first
    ! size of stack
    integer, private :: len=0
  contains
    procedure :: pop
    procedure :: push
    procedure :: peek
    procedure :: getSize
    procedure :: clearStack
    procedure :: isEmpty
  end type stack

contains

  function pop(this) result(x)
    class(stack) :: this
    real*8 :: x
    type(node), pointer :: tmp
    if ( this%len == 0 ) then
      print*, "popping from empty stack"
      !stop
    end if
    tmp => this%first
    x = this%first%data
    this%first => this%first%next
    deallocate(tmp)
    this%len = this%len -1
  end function pop

  subroutine push(this, x)
    real*8 :: x
    class(stack), target :: this
    type(node), pointer :: new, tmp
    allocate(new)
    new%data = x
    if (.not. associated(this%first)) then
      this%first => new
    else
      tmp => this%first
      this%first => new
      this%first%next => tmp
    end if
    this%len = this%len + 1
  end subroutine push

  function peek(this) result(x)
    class(stack) :: this
    real*8 :: x
    x = this%first%data
  end function peek

  function getSize(this) result(n)
    class(stack) :: this
    integer :: n
    n = this%len
  end function getSize

  function isEmpty(this) result(empty)
    class(stack) :: this
    logical :: empty
    if ( this%len > 0 ) then
      empty = .FALSE.
    else
      empty = .TRUE.
    end if
  end function isEmpty

  subroutine clearStack(this)
    class(stack) :: this
    type(node), pointer :: tmp
    integer :: i
    if ( this%len == 0 ) then
      return
    end if
    do i = 1, this%len
      tmp => this%first
      if ( .not. associated(tmp)) exit
      this%first => this%first%next
      deallocate(tmp)
    end do
    this%len = 0
  end subroutine clearStack
end module mod_stack

program main
  use mod_stack
  type(stack) :: my_stack
  integer :: i
  real*8 :: dat
  do i = 1, 5, 1
    dat = 1.0 * i
    call my_stack%push(dat)
  end do
  do while ( .not. my_stack%isEmpty() )
    print*, my_stack%pop()
  end do
  call my_stack%clearStack()
end program main

Free Pascal

Delphi adaptation

Example taken and adapted from the Delphi entry.

program Stack;
 {$IFDEF FPC}{$MODE DELPHI}{$IFDEF WINDOWS}{$APPTYPE CONSOLE}{$ENDIF}{$ENDIF} 
 {$ASSERTIONS ON} 
uses Generics.Collections;
 
var
  lStack: TStack<Integer>;
begin
  lStack := TStack<Integer>.Create;
  try
    lStack.Push(1);
    lStack.Push(2);
    lStack.Push(3);
    Assert(lStack.Peek = 3); // 3 should be at the top of the stack
 
    Write(lStack.Pop:2);   // 3
    Write(lStack.Pop:2);   // 2
    Writeln(lStack.Pop:2); // 1
    Assert(lStack.Count = 0, 'Stack is not empty'); // should be empty
  finally
    lStack.Free;
  end;
end.
Output:
 3 2 1

Object version from scratch

Works with: Free Pascal version version 3.2.0
PROGRAM StackObject.pas;
{$IFDEF FPC}
    {$mode objfpc}{$H+}{$J-}{$m+}{$R+}
{$ELSE}
    {$APPTYPE CONSOLE}
{$ENDIF}
(*)

        Free Pascal Compiler version 3.2.0 [2020/06/14] for x86_64
        TheStack free and readable alternative at C/C++ Sidxeeds
        compiles natively to almost any platform, including raSidxberry PI *
        Can run independently from DELPHI / Lazarus

        For debian Linux: apt -y install fpc
        It contains a text IDE called fp

        This is an experiment for a stack that can handle almost any
        simple type of variable.

        What happens after retrieving the variable is TBD by you.

        https://www.freepascal.org/advantage.var
(*)


USES
        Classes   ,
        Crt       ,
        Variants  ;
        {$WARN 6058 off : Call to subroutine "$1" marked as inline is not inlined} // Use for variants

TYPE

    Stack   =   OBJECT
        
                    CONST
                    
                        CrLf    =   #13#10  ;
                        
                    TYPE

                        VariantArr = array  of variant ;
                                
                    PRIVATE

                            Ar  :   VariantArr  ;

                            {$MACRO ON}
                                {$DEFINE STACKSIZE  :=  Length ( Ar )           * Ord ( Length ( Ar ) > 0 ) }
                                {$DEFINE TOP        :=  STACKSIZE - 1           * Ord ( STACKSIZE > 0 )     }
                                {$DEFINE SLEN       :=  length ( Ar [ TOP ] )   * Ord ( Length ( Ar [ TOP ] ) > 0 ) }

                            FUNCTION    IsEmpty             : boolean   ;
                            PROCEDURE   Print                           ;
                            FUNCTION    Pop                 : variant   ;
                            FUNCTION    Peep                : variant   ;
                            PROCEDURE   Push        ( item  : variant ) ;
                            FUNCTION    SecPop              : variant   ;

                    PUBLIC
                            CONSTRUCTOR Create                          ;
                                        
                END;
                                        

    CONSTRUCTOR Stack.Create ;

        BEGIN
                SetLength ( Ar, STACKSIZE ) ;
        END;

    FUNCTION    Stack.IsEmpty  : boolean ;
    
        BEGIN
                IsEmpty := ( STACKSIZE < 1 ) ;
        END;


    PROCEDURE   Stack.Print  ;

        VAR
                i   :   shortint ;
        BEGIN
                IF ( TOP < 1 ) or ( IsEmpty ) THEN
                    BEGIN
                        WriteLn ( CrLf + '<empty stack>' ) ;
                        EXIT ;
                    END;
                WriteLn ( CrLf , '<top>') ;
                
                FOR i := ( TOP )  DOWNTO 0 DO WriteLn ( Ar [ i ] ) ;
                WriteLn ( '<bottom>' ) ;
        END;        


    FUNCTION    Stack.Pop : variant ;

        BEGIN
                IF IsEmpty THEN EXIT        ;
                Pop        := Ar [ TOP ]    ;
                SetLength  ( Ar, TOP )      ;
        END;


    FUNCTION    Stack.Peep  : variant ;

        BEGIN
                IF IsEmpty THEN EXIT        ;
                Peep        := Ar [ TOP ]   ;
        END;


    PROCEDURE   Stack.Push  ( item : variant ) ;
    
        BEGIN
                SetLength ( Ar, STACKSIZE + 1 ) ;
                Ar  [ TOP ]   := item           ;
        END;


    FUNCTION    Stack.SecPop : variant ;
    
        (*) Pop and Wipe    (*)
        
        BEGIN
                IF IsEmpty THEN EXIT                            ;
                SecPop      := Ar [ TOP ]                       ;
                Ar [ TOP ]  := StringOfChar ( #255  , SLEN )    ;
                Ar [ TOP ]  := StringOfChar ( #0    , SLEN )    ;
                SetLength  ( Ar, TOP )                          ;
        END;

VAR
        n   :   integer  ;
        r   :   real     ;
        S   :   string   ;
        So  :   Stack    ;


BEGIN

        So.Create                           ;
        So.Print                            ;
        n   := 23                           ;
        So.Push  ( n )                      ;
        S   := '3 guesses '                 ;
        So.Push  ( S )                      ;
        r   :=  1.23                        ;
        So.Push  ( r )                      ;
        WriteLn  ( 'Peep : ', So.Peep  )    ;
        So.Push  ( 'Nice Try' )             ;
        So.Print                            ;
        WriteLn                             ;
        WriteLn  ( 'SecPop : ',So.SecPop )  ;
        WriteLn  ( 'SecPop : ',So.SecPop )  ;
        WriteLn  ( 'SecPop : ',So.SecPop )  ;
        WriteLn  ( 'SecPop : ',So.SecPop )  ;
        So.Print                            ;
END.
JPD 2021/07/03

Output:

<empty stack>

Peep : 1.23

<top>

Nice Try

1.23

3 guesses

23

<bottom>

SecPop : Nice Try

SecPop : 1.23

SecPop : 3 guesses

SecPop : 23

<empty stack>

FreeBASIC

We first use a macro to define a generic Stack type :

' FB 1.05.0 Win64

' stack_rosetta.bi
' simple generic Stack type

#Define Stack(T) Stack_##T

#Macro Declare_Stack(T)
Type Stack(T)
 Public:
    Declare Constructor()
    Declare Destructor()
    Declare Property capacity As Integer
    Declare Property count As Integer 
    Declare Property empty As Boolean
    Declare Property top As T 
    Declare Function pop() As T   
    Declare Sub push(item As T)
  Private:
    a(any) As T 
    count_ As Integer = 0  
    Declare Function resize(size As Integer) As Integer    
End Type

Constructor Stack(T)()
  Redim a(0 To 0) '' create a default T instance for various purposes 
End Constructor

Destructor Stack(T)()
  Erase a
End Destructor

Property Stack(T).capacity As Integer
  Return UBound(a)
End Property
 
Property Stack(T).count As Integer
  Return count_
End Property

Property Stack(T).empty As Boolean
  Return count_ = 0
End Property

Property Stack(T).top As T
  If count_ > 0 Then
    Return a(count_)
  End If
  Print "Error: Attempted to access 'top' element of an empty stack"
  Return a(0)  '' return default element 
End Property

Function Stack(T).pop() As T
  If count_ > 0 Then
    Dim value As T = a(count_)
    a(count_) = a(0)  '' zero element to be removed
    count_ -= 1
    Return value
  End If
  Print "Error: Attempted to remove 'top' element of an empty stack"
  Return a(0)  '' return default element
End Function

Sub Stack(T).push(item As T)
  Dim size As Integer = UBound(a)
  count_ += 1
  If count_ >  size Then
    size = resize(size)
    Redim Preserve a(0 to size)
  End If
  a(count_) = item   
End Sub

Function Stack(T).resize(size As Integer) As Integer
  If size = 0 Then
    size = 4
  ElseIf size <= 32 Then
    size  = 2 * size
  Else
    size += 32
  End If
  Return size
End Function
  
#EndMacro

We now use this type to create a Stack of Dog instances :

' FB 1.05.0 Win64

#Include "stack_rosetta.bi"

Type Dog
  name As String
  age As Integer
  Declare Constructor
  Declare Constructor(name_ As string, age_ As integer)
  Declare Operator Cast() As String
end type

Constructor Dog  '' default constructor
End Constructor

Constructor Dog(name_ As String, age_ As Integer)
  name = name_
  age = age_
End Constructor

Operator Dog.Cast() As String
  Return "[" + name + ", " + Str(age) + "]"
End Operator

Declare_Stack(Dog) '' expand Stack type for Dog instances

Dim dogStack As Stack(Dog)

Var cerberus = Dog("Cerberus", 10)
Var rover    = Dog("Rover", 3)
Var puppy    = Dog("Puppy", 0)
With dogStack  '' push these Dog instances onto the stack
  .push(cerberus)
  .push(rover)
  .push(puppy)
End With
Print "Number of dogs on the stack :" ; dogStack.count
Print "Capacity of dog stack       :" ; dogStack.capacity
Print "Top dog                     : "; dogStack.top
dogStack.pop()
Print "Top dog now                 : "; dogStack.top
Print "Number of dogs on the stack :" ; dogStack.count
dogStack.pop()
Print "Top dog now                 : "; dogStack.top
Print "Number of dogs on the stack :" ; dogStack.count
Print "Is stack empty now          : "; dogStack.empty
Print
Print "Press any key to quit"
Sleep
Output:
Number of dogs on the stack : 3
Capacity of dog stack       : 4
Top dog                     : [Puppy, 0]
Top dog now                 : [Rover, 3]
Number of dogs on the stack : 2
Top dog now                 : [Cerberus, 10]
Number of dogs on the stack : 1
Is stack empty now          : false

Frink

Frink's array class has all of the methods to make it usable as a stack or a deque. The methods are called array.push[x], array.pop[], and array.isEmpty[]

a = new array
a.push[1]
a.push[2]
a.peek[]
while ! a.isEmpty[]
   println[a.pop[]]

Genie

[indent=4]
/*
   Stack, in Genie, with GLib double ended Queues
   valac stack.gs
*/
init
    var stack = new Queue of int()

    // push
    stack.push_tail(2)
    stack.push_tail(1)

    // pop (and peek at top)
    print stack.pop_tail().to_string()
    print stack.peek_tail().to_string()

    // empty
    print "stack size before clear: " + stack.get_length().to_string()
    stack.clear()
    print "After clear, stack.is_empty(): " + stack.is_empty().to_string()
Output:
prompt$ valac stack.gs
prompt$ ./stack
1
2
stack size before clear: 1
After clear, stack.is_empty(): true

Go

Go slices make excellent stacks without defining any extra types, functions, or methods. For example, to keep a stack of integers, simply declare one as,

var intStack []int

Use the built in append function to push numbers on the stack:

intStack = append(intStack, 7)

Use a slice expression with the built in len function to pop from the stack:

popped, intStack = intStack[len(intStack)-1], intStack[:len(intStack)-1]

The test for an empty stack:

len(intStack) == 0

And to peek at the top of the stack:

intStack[len(intStack)-1]

It is idiomatic Go to use primitive language features where they are sufficient, and define helper functions or types and methods only as they make sense for a particular situation. Below is an example using a type with methods and idiomatic "ok" return values to avoid panics. It is only an example of something that might make sense in some situation.

package main

import "fmt"

type stack []interface{}

func (k *stack) push(s interface{}) {
    *k = append(*k, s)
}

func (k *stack) pop() (s interface{}, ok bool) {
    if k.empty() {
        return
    }
    last := len(*k) - 1
    s = (*k)[last]
    *k = (*k)[:last]
    return s, true
}

func (k *stack) peek() (s interface{}, ok bool) {
    if k.empty() {
        return
    }
    last := len(*k) - 1
    s = (*k)[last]
    return s, true
}

func (k *stack) empty() bool {
    return len(*k) == 0
}

func main() {
    var s stack
    fmt.Println("new stack:", s)
    fmt.Println("empty?", s.empty())
    s.push(3)
    fmt.Println("push 3. stack:", s)
    fmt.Println("empty?", s.empty())
    s.push("four")
    fmt.Println(`push "four" stack:`, s)
    if top, ok := s.peek(); ok {
        fmt.Println("top value:", top)
    } else {
        fmt.Println("nothing on stack")
    }
    if popped, ok := s.pop(); ok {
        fmt.Println(popped, "popped.  stack:", s)
    } else {
        fmt.Println("nothing to pop")
    }
}
Output:
new stack: []
empty? true
push 3. stack: [3]
empty? false
push "four" stack: [3 four]
top value: four
four popped.  stack: [3]

GDScript

In GDScript there is built-in Array class, that implements either 'push', 'pop', 'top' and 'empty' methods. Method names are:

  • push -> push_back
  • pop -> pop_back
  • top -> back
  • empty -> is_empty
extends Node2D

func _ready() -> void:
	# Empty stack creation.
	var stack : Array = []
	
	# In Godot 4.2.1 nothing happens here.
	stack.pop_back()
	
	if stack.is_empty():
		print("Stack is empty.")
	
	stack.push_back(3)
	stack.push_back("Value")
	stack.push_back(1.5e32)
	print(stack)
	
	print("Last element is: " + str(stack.back()))
	
	stack.pop_back()
	print(stack)
	print("Last element is: " + str(stack.back()))
	if not stack.is_empty():
		print("Stack is not empty.")
	return
Output:
Stack is empty.
[3, "Value", 149999999999999999042044051849216]
Last element is: 149999999999999999042044051849216
[3, "Value"]
Last element is: Value
Stack is not empty.

Groovy

In Groovy, all lists have stack semantics, including "push()" and "pop()" methods, an "empty" property, and a "last()" method as a stand-in for "top/peek" semantics. Calling "pop()" on an empty list throws an exception.

Of course, these stack semantics are not exclusive. Elements of the list can still be accessed and manipulated in myriads of other ways.

def stack = []
assert stack.empty

stack.push(55)
stack.push(21)
stack.push('kittens')
assert stack.last() == 'kittens'
assert stack.size() == 3
assert ! stack.empty
 
println stack

assert stack.pop() == "kittens"
assert stack.size() == 2

println stack

stack.push(-20)

println stack

stack.push( stack.pop() * stack.pop() )
assert stack.last() == -420
assert stack.size() == 2

println stack

stack.push(stack.pop() / stack.pop())
assert stack.size() == 1

println stack

println stack.pop()
assert stack.size() == 0
assert stack.empty

try { stack.pop() } catch (NoSuchElementException e) { println e.message }
Output:
[55, 21, kittens]
[55, 21]
[55, 21, -20]
[55, -420]
[-7.6363636364]
-7.6363636364
Cannot pop() an empty List

Haskell

The Haskell solution is trivial, using a list. Note that pop returns both the element and the changed stack, to remain purely functional.

type Stack a = [a]

create :: Stack a
create = []

push :: a -> Stack a -> Stack a
push = (:)

pop :: Stack a -> (a, Stack a)
pop []     = error "Stack empty"
pop (x:xs) = (x,xs)

empty :: Stack a -> Bool
empty = null

peek :: Stack a -> a
peek []    = error "Stack empty"
peek (x:_) = x

We can make a stack that can be destructively popped by hiding the list inside a State monad.

import Control.Monad.State

type Stack a b = State [a] b

push :: a -> Stack a ()
push = modify . (:)

pop :: Stack a a
pop = do
    nonEmpty
    x <- peek
    modify tail
    return x

empty :: Stack a Bool
empty = gets null

peek :: Stack a a
peek = nonEmpty >> gets head

nonEmpty :: Stack a ()
nonEmpty = empty >>= flip when (fail "Stack empty")

Icon and Unicon

Stacks (and double ended queues) are built into Icon and Unicon as part of normal list access. In addition to 'push' and 'pop', there are the functions 'put', 'get' (alias for pop), 'pull', list element addressing, and list sectioning (like sub-strings). Unicon extended 'insert' and 'delete' to work with lists. The programmer is free to use any or all of the list processing functions on any problem. The following illustrates typical stack usage:

procedure main()
stack := []                                     # new empty stack
push(stack,1)                                   # add item
push(stack,"hello",table(),set(),[],5)          # add more items of mixed types in order left to right
y := top(stack)                                 # peek
x := pop(stack)                                 # remove item
write("The stack is ",if isempty(stack) then "empty" else "not empty")
end

procedure isempty(x)           #: test if a datum is empty, return the datum or fail (task requirement)
if *x = 0 then return x        #  in practice just write *x = 0 or *x ~= 0 for is/isn't empty
end

procedure top(x)               #: return top element w/o changing stack
return x[1]                    #  in practice, just use x[1]
end

Io

aside from using built-in lists, a stack can be created using nodes like so:

Node := Object clone do(
    next := nil
    obj := nil
)

Stack := Object clone do(
    node := nil
    
    pop := method(
        obj := node obj
        node = node next
        obj
    )
    
    push := method(obj,
        nn := Node clone
        nn obj = obj
        nn next = self node
        self node = nn
    )
)

Ioke

Stack = Origin mimic do(
  initialize = method(@elements = [])
  pop = method(@elements pop!)
  empty = method(@elements empty?)
  push = method(element, @elements push!(element))
)

IS-BASIC

100 LET N=255 ! Size of stack
110 NUMERIC STACK(1 TO N)
120 LET PTR=1
130 DEF PUSH(X)
140   IF PTR>N THEN
150     PRINT "Stack is full.":STOP 
160   ELSE 
170     LET STACK(PTR)=X:LET PTR=PTR+1
180   END IF 
190 END DEF 
200 DEF POP
210   IF PTR=1 THEN
220     PRINT "Stack is empty.":STOP 
230   ELSE 
240     LET PTR=PTR-1:LET POP=STACK(PTR)
250   END IF 
260 END DEF 
270 DEF EMPTY
280   LET PTR=1
290 END DEF 
300 DEF TOP=STACK(PTR-1)
310 CALL PUSH(3):CALL PUSH(5)
320 PRINT POP+POP

J

stack=: ''
push=: monad def '0$stack=:stack,y'
pop=: monad def 'r[ stack=:}:stack[ r=.{:stack'
empty=: monad def '0=#stack'

Example use:

   push 9

   pop ''
9
   empty ''
1

pop and empty ignore their arguments. In this implementation. push returns an empty list.

Java

The collections framework includes a Stack class. Let's test it:

import java.util.Stack;

public class StackTest {
    public static void main( final String[] args ) {
        final Stack<String> stack = new Stack<String>();

        System.out.println( "New stack empty? " + stack.empty() );

        stack.push( "There can be only one" );
        System.out.println( "Pushed stack empty? " + stack.empty() );
        System.out.println( "Popped single entry: " + stack.pop() );

        stack.push( "First" );
        stack.push( "Second" );
        System.out.println( "Popped entry should be second: " + stack.pop() );

        // Popping an empty stack will throw...
        stack.pop();
        stack.pop();
    }
}
Output:
New stack empty? true
Pushed stack empty? false
Popped single entry: There can be only one
Popped entry should be second: Second
Exception in thread "main" java.util.EmptyStackException
	at java.util.Stack.peek(Stack.java:85)
	at java.util.Stack.pop(Stack.java:67)
	at StackTest.main(StackTest.java:21)

Alternatively, you might implement a stack yourself...

public class Stack{
    private Node first = null;
    public boolean isEmpty(){
        return first == null;
    }
    public Object Pop(){
        if(isEmpty()) 
            throw new Exception("Can't Pop from an empty Stack.");
        else{
            Object temp = first.value;
            first = first.next;
            return temp;
        }
    }
    public void Push(Object o){
        first = new Node(o, first);
    }
    class Node{
        public Node next;
        public Object value;
        public Node(Object value){
            this(value, null); 
        }
        public Node(Object value, Node next){
            this.next = next;
            this.value = value;
        }
    }
}
Works with: Java version 1.5
public class Stack<T>{
    private Node first = null;
    public boolean isEmpty(){
        return first == null;
    }
    public T Pop(){
        if(isEmpty()) 
            throw new Exception("Can't Pop from an empty Stack.");
        else{
            T temp = first.value;
            first = first.next;
            return temp;
        }
    }
    public void Push(T o){
        first = new Node(o, first);
    }
    class Node{
        public Node next;
        public T value;
        public Node(T value){
            this(value, null); 
        }
        public Node(T value, Node next){
            this.next = next;
            this.value = value;
        }
    }
}

JavaScript

The built-in Array class already has stack primitives.

var stack = [];
stack.push(1)
stack.push(2,3);
print(stack.pop());   // 3
print(stack.length);   // 2, stack empty if 0

Here's a constructor that wraps the array:

function Stack() {
    this.data = new Array();

    this.push  = function(element) {this.data.push(element)}
    this.pop   = function() {return this.data.pop()}
    this.empty = function() {return this.data.length == 0}
    this.peek  = function() {return this.data[this.data.length - 1]}
}

Here's an example using the revealing module pattern instead of prototypes.

function makeStack() {
  var stack = [];

  var popStack = function () {
    return stack.pop();
  };
  var pushStack = function () {
    return stack.push.apply(stack, arguments);
  };
  var isEmpty = function () {
    return stack.length === 0;
  };
  var peekStack = function () {
    return stack[stack.length-1];
  };
    
  return {
    pop: popStack,
    push: pushStack,
    isEmpty: isEmpty,
    peek: peekStack,
    top: peekStack
  };
}

Jsish

From Javascript entry. Being ECMAScript, Jsi supports stack primitives as part of the Array methods.

/* Stack, is Jsish */
var stack = [];
puts('depth:', stack.length);

stack.push(42);
stack.push('abc');
puts('depth:', stack.length);

puts('popped:', stack.pop());
if (stack.length) printf('not '); printf('empty\n');
puts('top:', stack[stack.length-1]);
puts('popped:', stack.pop());
if (stack.length) printf('not '); printf('empty\n');

puts('depth:', stack.length);
Output:
prompt$ jsish stack.jsi
depth: 0
depth: 2
popped: abc
not empty
top: 42
popped: 42
empty
depth: 0

jq

For most purposes, jq's arrays can be used for stacks if needed, without much further ado. However, since the present task requires the definition of special stack-oriented operations, we shall start with the following definitions:

# create a Stack
def Stack: {stack: []};

# check an object is a Stack
def isStack:
  type == "object" and has("stack") and (.stack|type) == "array";

def pop:
  if .stack|length == 0 then "pop: stack is empty" | error
  else {stack: .stack[1:], item: .stack[0]]
  end;

def push($x):
  .stack = [$x] + .stack | .item = null;

def size:
  .stack | length;

def isEmpty:
  size == 0;

Depending on context, additional code to check for or to enforce type discipline could be added, but is omitted for simplicity here. If using the C implementation of jq, the function names could also be prefixed with "Stack::" to distinguish them as stack-oriented operations.

For some purposes, this approach may be sufficient, but it can easily become cumbersome if a sequence of operations must be performed while also producing outputs that reflect intermediate states.

Suppose for example that we wish to create a stack, push some value, and then pop the stack, obtaining the popped value as the final result. This could be accomplished by the pipe:

Stack | push(3) | pop | .item

Now suppose we also wish to record the size of the stack after each of these three operations. One way to do this would be to write:

        Stack
| size, (push(3)
| size, (pop
| size, .item ))

Unfortunately this approach is error-prone and can quickly become tedious, so we introduce an "observer" function that can "observe" intermediate states following any operation. With observer/2 as defined below, we can instead write:

null
| observe(Stack;   size)
| observe(push(3); size)
| observe(pop;     size)
| .emit, item

The idea is that each call to `observe` updates the "emit" slot, so that all the accumulated messages are available at any point in the pipeline.

# Input: an object
# Output: the updated object with .emit filled in from `update|emit`.
# `emit` may produce a stream of values, which need not be strings.
def observe(update; emit):
  def s(stream): reduce stream as $_ (null;
    if $_ == null then .
    elif . == null then "\($_)"
    else . + "\n\($_)"
    end);
  .emit as $x
  | update
  | .emit = s($x // null, emit);


Julia

Works with: Julia version 0.6

The built-in Array class already has efficient (linear amortized time) stack primitives.

stack = Int[]           # []
@show push!(stack, 1)   # [1]
@show push!(stack, 2)   # [1, 2]
@show push!(stack, 3)   # [1, 2, 3]
@show pop!(stack)       # 3
@show length(stack)     # 2
@show empty!(stack)     # []
@show isempty(stack)    # true

K

stack:()
push:{stack::x,stack}
pop:{r:*stack;stack::1_ stack;r}
empty:{0=#stack}

/example:
stack:()
  push 3
  stack
,3
  push 5
  stack
5 3
  pop[]
5
  stack
,3
  empty[]
0
  pop[]
3
  stack
!0
  empty[]
1

Kotlin

Rather than use the java.util.Stack<E> class, we will write our own simple Stack<E> class for this task:

// version 1.1.2

class Stack<E> {
    private val data = mutableListOf<E>()

    val size get() = data.size

    val empty get() = size == 0

    fun push(element: E) = data.add(element)

    fun pop(): E {
        if (empty) throw RuntimeException("Can't pop elements from an empty stack")
        return data.removeAt(data.lastIndex)
    }

    val top: E
        get() {
            if (empty) throw RuntimeException("Empty stack can't have a top element")
            return data.last()
        }

    fun clear() = data.clear()

    override fun toString() = data.toString()
}

fun main(args: Array<String>) {
    val s = Stack<Int>()
    (1..5).forEach { s.push(it) }
    println(s)
    println("Size of stack = ${s.size}")
    print("Popping: ")
    (1..3).forEach { print("${s.pop()} ") }
    println("\nRemaining on stack: $s")
    println("Top element is now ${s.top}")
    s.clear()
    println("After clearing, stack is ${if(s.empty) "empty" else "not empty"}")
    try {
        s.pop()
    }
    catch (e: Exception) {
        println(e.message)
    }
}
Output:
[1, 2, 3, 4, 5]
Size of stack = 5
Popping: 5 4 3
Remaining on stack: [1, 2]
Top element is now 2
After clearing, stack is empty
Can't pop elements from an empty stack

Lambdatalk

The APIs of stacks and queues are built on lambdatalk array primitives, [A.new, A.disp, A.join, A.split, A.array?, A.null?, A.empty?, A.in?, A.equal?, A.length, A.get, A.first, A.last, A.rest, A.slice, A.duplicate, A.reverse, A.concat, A.map, A.set!, A.addlast!, A.sublast!, A.addfirst!, A.subfirst!, A.reverse!, A.sort!, A.swap!, A.lib]. Note that the [A.addlast!, A.sublast!, A.addfirst!, A.subfirst!] primitives are the standard [push!, shift!, pop!, unshift!] ones.

{def stack.add 
 {lambda {:v :s}
  {let { {_ {A.addfirst! :v :s}}}
       } ok}}
-> stack.add

{def stack.get 
 {lambda {:s} 
  {let { {:v {A.first :s}} 
         {_ {A.subfirst! :s}} 
       } :v}}}
-> stack.get

{def stack.peek
 {lambda {:s}
  {A.first :s}}}
-> stack.peek

{def stack.empty?
 {lambda {:s}
  {A.empty? :s}}}
-> stack.empty?

{def S {A.new}}    -> S      []
{stack.add 1 {S}}  ->  ok    [1]
{stack.add 2 {S}}  ->  ok    [2,1]
{stack.add 3 {S}}  ->  ok    [3,2,1]
{stack.empty? {S}} -> false 
{stack.get {S}}    -> 3      [2,1]
{stack.add 4 {S}}  ->  ok    [4,2,1]
{stack.peek {S}}   -> 4      [4,2,1]
{stack.get {S}}    -> 4      [2,1]
{stack.get {S}}    -> 2      [1]
{stack.get {S}}    -> 1      []
{stack.get {S}}    -> undefined      
{stack.empty? {S}} -> true

lang5

: cr  "\n" . ;
: empty?  dup execute length if 0 else -1 then swap drop ;
: pop  dup execute length 1 - extract swap drop ;
: push  dup execute rot append over ;
: s. stack execute . ;

[] '_ set
: stack '_ ;
stack                     # local variable
    1 swap push set
    2 swap push set s. cr # [    1     2  ]
    pop .           s. cr # 2     [    1  ]
    pop drop
    empty? .              # -1

Lasso

Lasso Arrays natively supports push and pop.

local(a) = array

#a->push('a') 
#a->push('b') 
#a->push('c')

#a->pop // c
#a->pop // b
#a->pop // a
#a->pop // null

Liberty BASIC

global stack$
stack$=""

randomize .51
for i = 1 to 10
    if rnd(1)>0.5 then
        print  "pop => ";pop$()
    else
        j=j+1
        s$ = chr$(j + 64)
        print "push ";s$
        call push s$
    end if
next

print
print "Clean-up"
do
    print  "pop => ";pop$()
loop while not(empty())
print "Stack is empty"

end

'------------------------------------
sub push s$
    stack$=s$+"|"+stack$    'stack
end sub

function pop$()
    if stack$="" then pop$="*EMPTY*": exit function
    pop$=word$(stack$,1,"|")
    stack$=mid$(stack$,instr(stack$,"|")+1)
end function

function empty()
     empty =(stack$="")
end function

Lingo

-- parent script "Stack"

property _tos

on push (me, data)
  me._tos = [#data:data, #next:me._tos]
end

on pop (me)
  if voidP(me._tos) then return VOID
  data = me._tos.data
  me._tos = me._tos.next
  return data
end

on peek (me)
  if voidP(me._tos) then return VOID
  return me._tos.data
end

on empty (me)
  return voidP(me.peek())
end

UCB Logo has built-in methods for treating lists as stacks. Since they are destructive, they take the name of the stack rather than the list itself.

make "stack []
push "stack 1
push "stack 2
push "stack 3
print pop "stack   ; 3
print empty? :stack ; false

Logtalk

A stack can be trivially represented using the built-in representation for lists:

:- object(stack).

    :- public(push/3).
    push(Element, Stack, [Element| Stack]).

    :- public(pop/3).
    pop([Top| Stack], Top, Stack).

    :- public(empty/1)
    empty([]).

:- end_object.

LOLCODE

Translation of: UNIX Shell
HAI 2.3
HOW IZ I Init YR Stak
   Stak HAS A Length ITZ 0
IF U SAY SO

HOW IZ I Push YR Stak AN YR Value
  Stak HAS A SRS Stak'Z Length ITZ Value
  Stak'Z Length R SUM OF Stak'Z Length AN 1
IF U SAY SO

HOW IZ I Top YR Stak
  FOUND YR Stak'Z SRS DIFF OF Stak'Z Length AN 1
IF U SAY SO

HOW IZ I Pop YR Stak
  I HAS A Top ITZ I IZ Top YR Stak MKAY
  Stak'Z Length R DIFF OF Stak'Z Length AN 1
  FOUND YR Top
IF U SAY SO

HOW IZ I Empty YR Stak
  FOUND YR BOTH SAEM 0 AN Stak'Z Length
IF U SAY SO

I HAS A Stak ITZ A BUKKIT
I IZ Init YR Stak MKAY
I IZ Push YR Stak AN YR "Fred" MKAY
I IZ Push YR Stak AN YR "Wilma" MKAY
I IZ Push YR Stak AN YR "Betty" MKAY
I IZ Push YR Stak AN YR "Barney" MKAY

IM IN YR Loop UPPIN YR Dummy TIL I IZ Empty YR Stak MKAY
  VISIBLE I IZ Pop YR Stak MKAY
IM OUTTA YR Loop

KTHXBYE
Output:
Barney
Betty
Wilma
Fred

Lua

Tables have stack primitives by default:

stack = {}
table.insert(stack,3)
print(table.remove(stack)) --> 3

M2000 Interpreter

A Stack object can be used as LIFO or FIFO. Push statement push to top of stack. Read pop a value to a variable from top of stack. StackItem(1) read top item without modified stack. Data statement append items to bottom.

Module Checkit {
      a=Stack
      Stack a {
            Push 100, 200, 300
      }
      Print StackItem(a, 1)=300
      Stack a {
            Print StackItem(1)=300
            While not empty {
                  Read N
                  Print N
            }
      }
}
Checkit

Every module and function has a "current" stack. Number is a read only variable, which pop a value from current stack (or raise error if not number is in top of stack).

User functions get a new stack, and drop it at return. Modules take parent stack, and return stack to parent. So a Module can return values too. In M2000 a call happen without checkig signatures (except for special events calls). We have to leave stack at a proper state, when return from a module. Return/Execution stack is hidden and different from stack of values.

Module Checkit {
      Read a, b
      Print a, b
}
\\ add parameters in a FIFO, and this FIFO merged to current stack
Push 100
Checkit 10, 20
Print StackItem(1)=100
Module Checkit {
      Read a, b
      Print a=20, b=100
}
Checkit 20

Function alfa {
      k=0
      n=0
      while not empty {
            k+=number
            n++
      }
      if n=0 then Error "No parameters found"
      =k/n
}

Print alfa(1,2,3,4)=2.5

Maple

with(stack): # load the package, to allow use of short command names

s := stack:-new(a, b):

push(c, s):

# The following statements terminate with a semicolon and print output.
top(s);
pop(s);
pop(s);
empty(s);
pop(s);
empty(s);
Output:
                                      c

                                      c

                                      b

                                    false

                                      a

                                    true

Mathematica/Wolfram Language

EmptyQ[a_] := If[Length[a] == 0, True, False]
SetAttributes[Push, HoldAll];[a_, elem_] := AppendTo[a, elem]
SetAttributes[Pop, HoldAllComplete]; 
Pop[a_] := If[EmptyQ[a], False, b = Last[a]; Set[a, Most[a]]; b]
Peek[a_] := If[EmptyQ[a], False, Last[a]]

Example use:
stack = {};Push[stack, 1]; Push[stack, 2]; Push[stack, 3]; Push[stack, 4];
Peek[stack]
->4
Pop[stack] 
->4
Peek[stack]
->3

MATLAB / Octave

Here is a simple implementation of a stack, that works in Matlab and Octave. It is closely related to the queue/fifo example.

mystack = {};
   
% push 
mystack{end+1} = x; 

%pop
x = mystack{end};  mystack{end} = [];

%peek,top
x = mystack{end};

% empty 
isempty(mystack)

Below is another solution, that encapsulates the fifo within the object-orientated "class" elements supported by Matlab. The given implementation is exactly the same as the MATLAB FIFO example, except that the "push()" function is modified to add stuff to the end of the queue instead of the beginning. This is a naive implementation, for rigorous applications this should be modified to initialize the LIFO to a buffered size, so that the "pop()" and "push()" functions don't resize the cell array that stores the LIFO's elements, every time they are called.

To use this implementation you must save this code in a MATLAB script file named "LIFOQueue.m" which must be saved in a folder named @LIFOQueue in your MATLAB directory.

%This class impliments a standard LIFO queue.
classdef LIFOQueue
    
    properties  
        queue
    end
    
    methods
         
        %Class constructor
        function theQueue = LIFOQueue(varargin)
            
            if isempty(varargin) %No input arguments
                
                %Initialize the queue state as empty
                theQueue.queue = {};
            elseif (numel(varargin) > 1) %More than 1 input arg
                
                %Make the queue the list of input args
                theQueue.queue = varargin;
            elseif iscell(varargin{:}) %If the only input is a cell array
                
                %Make the contents of the cell array the elements in the queue 
                theQueue.queue = varargin{:};
            else %There is one input argument that is not a cell
                
                %Make that one arg the only element in the queue
                theQueue.queue = varargin;
            end
            
        end        
        
        %push() - pushes a new element to the end of the queue
        function push(theQueue,varargin)
            
            if isempty(varargin)
                theQueue.queue(end+1) = {[]};
            elseif (numel(varargin) > 1) %More than 1 input arg
                
                %Make the queue the list of input args
                theQueue.queue( end+1:end+numel(varargin) ) = varargin;
            elseif iscell(varargin{:}) %If the only input is a cell array
                
                %Make the contents of the cell array the elements in the queue 
                theQueue.queue( end+1:end+numel(varargin{:}) ) = varargin{:};
            else %There is one input argument that is not a cell
                
                %Make that one arg the only element in the queue
                theQueue.queue{end+1} = varargin{:};                
            end
            
            %Makes changes to the queue permanent
            assignin('caller',inputname(1),theQueue);  
            
        end
        
        %pop() - pops the first element off the queue
        function element = pop(theQueue)
           
            if empty(theQueue)
                error 'The queue is empty'
            else
                %Returns the first element in the queue
                element = theQueue.queue{end};
                
                %Removes the first element from the queue
                theQueue.queue(end) = [];
                
                %Makes changes to the queue permanent
                assignin('caller',inputname(1),theQueue);
            end
        end
        
        %empty() - Returns true if the queue is empty
        function trueFalse = empty(theQueue)
           
            trueFalse = isempty(theQueue.queue);
            
        end
        
    end %methods
end

Sample Usage:

>> myLIFO = LIFOQueue(1,'fish',2,'fish','red fish','blue fish')
 
myLIFO =
 
	LIFOQueue

>> myLIFO.pop()

ans =

blue fish

>> myLIFO.push('Cat Fish')
>> myLIFO.pop()

ans =

Cat Fish

>> myLIFO.pop()

ans =

red fish

>> empty(myLIFO)

ans =

     0

Maxima

/* lists can be used as stacks; Maxima provides pop and push */

load(basic)$

a: []$
push(25, a)$
push(7, a)$
pop(a);

emptyp(a);
length(a);

Mercury

Efficient, generic stacks are provided as part of the standard library in Mercury. For sake of illustration, here is how a simple stack could be implemented.

:- module sstack.

:- interface.

% We're going to call the type sstack (simple stack) because we don't want to get it
% accidentally confused with the official stack module in the standard library.
:- type sstack(T).

:- func sstack.new = sstack(T).
:- pred sstack.is_empty(sstack(T)::in) is semidet.
:- func sstack.push(sstack(T), T) = sstack(T).
:- pred sstack.pop(T::out, sstack(T)::in, sstack(T)::out) is semidet.

:- implementation.

:- import_module list.

:- type sstack(T)
   --->  sstack(list(T)).

sstack.new = sstack([]).

sstack.is_empty(sstack([])).

sstack.push(Stack0, Elem) = Stack1 :-
   Stack0 = sstack(Elems),
   Stack1 = sstack([Elem | Elems]).

sstack.pop(Elem, !Stack) :-
   !.Stack = sstack([Elem | Elems]),
   !:Stack = sstack(Elems).

:- end_module sstack.

It should be noted that this is purely an illustrative example of a very simple stack. A real implementation would have predicate (:- pred) versions of the functions (:- func), for example, for consistency's sake with either the functions implemented in terms of the predicates or vice versa. The real library implementation also features more functionality including both semi-deterministic and deterministic versions of some functions/predicates as well as the ability to push a list of values in one operation.

Some of the implementation decisions above need an explanation. new/0 and push/2 were implemented as functions both for pedagogical reasons (a desire to show function syntax) and because they are a natural fit for functional thought: 0 or more inputs, one output, deterministic. is_empty/1 was implemented as a predicate because it's a single, simple succeed/fail test which is precisely what a predicate is in logic. pop/3 was implemented as a predicate because it has two outputs (the element and the new stack) and because it is semi-deterministic (it will fail if the stack is empty).

Note also that while pop/3 has three parameters, the function implementation looks like it has two. This is because the !Stack "parameter" is actually a pair of parameters using Mercury's state variable notation. !Stack is, in effect, two variables: !.Stack and !:Stack, input and output respectively. Using state variable notation here is a bit of overkill but again was brought in for pedagogical reasons to show the syntax.

MIPS Assembly

addi sp,sp,-4
sw t0,0(sp)      ;push

lw t0,0(sp)
addi sp,sp,4     ;pop

lw t0,0(sp)      ;top

"Empty" requires you to know the starting value of SP. Since it's hardware-dependent, there's no one answer for this part of the task.

MiniScript

// Note in Miniscript, a value of zero is false,
// and any other number is true.
// therefore the .len function works as the inverse of a .empty function
stack = [2, 4, 6]
stack.push 8
print "Stack is " + stack
print "Adding '9' to stack " + stack.push(9)
print "Top of stack is " + stack.pop
print "Stack is " + stack
if stack.len then
    print "Stack is not empty"
else
    print "Stack is empty"
end if
Output:
Stack is [2, 4, 6, 8]
Adding '9' to stack [2, 4, 6, 8, 9]
Top of stack is 9
Stack is [2, 4, 6, 8]
Stack is not empty

Nanoquery

class Stack
        declare internalList

        // constructor
        def Stack()
                internalList = list()
        end

        def push(val)
                internalList.append(val)
        end

        def pop()
                val = internalList[int(len($internalList) - 1)]
                internalList.remove(val)

                return val
        end

        def empty()
                return len(internalList) = 0
        end
end

Nemerle

Mutable stacks are available in System.Collections, System.Collections.Generic and Nemerle.Collections depending on what functionality beyond the basics you want. An immutable stack could be implemented fairly easily, as, for example, this quick and dirty list based implementation.

public class Stack[T]
{
    private stack : list[T];
    
    public this()
    {
        stack = [];
    }
    
    public this(init : list[T])
    {
        stack = init;
    }
    
    public Push(item : T) : Stack[T]
    {
        Stack(item::stack)
    }
    
    public Pop() : T * Stack[T]
    {
        (stack.Head, Stack(stack.Tail))
    }
    
    public Peek() : T
    {
        stack.Head
    }
    
    public IsEmpty() : bool
    {
        stack.Length == 0
    }
}

NetRexx

/* NetRexx ************************************************************
* 13.08.2013 Walter Pachl  translated from REXX version 2
**********************************************************************/
options replace format comments java crossref savelog symbols nobinary

stk = create_stk

say push(stk,123) 'from push'
say empty(stk) 
say peek(stk)     'from peek'
say pull(stk)     'from pull'
say empty(stk) 
Say pull(stk)     'from pull'

method create_stk static returns Rexx
  stk = ''
  stk[0] = 0
  return stk

method push(stk,v) static
  stk[0]=stk[0]+1
  stk[stk[0]]=v
  Return v

method peek(stk) static
  x=stk[0]
  If x=0 Then
    Return 'stk is empty'
  Else
    Return stk[x]

method pull(stk) static
  x=stk[0]
  If x=0 Then
    Return 'stk is empty'
  Else Do
    stk[0]=stk[0]-1
    Return stk[x]
    End

method empty(stk) static
  Return stk[0]=0
Output:
123 from push
0
123 from peek
123 from pull
1
stk is empty from pull

Nim

In Nim, the sequences offer all the functionalities of a stack. Procedure add appends an item at the end, procedure pop returns the last element and removes it from the sequence. And it’s easy to check if if the sequence is empty with the procedure len which returns its length.

If we want a stack type limited to the four or five functions of the task, it is possible to define a distinct generic type Stack[T] derived from seq[T]. The code will be typically as follows. Note that we have defined a procedure top to get the value of the top item, another mtop to get a mutable reference to the top item and also a procedure mtop= to assign directly a value to the top item.

type Stack[T] = distinct seq[T]

func initStack[T](initialSize = 32): Stack[T] =
  Stack[T](newSeq[T](initialSize))

func isEmpty[T](stack: Stack[T]): bool =
  seq[T](stack).len == 0

func push[T](stack: var Stack[T]; item: sink T) =
  seq[T](stack).add(item)

func pop[T](stack: var Stack[T]): T =
  if stack.isEmpty:
    raise newException(IndexDefect, "stack is empty.")
  seq[T](stack).pop()

func top[T](stack: Stack[T]): T =
  if stack.isEmpty:
    raise newException(IndexDefect, "stack is empty.")
  seq[T](stack)[^1]

func mtop[T](stack: var Stack[T]): var T =
  if stack.isEmpty:
    raise newException(IndexDefect, "stack is empty.")
  seq[T](stack)[^1]

func `mtop=`[T](stack: var Stack[T]; value: T) =
  if stack.isEmpty:
    raise newException(IndexDefect, "stack is empty.")
  seq[T](stack)[^1] = value

when isMainModule:

  var s = initStack[int]()
  s.push 2
  echo s.pop
  s.push 3
  echo s.top
  s.mtop += 1
  echo s.top
  s.mtop = 5
  echo s.top
Output:
2
3
4
5

Oberon-2

Works with: oo2c version 2
MODULE Stacks;
IMPORT 
  Object,
  Object:Boxed,
  Out := NPCT:Console;

TYPE
  Pool(E: Object.Object) = POINTER TO ARRAY OF E;
  Stack*(E: Object.Object) = POINTER TO StackDesc(E);
  StackDesc*(E: Object.Object) = RECORD
    pool: Pool(E);
    cap-,top: LONGINT;
  END;

  PROCEDURE (s: Stack(E)) INIT*(cap: LONGINT);
  BEGIN
    NEW(s.pool,cap);s.cap := cap;s.top := -1
  END INIT;

  PROCEDURE (s: Stack(E)) Top*(): E;
  BEGIN
    RETURN s.pool[s.top]
  END Top;

  PROCEDURE (s: Stack(E)) Push*(e: E);
  BEGIN
    INC(s.top);
    ASSERT(s.top < s.cap);
    s.pool[s.top] := e;
  END Push;

  PROCEDURE (s: Stack(E)) Pop*(): E;
  VAR
    resp: E;
  BEGIN
    ASSERT(s.top >= 0);
    resp := s.pool[s.top];DEC(s.top);
    RETURN resp
  END Pop;

  PROCEDURE (s: Stack(E)) IsEmpty(): BOOLEAN;
  BEGIN
    RETURN s.top < 0
  END IsEmpty;

  PROCEDURE (s: Stack(E)) Size*(): LONGINT;
  BEGIN
    RETURN s.top + 1
  END Size;

  PROCEDURE Test;
  VAR
    s: Stack(Boxed.LongInt);
  BEGIN
    s := NEW(Stack(Boxed.LongInt),100);
    s.Push(NEW(Boxed.LongInt,10));
    s.Push(NEW(Boxed.LongInt,100));
    Out.String("size: ");Out.Int(s.Size(),0);Out.Ln;
    Out.String("pop: ");Out.Object(s.Pop());Out.Ln;
    Out.String("top: ");Out.Object(s.Top());Out.Ln;
    Out.String("size: ");Out.Int(s.Size(),0);Out.Ln
  END Test;
 
BEGIN 
  Test
END Stacks.
Output:
size: 2
pop: 100
top: 10
size: 1
Works with: AOS
MODULE Stacks; (** AUTHOR ""; PURPOSE ""; *)

IMPORT
	Out := KernelLog;

TYPE	
	Object = OBJECT
	END Object;
	
	Stack* = OBJECT
	VAR
		top-,capacity-: LONGINT;
		pool: POINTER TO ARRAY OF Object;
		
		PROCEDURE & InitStack*(capacity: LONGINT);
		BEGIN
			SELF.capacity := capacity;
			SELF.top := -1;
			NEW(SELF.pool,capacity)
		END InitStack;
		
		PROCEDURE Push*(a:Object);
		BEGIN
			INC(SELF.top);
			ASSERT(SELF.top < SELF.capacity,100);
			SELF.pool[SELF.top] := a
		END Push;
		
		PROCEDURE Pop*(): Object;
		VAR
			r: Object;
		BEGIN
			ASSERT(SELF.top >= 0);
			r := SELF.pool[SELF.top];
			DEC(SELF.top);RETURN r
		END Pop;
		
		PROCEDURE Top*(): Object;
		BEGIN
			ASSERT(SELF.top >= 0);
			RETURN SELF.pool[SELF.top]
		END Top;
		
		PROCEDURE IsEmpty*(): BOOLEAN;
		BEGIN
			RETURN SELF.top < 0
		END IsEmpty;
		
	END Stack;
	
	BoxedInt = OBJECT
	(Object)
	VAR
		val-: LONGINT;

	PROCEDURE & InitBoxedInt*(CONST val: LONGINT);
	BEGIN	
		SELF.val := val
	END InitBoxedInt;

	END BoxedInt;

	PROCEDURE Test*;
	VAR
		s: Stack;
		bi: BoxedInt;
		obj: Object;
	BEGIN
		NEW(s,10); (* A new stack of ten objects *)
		NEW(bi,100);s.Push(bi);
		NEW(bi,102);s.Push(bi);		
		NEW(bi,104);s.Push(bi);
		Out.Ln;
		Out.String("Capacity:> ");Out.Int(s.capacity,0);Out.Ln;
		Out.String("Size:> ");Out.Int(s.top + 1,0);Out.Ln;
		obj := s.Pop(); obj := s.Pop();
		WITH obj: BoxedInt DO 
			Out.String("obj:> ");Out.Int(obj.val,0);Out.Ln
		ELSE
			Out.String("Unknown object...");Out.Ln;
		END (* with *)
	END Test;
END Stacks.
Output:
Capacity:> 10
Size:> 3
obj:> 102

Objeck

Class library support for Stack/IntStack/FloatStack

stack := IntStack->New();
stack->Push(13);
stack->Push(7);
(stack->Pop() + stack->Pop())->PrintLine();
stack->IsEmpty()->PrintLine();

Objective-C

Using a NSMutableArray:

NSMutableArray *stack = [NSMutableArray array]; // creating

[stack addObject:value]; // pushing

id value = [stack lastObject];
[stack removeLastObject]; // popping

[stack count] == 0 // is empty?

OCaml

Implemented as a singly-linked list, wrapped in an object:

exception Stack_empty

class ['a] stack =
  object (self)
    val mutable lst : 'a list = []

    method push x =
      lst <- x::lst

    method pop =
      match lst with
        []    -> raise Stack_empty
      | x::xs -> lst <- xs;
                 x

    method is_empty =
      lst = []
  end

Oforth

Stack is already defined at startup.

ListBuffer Class new: Stack
Stack method: push  self add ;
Stack method: pop   self removeLast ;
Stack method: top   self last ;

Usage :

: testStack
| s |
   Stack new ->s
   s push(10)
   s push(11)
   s push(12)
   s top println
   s pop println
   s pop println
   s pop println
   s isEmpty ifTrue: [ "Stack is empty" println ] ;
Output:
12
12
11
10
Stack is empty

Ol

Simplest stack can be implemented using 'cons' and 'uncons' primitives.

(define stack #null)
(print "stack is: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* pushing 1")
(define stack (cons 1 stack))
(print "stack is: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* pushing 2")
(define stack (cons 2 stack))
(print "stack is: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* pushing 3")
(define stack (cons 3 stack))
(print "stack is: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* poping")
(define-values (value stack) (uncons stack #f))
(print "value: " value)
(print "stack: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* poping")
(define-values (value stack) (uncons stack #f))
(print "value: " value)
(print "stack: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* poping")
(define-values (value stack) (uncons stack #f))
(print "value: " value)
(print "stack: " stack)
(print "is stack empty: " (eq? stack #null))

(print "* poping")
(define-values (value stack) (uncons stack #f))
(print "value: " value)
(print "stack: " stack)
(print "is stack empty: " (eq? stack #null))
Output:
stack is: ()
is stack empty: #true
* pushing 1
stack is: (1)
is stack empty: #false
* pushing 2
stack is: (2 1)
is stack empty: #false
* pushing 3
stack is: (3 2 1)
is stack empty: #false
* poping
value: 3
stack: (2 1)
is stack empty: #false
* poping
value: 2
stack: (1)
is stack empty: #false
* poping
value: 1
stack: ()
is stack empty: #true
* poping
value: #false
stack: ()
is stack empty: #true


But in real programs may be useful a more complex stack implementation based on coroutines (ol is a purely functional lisp, so it does not support mutators like 'set!').

(fork-server 'stack (lambda ()
   (let this ((me '()))
      (let*((envelope (wait-mail))
            (sender msg envelope))
         (case msg
            (['empty]
               (mail sender (null? me))
               (this me))
            (['push value]
               (this (cons value me)))
            (['pop]
               (cond
                  ((null? me)
                     (mail sender #false)
                     (this me))
                  (else
                     (mail sender (car me))
                     (this (cdr me))))))))))
(define (push value)
   (mail 'stack ['push value]))
(define (pop)
   (await (mail 'stack ['pop])))
(define (empty)
   (await (mail 'stack ['empty])))

(for-each (lambda (n)
      (print "pushing " n)
      (push n))
   (iota 5 1)) ; '(1 2 3 4 5)

(let loop ()
   (print "is stack empty: " (empty))
   (unless (empty)
      (begin
         (print "popping value, got " (pop))
         (loop))))
(print "done.")
Output:
pushing 1
pushing 2
pushing 3
pushing 4
pushing 5
is stack empty: #false
popping value, got 5
is stack empty: #false
popping value, got 4
is stack empty: #false
popping value, got 3
is stack empty: #false
popping value, got 2
is stack empty: #false
popping value, got 1
is stack empty: #true
done.

ooRexx

The ooRexx queue class functions as a stack as well (it is a dequeue really).

stack = .queue~of(123, 234)  -- creates a stack with a couple of items
stack~push("Abc")   -- pushing
value = stack~pull  -- popping
value = stack~peek  -- peeking
-- the is empty test
if stack~isEmpty then say "The stack is empty"

OxygenBasic

The real stack is freely available!

function f()
  sys a=1,b=2,c=3,d=4
  push a
  push b
  push c
  push d
  print a "," b "," c "," d 'result 1,2,3,4
  a=10
  b=20
  c=30
  d=40
  print a "," b "," c "," d 'result 10,20,30,40
  pop a
  pop b
  pop c
  pop d
  print a "," b "," c "," d 'result 4,3,2,1
end function

f

Oz

A thread-safe, list-based stack. Implemented as a module:

functor
export
   New
   Push
   Pop
   Empty
define   
   fun {New}
      {NewCell nil}
   end

   proc {Push Stack Element}
      NewStack
      %% Use atomic swap for thread safety
      OldStack = Stack := NewStack
   in
      NewStack = Element|OldStack
   end

   proc {Pop Stack ?Result}
      NewStack
      %% Use atomic swap for thread safety
      OldStack = Stack := NewStack
   in
      Result|NewStack = OldStack
   end
   
   fun {Empty Stack}
      @Stack == nil
   end
end

There is also a stack implementation in the standard library.

PARI/GP

push(x)=v=concat(v,[x]);;
pop()={
  if(#v,
    my(x=v[#v]);
    v=vecextract(v,1<<(#v-1)-1);
    x
  ,
    error("Stack underflow")
  )
};
empty()=v==[];
peek()={
  if(#v,
    v[#v]
  ,
    error("Stack underflow")
  )
};

Pascal

This implements stacks of integers in standard Pascal (should work on all existing Pascal dialects).

{ tStack is the actual stack type, tStackNode a helper type }
type
  pStackNode = ^tStackNode;
  tStackNode = record
                next: pStackNode;
                data: integer;
               end;
  tStack = record
            top: pStackNode;
           end;

{ Always call InitStack before using a stack }
procedure InitStack(var stack: tStack);
 begin
  stack.top := nil
 end;

{ This function removes all content from a stack; call before disposing, or before a local stack variable goes out of scope }
procedure ClearStack(var stack: tStack);
 var
  node: pStackNode;
 begin
  while stack.top <> nil do
   begin
    node := stack.top;
    stack.top := stack.top^.next;
    dispose(node);
   end
 end;

function StackIsEmpty(stack: tStack):Boolean;
 begin
  StackIsEmpty := stack.top = nil
 end;

procedure PushToStack(var stack: tStack; value: integer);
 var
  node: pStackNode;
 begin
  new(node);
  node^.next := stack.top;
  node^.data := value;
  stack.top := node
 end;

{ may only be called on a non-empty stack! }
function PopFromStack(var stack: tStack): integer;
 var
  node: pStackNode;
 begin
  node := stack.top;
  stack.top := node^.next;
  PopFromStack := node^.data;
  dispose(node);
 end;

Perl

Perl comes prepared to treat its arrays as stacks, giving us the push and pop functions for free. To add empty, we basically give a new name to "not":

sub empty{ not @_ }

Phix

with javascript_semantics
-- comparing a simple implementation against using the builtins:
sequence stack = {}
 
procedure push_(object what)
    stack = append(stack,what)
end procedure
 
function pop_()
    object what = stack[$]
    stack = stack[1..$-1]
    return what
end function
 
function empty_()
    return length(stack)=0
end function
 
?empty_()               -- 1
push_(5)
?empty_()               -- 0
push_(6)
?pop_()                 -- 6
?pop_()                 -- 5
?empty_()               -- 1

?"===builtins==="
requires("1.0.2") -- (latest bugfixes, plus top renamed as peep, for p2js)

integer sid = new_stack()
?stack_empty(sid)       -- 1
push(sid,5)
?stack_empty(sid)       -- 0
push(sid,6)
--?peep(sid)            -- 6 (leaving it there)
?pop(sid)               -- 6
?pop(sid)               -- 5
?stack_empty(sid)       -- 1

Note you get true/false rather than 1/0 under pwa/p2js (use printf(%t) for consistent results)

PHP

PHP arrays behave like a stack:

$stack = array();

empty( $stack ); // true

array_push( $stack, 1 ); // or $stack[] = 1;
array_push( $stack, 2 ); // or $stack[] = 2;

empty( $stack ); // false

echo array_pop( $stack ); // outputs "2"
echo array_pop( $stack ); // outputs "1"

PicoLisp

The built-in functions push and pop are used to maintain a stack (of any type).

(push 'Stack 3)
(push 'Stack 2)
(push 'Stack 1)
: Stack
-> (1 2 3)

: (pop 'Stack)
-> 1

: Stack
-> (2 3)

: (set 'Stack)  # empty
-> NIL

: Stack
-> NIL

Pike

Pike has a built in module ADT (Abstract Data Types) which among other things contains a stack.

object s = ADT.Stack();
s->push("a");
s->push("b");
write("top: %O, pop1: %O, pop2: %O\n",
      s->top(), s->pop(), s->pop());
s->reset(); // Empty the stack
Output:
top: "b", pop1: "b", pop2: "a"

PL/I

/* Any controlled variable may behave as a stack. */

declare s float controlled;

/* to push a value on the stack. */
allocate s;
s = 10;

/* To pop a value from the stack. */
put (s);
free s;

/* to peek at the top of stack> */
put (s);

/* To see whether the stack is empty */
if allocation(s) = 0 then ...

/* Note: popping a value from the stack, or peeking,          */
/* would usually require a check that the stack is not empty. */

/* Note: The above is a simple stack for S. */
/* S can be any kind of data structure, an array, etc. */

/* Example to push ten values onto the stack, and then to */
/* remove them.                                           */

/* Push ten values, obtained from the input, onto the stack: */
declare S float controlled;
do i = 1 to 10;
   allocate s;
   get list (s);
end;
/* To pop those values from the stack: */
do while (allocation(s) > 0);
   put skip list (s);
   free s;
end;
/* The values are printed in the reverse order, of course. */

PostScript

Library: initlib
% empty? is already defined.
/push {exch cons}.
/pop {uncons exch pop}.
[2 3 4 5 6] 1 push
= [1 2 3 4 5 6]
[1 2 3 4 5 6] pop
=[2 3 4 5 6]
[2 3 4 5 6] empty?
=false
[] empty?
=true

PowerShell

A new stack:

$stack = New-Object -TypeName System.Collections.Stack
# or
$stack = [System.Collections.Stack] @()

Push some stuff on the stack:

1, 2, 3, 4 | ForEach-Object {$stack.Push($_)}

Show stack as a string:

$stack -join ", "
Output:
4, 3, 2, 1

Pop the top level of the stack:

$stack.Pop()
Output:
4

Show stack as a string:

$stack -join ", "
Output:
3, 2, 1

Get a copy of the top level of the stack:

$stack.Peek()
Output:
3

The stack:

$stack
Output:
3
2
1

Prolog

Prolog is a particularly silly language to implement stack functions in, as the built-in lists can be treated as stacks in an ad hoc manner. Nonetheless, in the name of completeness:

% push( ELEMENT, STACK, NEW )
% True if NEW is [ELEMENT|STACK]
push(ELEMENT,STACK,[ELEMENT|STACK]).

% pop( STACK, TOP, NEW )
% True if TOP and NEW are head and tail, respectively, of STACK
pop([TOP|STACK],TOP,STACK).

% empty( STACK )
% True if STACK is empty
empty([]).

PureBasic

For LIFO function PureBasic normally uses linked lists. Usage as described above could look like;

Global NewList MyStack()

Procedure Push_LIFO(n)
  FirstElement(MyStack())
  InsertElement(MyStack())
  MyStack() = n
EndProcedure

Procedure Pop_LIFO()
  If FirstElement(MyStack())
    Topmost = MyStack()
    DeleteElement(MyStack())
  EndIf
  ProcedureReturn Topmost
EndProcedure

Procedure Empty_LIFO()
  Protected Result
  If ListSize(MyStack())=0
    Result = #True
  EndIf
  ProcedureReturn Result
EndProcedure

Procedure Peek_LIFO()
  If FirstElement(MyStack())
    Topmost = MyStack()
  EndIf
  ProcedureReturn Topmost
EndProcedure

;----   Example of implementation ----
Push_LIFO(3)
Push_LIFO(1)
Push_LIFO(4)
While Not Empty_LIFO()
  Debug Pop_LIFO()
Wend
Output:
 4
 1
 3

Python

Works with: Python version 2.5

The faster and Pythonic way is using a deque (available from 2.4). A regular list is a little slower.

from collections import deque
stack = deque()
stack.append(value) # pushing
value = stack.pop()
not stack # is empty?

If you need to expose your stack to the world, you may want to create a simpler wrapper:

from collections import deque

class Stack:
    def __init__(self):
        self._items = deque()
    def append(self, item):
        self._items.append(item)
    def pop(self):
        return self._items.pop()
    def __nonzero__(self):
        return bool(self._items)

Here is a stack implemented as linked list - with the same list interface.

class Stack:
    def __init__(self):
        self._first = None
    def __nonzero__(self):
        return self._first is not None 
    def append(self, value):
        self._first = (value, self._first)
    def pop(self):
        if self._first is None:
            raise IndexError, "pop from empty stack"
        value, self._first = self._first
        return value

Notes:

Using list interface - append, __nonzero__ make it easier to use, cleanup the client code, and allow changing the implementation later without affecting the client code. For example, instead of:

while not stack.empty():

You can write:

while stack:

Quick testing show that deque is about 5 times faster then the wrapper linked list implementations. This may be important if your stack is used in tight loops.

Quackery

Quackery is a stack based language. In addition to the stack (i.e. the Quackery data stack) and the call stack, named ancillary stacks can be created with [ stack ] is <name-of-stack>. Pushing to and popping from ancillary stacks is done with the words put and take. A word to test if an ancillary stack is empty can be defined as [ size 1 = ] is isempty. (The word empty already has a meaning in Quackery.) The word share returns the topmost element of an ancillary stack without changing the ancillary stack. Other ancillary stack operations are also available.

[ size 1 = ] is isempty ( s --> b )

[ stack ]    is mystack (   --> s )

mystack isempty if [ say "mystack is empty" cr cr ]
23 mystack put
mystack share echo   say " is on the top of mystack" cr cr
 
mystack mystack put ( you can put anything on an ancillary stack, even itself! )
 
mystack share  echo  say " is on the top of mystack" cr cr
mystack take   echo  say " has been removed from mystack" cr cr
mystack take   echo  say " has been removed from mystack" cr cr
mystack isempty if [ say "mystack is empty" cr cr ]
say "you are in a maze of twisty little passages, all alike"
Output:
mystack is empty

23 is on the top of mystack

mystack is on the top of mystack

mystack has been removed from mystack

23 has been removed from mystack

mystack is empty

you are in a maze of twisty little passages, all alike

R

Library: proto

See FIFO for functional and object oriented implementations of a First-In-First-Out object, with similar code.

library(proto)

stack <- proto(expr = {
   l <- list()
   empty <- function(.) length(.$l) == 0
   push <- function(., x) 
   {
      .$l <- c(list(x), .$l)
      print(.$l)
      invisible()
   }
   pop <- function(.) 
   {
      if(.$empty()) stop("can't pop from an empty list")
      .$l[[1]] <- NULL
      print(.$l)
      invisible()
   }
})

stack$empty()
# [1] TRUE
stack$push(3)
# [[1]]
# [1] 3
stack$push("abc")
# [[1]]
# [1] "abc"
# [[2]]
# [1] 3
stack$push(matrix(1:6, nrow=2))
# [[1]]
#      [,1] [,2] [,3]
# [1,]    1    3    5
# [2,]    2    4    6
# [[2]]
# [1] "abc"
# [[3]]
# [1] 3
stack$empty()
# [1] FALSE
stack$pop()
# [[1]]
[1] "abc"
# [[2]]
# [1] 3
stack$pop()
# [[1]]
# [1] 3
stack$pop()
# list()
stack$pop()
# Error in get("pop", env = stack, inherits = TRUE)(stack, ...) : 
#   can't pop from an empty list

Racket

Quick functional version:

#lang racket
(define stack '())
(define (push x stack) (cons x stack))
(define (pop stack) (values (car stack) (cdr stack)))
(define (empty? stack) (null? stack))

And a destructive object:

(struct stack ([items #:auto]) #:mutable #:auto-value '())
(define (push! x stack)
  (set-stack-items! stack (cons x (stack-items stack))))
(define (pop! stack)
  (begin0 (car (stack-items stack))
    (set-stack-items! stack (cdr (stack-items stack)))))
(define (empty? stack)
  (null? (stack-items stack)))

Raku

(formerly Perl 6)

Raku still has the stack functions from Perl 5, but now they also can be accessed by object notation:

my @stack;          # just a array
@stack.push($elem); # add $elem to the end of @stack
$elem = @stack.pop; # get the last element back
@stack.elems == 0   # true, because the stack is empty
not @stack          # also true because @stack is false

Raven

Use built in stack type:

new stack as s
1 s push
s pop

Word empty is also built in:

s empty if 'stack is empty' print

REBOL

REBOL [
	Title: "Stack"
	URL: http://rosettacode.org/wiki/Stack
]

stack: make object! [
	data: copy []

	push: func [x][append data x]
	pop: func [/local x][x: last data  remove back tail data  x]
	empty: does [empty? data]

	peek: does [last data]
]

; Teeny Tiny Test Suite
 
assert: func [code][print [either do code ["  ok"]["FAIL"]  mold code]]

print "Simple integers:"
s: make stack []  s/push 1  s/push 2 ; Initialize.

assert [2 = s/peek]
assert [2 = s/pop]
assert [1 = s/pop]
assert [s/empty]

print [lf "Symbolic data on stack:"]
v: make stack [data: [this is a test]] ; Initialize on instance.

assert ['test = v/peek]
assert ['test = v/pop]
assert ['a = v/pop]
assert [not v/empty]

Sample run:

Simple integers:
  ok [2 = s/peek]
  ok [2 = s/pop]
  ok [1 = s/pop]
  ok [s/empty]

Symbolic data on stack:
  ok ['test = v/peek]
  ok ['test = v/pop]
  ok ['a = v/pop]
  ok [not v/empty]

Retro

: stack ( n"-  ) create 0 , allot ;
: push  ( na-  ) dup ++ dup @ + ! ;
: pop   (  a-n ) dup @ over -- + @ ;
: top   (  a-n ) dup @ + @ ;
: empty? ( a-f ) @ 0 = ;

10 stack st

1 st push
2 st push
3 st push
st empty? putn
st top putn
st pop putn st pop putn st pop putn
st empty? putn

REXX

version 1

y=123                        /*define a REXX variable, value is 123  */
push y                       /*pushes   123   onto the stack.        */
pull g                       /*pops last value stacked & removes it. */
q=empty()                    /*invokes the  EMPTY  subroutine (below)*/
exit                         /*stick a fork in it, we're done.       */

empty: return queued()       /*subroutine returns # of stacked items.*/

version 2

/* REXX ***************************************************************
* supports push, pull, and peek
* 11.08.2013 Walter Pachl
**********************************************************************/
stk.=0
Call push 123
Say empty()
say peek()
say pull()
Say empty()
say peek()
say push(456)
say peek()
Exit

push: Procedure Expose stk.
  Parse Arg v
  z=stk.0+1
  stk.z=v
  stk.0=z
  Return v

peek: Procedure Expose stk.
  If stk.0=0 Then
    Return 'stack is empty'
  Else Do
    z=stk.0
    Return stk.z
    End

pull: Procedure Expose stk.
  If stk.0=0 Then
    Return 'stack is empty'
  Else Do
    z=stk.0
    res=stk.z
    stk.0=stk.0-1
    Return res
    End

empty: Procedure Expose stk.
  Return stk.0=0
Output:
0
123
123
1
stack is empty
456
456

Ring

# Project : Stack

load "stdlib.ring"
ostack = new stack
for n = 5 to 7
     see "Push: " + n + nl
     ostack.push(n) 
next
see "Pop:" + ostack.pop() + nl
see "Push: " + "8" + nl
ostack.push(8)
while len(ostack) > 0
        see "Pop:" + ostack.pop() + nl
end
if len(ostack) = 0
   see "Pop: stack is empty" + nl
ok

Output:

Push: 5
Push: 6
Push: 7
Pop:7
Push: 8
Pop:8
Pop:6
Pop:5
Pop: stack is empty

RPL

The RPL interpreter is based on a stack, with which the user interacts.

  • the push operation is performed by the DUP instruction
  • the pop operation by DROP
  • DEPTH provides the stack size. To test the emptiness of the stack, the following program can be created as an user-defined instruction:
≪ DEPTH NOT ≫ 'EMPTY?' STO

Ruby

Using an Array, there are already methods Array#push, Array#pop and Array#empty?.

stack = []
stack.push(value) # pushing
value = stack.pop # popping
stack.empty? # is empty?

If you need to expose your stack to the world, you may want to create a simpler wrapper. Here is a wrapper class Stack that wraps Array but only exposes stack methods.

require 'forwardable'

# A stack contains elements in last-in, first-out order.
# Stack#push adds new elements to the top of the stack;
# Stack#pop removes elements from the top.
class Stack
  extend Forwardable
  
  # Creates a Stack containing _objects_.
  def self.[](*objects)
    new.push(*objects)
  end
  
  # Creates an empty Stack.
  def initialize
    @ary = []
  end
  
  # Duplicates a Stack.
  def initialize_copy(obj)
    super
    @ary = @ary.dup
  end
  
  # Adds each object to the top of this Stack. Returns self.
  def push(*objects)
    @ary.push(*objects)
    self
  end
  alias << push
  
  ##
  # :method: pop
  # :call-seq:
  #   pop -> obj or nil
  #   pop(n) -> ary
  #
  # Removes an element from the top of this Stack, and returns it.
  # Returns nil if the Stack is empty.
  #
  # If passing a number _n_, removes the top _n_ elements, and returns
  # an Array of them. If this Stack contains fewer than _n_ elements,
  # returns them all. If this Stack is empty, returns an empty Array.
  def_delegator :@ary, :pop
  
  ##
  # :method: top
  # :call-seq:
  #   top -> obj or nil
  #   top(n) -> ary
  # Returns the topmost element without modifying the stack.
  def_delegator :@ary, :last, :top
  
  ##
  # :method: empty?
  # Returns true if this Stack contains no elements.
  def_delegator :@ary, :empty?
  
  ##
  # :method: size
  # Returns the number of elements in this Stack.
  def_delegator :@ary, :size
  alias length size
  
  # Converts this Stack to a String.
  def to_s
    "#{self.class}#{@ary.inspect}"
  end
  alias inspect to_s
end
p s = Stack.new                 # => Stack[]
p s.empty?                      # => true
p s.size                        # => 0
p s.top                         # => nil
p s.pop                         # => nil
p s.pop(1)                      # => []
p s.push(1)                     # => Stack[1]
p s.push(2, 3)                  # => Stack[1, 2, 3]
p s.top                         # => 3
p s.top(2)                      # => [2, 3]
p s                             # => Stack[1, 2, 3]
p s.size                        # => 3
p s.pop                         # => 3
p s.pop(1)                      # => [2]
p s.empty?                      # => false

p s = Stack[:a, :b, :c]         # => Stack[:a, :b, :c]
p s << :d                       # => Stack[:a, :b, :c, :d]
p s.pop                         # => :d

Just meeting the requirements of a push, pop and empty method:

require 'forwardable'

class Stack
  extend Forwardable

  def initialize
    @stack = []
  end

  def_delegators :@stack, :push, :pop, :empty?
end

(push takes multiple arguments; pop takes an optional argument which specifies how many to pop)

Run BASIC

dim stack$(10)   ' stack of ten
global stack$
global stackEnd

for i = 1 to 5                                      ' push 5 values to the stack
 a$ = push$(chr$(i + 64))
 print "Pushed ";chr$(i + 64);" stack has ";stackEnd
next i

print "Pop Value:";pop$();" stack has ";stackEnd  ' pop last in
print "Pop Value:";pop$();" stack has ";stackEnd  ' pop last in

e$ = mt$()                                        ' MT the stack
print "Empty stack. stack has ";stackEnd

' ------ PUSH the stack
FUNCTION push$(val$)
stackEnd = stackEnd + 1                            ' if more than 10 then lose the oldest
if stackEnd > 10 then
   for i = 0 to 9
      stack$(i) = stack$(i+1)
   next i
   stackEnd   = 10
end if
stack$(stackEnd) = val$
END FUNCTION

' ------ POP the stack -----
FUNCTION pop$()
if stackEnd = 0 then 
   pop$     = "Stack is MT"
  else
   pop$     = stack$(stackEnd)                        ' pop last in
   stackEnd = max(stackEnd - 1,0)
end if
END FUNCTION

' ------ MT the stack ------
FUNCTION mt$()
  stackEnd = 0
END FUNCTION
Output:
Pushed A stack has 1
Pushed B stack has 2
Pushed C stack has 3
Pushed D stack has 4
Pushed E stack has 5
Pop Value:E stack has 4
Pop Value:D stack has 3
Empty stack. stack has 0

Rust

Using the standard library

One could just use a vector (Vec<T>) which is part of the standard library

fn main() {
    let mut stack = Vec::new();
    stack.push("Element1");
    stack.push("Element2");
    stack.push("Element3");

    assert_eq!(Some(&"Element3"), stack.last());
    assert_eq!(Some("Element3"), stack.pop());
    assert_eq!(Some("Element2"), stack.pop());
    assert_eq!(Some("Element1"), stack.pop());
    assert_eq!(None, stack.pop());
}

Simple implementation

Simply uses a singly-linked list.

type Link<T> = Option<Box<Frame<T>>>;

pub struct Stack<T> {
    head: Link<T>,
}
struct Frame<T> { 
    elem: T,
    next: Link<T>,
}

/// Iterate by value (consumes list)
pub struct IntoIter<T>(Stack<T>); 
impl<T> Iterator for IntoIter<T> {
    type Item = T;
    fn next(&mut self) -> Option<Self::Item> {
        self.0.pop()
    }
}

/// Iterate by immutable reference
pub struct Iter<'a, T: 'a> { 
    next: Option<&'a Frame<T>>,
}
impl<'a, T> Iterator for Iter<'a, T> { // Iterate by immutable reference
    type Item = &'a T;
    fn next(&mut self) -> Option<Self::Item> {
        self.next.take().map(|frame| {
            self.next = frame.next.as_ref().map(|frame| &**frame);
            &frame.elem
        })
    }
}

/// Iterate by mutable reference
pub struct IterMut<'a, T: 'a> {
    next: Option<&'a mut Frame<T>>,
}
impl<'a, T> Iterator for IterMut<'a, T> {
    type Item = &'a mut T;
    fn next(&mut self) -> Option<Self::Item> {
        self.next.take().map(|frame| {
            self.next = frame.next.as_mut().map(|frame| &mut **frame);
            &mut frame.elem
        })
    }
}


impl<T> Stack<T> {
    /// Return new, empty stack
    pub fn new() -> Self {
        Stack { head: None }
    }

    /// Add element to top of the stack
    pub fn push(&mut self, elem: T) {
        let new_frame = Box::new(Frame {
            elem: elem,
            next: self.head.take(),
        });
        self.head = Some(new_frame);
    }

    /// Remove element from top of stack, returning the value
    pub fn pop(&mut self) -> Option<T> {
        self.head.take().map(|frame| { 
            let frame = *frame;
            self.head = frame.next;
            frame.elem
        })
    }

    /// Get immutable reference to top element of the stack
    pub fn peek(&self) -> Option<&T> {
        self.head.as_ref().map(|frame| &frame.elem)
    }

    /// Get mutable reference to top element on the stack
    pub fn peek_mut(&mut self) -> Option<&mut T> {
        self.head.as_mut().map(|frame| &mut frame.elem)
    }

    /// Iterate over stack elements by value
    pub fn into_iter(self) -> IntoIter<T> {
        IntoIter(self)
    }

    /// Iterate over stack elements by immutable reference
    pub fn iter<'a>(&'a self) -> Iter<'a,T> {
        Iter { next: self.head.as_ref().map(|frame| &**frame) }
    }

    /// Iterate over stack elements by mutable reference
    pub fn iter_mut(&mut self) -> IterMut<T> {
        IterMut { next: self.head.as_mut().map(|frame| &mut **frame) }
    }
}

// The Drop trait tells the compiler how to free an object after it goes out of scope. 
// By default, the compiler would do this recursively which *could* blow the stack for
// extraordinarily long lists. This simply tells it to do it iteratively.
impl<T> Drop for Stack<T> {
    fn drop(&mut self) {
        let mut cur_link = self.head.take();
        while let Some(mut boxed_frame) = cur_link {
            cur_link = boxed_frame.next.take();
        }
    }
}

Sather

This one uses a builtin linked list to keep the values pushed onto the stack.

class STACK{T} is
  private attr stack :LLIST{T};

  create:SAME is 
    res ::= new;
    res.stack := #LLIST{T};
    return res;
  end;

  push(elt: T) is
    stack.insert_front(elt);    
  end;

  pop: T is
    if ~stack.is_empty then
      stack.rewind;
      r ::= stack.current;
      stack.delete;
      return r;
    else
      raise "stack empty!\n";
    end;
  end;

  top: T is
    stack.rewind;
    return stack.current;
  end;

  is_empty: BOOL is
    return stack.is_empty;
  end;
end;
class MAIN is
  main is
    s ::= #STACK{INT};
    #OUT + "push values...\n";
    s.push(3);
    s.push(2);
    s.push(1);
    s.push(0);
    #OUT + "retrieving them...\n";
    loop
      #OUT + s.pop + "\n";
    until!(s.is_empty); end;
  end;
end;

Sather library has the abstract class $STACK{T}, but using this forces us to implement other methods too.

Scala

The Do it yourself approach:

class Stack[T] {
  private var items = List[T]()

  def isEmpty = items.isEmpty

  def peek = items match {
    case List()       => error("Stack empty")
    case head :: rest => head
  }

  def pop = items match {
    case List()       => error("Stack empty")
    case head :: rest => items = rest; head
  }

  def push(value: T) = items = value +: items
}

Or use the standard Scala library. Slightly modified to meet to requirements of this task.

import collection.mutable.{ Stack => Stak }

class Stack[T] extends Stak[T] {
  override def pop: T = {
    if (this.length == 0) error("Can't Pop from an empty Stack.")
    else super.pop
  }
  def peek: T = this.head
}
A test could be:
object StackTest extends App {

  val stack = new Stack[String]

  stack.push("Peter Pan")
  stack.push("Suske & Wiske", "Alice in Wonderland")

  assert(stack.peek == "Alice in Wonderland")
  assert(stack.pop() == "Alice in Wonderland")
  assert(stack.pop() == "Suske & Wiske")
  assert(stack.pop() == "Peter Pan")
  println("Completed without errors")
}

Scheme

This version uses primitive message passing.

(define (make-stack)
  (let ((st '()))
    (lambda (message . args)
      (case message
        ((empty?) (null? st))
        ((top) (if (null? st)
                   'empty
                   (car st)))
        ((push) (set! st (cons (car args) st)))
        ((pop) (if (null? st)
                   'empty
                   (let ((result (car st)))
                     (set! st (cdr st))
                     result)))
        (else 'badmsg)))))

Seed7

$ include "seed7_05.s7i";

const func type: stack (in type: baseType) is func
  result
    var type: stackType is void;
  begin
    stackType := array baseType;

    const proc: push (inout stackType: aStack, in baseType: top) is func
      begin
         aStack := [] (top) & aStack;
      end func;

    const func baseType: pop (inout stackType: aStack) is func
      result
        var baseType: top is baseType.value;
      begin
        if length(aStack) = 0 then
          raise RANGE_ERROR;
        else
          top := aStack[1];
          aStack := aStack[2 ..];
        end if;
      end func;

    const func boolean: empty (in stackType: aStack) is
      return length(aStack) = 0;
  end func;

const type: intStack is stack(integer);

const proc: main is func
  local
    var intStack: s is intStack.value;
  begin
    push(s, 10);
    push(s, 20);
    writeln(pop(s) = 20);
    writeln(pop(s) = 10);
    writeln(empty(s));
  end func;

SenseTalk

put () into stack
repeat with each item of 1 .. 10
	push it into stack
end repeat

repeat while stack is not empty
	pop stack
	put it
end repeat

Sidef

Using a built-in array:

var stack = [];
stack.push(42);         # pushing
say stack.pop;          # popping
say stack.is_empty;     # is_emtpy?

Creating a Stack class:

class Stack(stack=[]) {
    method pop        { stack.pop };
    method push(item) { stack.push(item) };
    method empty      { stack.is_empty };
}

var stack = Stack();
stack.push(42);
say stack.pop;          # => 42
say stack.empty;        # => true

Slate

From Slate's standard library:

collections define: #Stack &parents: {ExtensibleArray}.
"An abstraction over ExtensibleArray implementations to follow the stack
protocol. The convention is that the Sequence indices run least-to-greatest
from bottom to top."

s@(Stack traits) push: obj
[s addLast: obj].

s@(Stack traits) pop
[s removeLast].

s@(Stack traits) pop: n
[s removeLast: n].

s@(Stack traits) top
[s last].

s@(Stack traits) top: n
[s last: n].

s@(Stack traits) bottom
[s first].

Smalltalk

Smalltalk has a built-in Stack class, instances of which you can send messages:

s := Stack new.
s push: 1.
s push: 2.
s push: 3.
s pop.
s top. "2"

Standard ML

The signature for a module supplying a stack interface, with a couple added functions.

signature STACK =
sig
    type 'a stack
    exception EmptyStack

    val empty : 'a stack
    val isEmpty : 'a stack -> bool

    val push : ('a * 'a stack) -> 'a stack
    val pop  : 'a stack -> 'a stack
    val top  : 'a stack -> 'a
    val popTop : 'a stack -> 'a stack * 'a

    val map : ('a -> 'b) -> 'a stack -> 'b stack
    val app : ('a -> unit) -> 'a stack -> unit
end

An implementation of the STACK signature, using immutable lists.

structure Stack :> STACK =
struct
    type 'a stack = 'a list
    exception EmptyStack

    val empty = []

    fun isEmpty st = null st

    fun push (x, st) = x::st

    fun pop []      = raise EmptyStack
      | pop (x::st) = st

    fun top []      = raise EmptyStack
      | top (x::st) = x

    fun popTop st = (pop st, top st)

    fun map f st = List.map f st
    fun app f st = List.app f st
end

Stata

See Singly-linked list/Element definition#Stata.

Swift

Generic stack.

struct Stack<T> {
    var items = [T]()
    var empty:Bool {
        return items.count == 0
    }
    
    func peek() -> T {
        return items[items.count - 1]
    }
    
    mutating func pop() -> T {
        return items.removeLast()
    }
    
    mutating func push(obj:T) {
        items.append(obj)
    }
}

var stack = Stack<Int>()
stack.push(1)
stack.push(2)
println(stack.pop())
println(stack.peek())
stack.pop()
println(stack.empty)
Output:
2
1
true

Tailspin

processor Stack
  @: $;

  sink push
    ..|@Stack: $;
  end push

  source peek
    $@Stack(last) !
  end peek

  source pop
    ^@Stack(last) !
  end pop

  source empty
    $@Stack::length -> #
    <=0> 1 !
    <> 0 !
  end empty
end Stack

def myStack: [1] -> Stack;

2 -> !myStack::push

'$myStack::empty; $myStack::pop;
' -> !OUT::write
'$myStack::empty; $myStack::pop;
' -> !OUT::write
'$myStack::empty;
' -> !OUT::write

3 -> !myStack::push
'$myStack::empty; $myStack::peek;
' -> !OUT::write
'$myStack::empty; $myStack::pop;
' -> !OUT::write
'$myStack::empty;' -> !OUT::write
Output:
0 2
0 1
1
0 3
0 3
1

Tcl

Here's a simple implementation using a list:

proc push {stackvar value} {
    upvar 1 $stackvar stack
    lappend stack $value
}
proc pop {stackvar} {
    upvar 1 $stackvar stack
    set value [lindex $stack end]
    set stack [lrange $stack 0 end-1]
    return $value
}
proc size {stackvar} {
    upvar 1 $stackvar stack
    llength $stack
}
proc empty {stackvar} {
    upvar 1 $stackvar stack
    expr {[size stack] == 0}
}
proc peek {stackvar} {
    upvar 1 $stackvar stack
    lindex $stack end
}

set S [list]
empty S ;# ==> 1 (true)
push S foo
empty S ;# ==> 0 (false)
push S bar
peek S ;# ==> bar
pop S ;# ==> bar
peek S ;# ==> foo
Library: Tcllib (Package: struct::stack)
package require struct::stack
struct::stack S
S size ;# ==> 0
S push a b c d e
S size ;# ==> 5
S peek ;# ==> e
S pop ;# ==> e
S peek ;# ==> d
S pop 4 ;# ==> d c b a
S size ;# ==> 0

Uiua

[3] # Since UIUA is a stack language, everything is pushed on the stack
x ← # stores the top of the stack into the variable x
? # ? checks the stack, it is now empty


UnixPipes

init() { if [ -e stack ]; then rm stack; fi } # force pop to blow up if empty
push() { echo $1 >> stack; }
pop() {
	tail -1 stack;
	x=`head -n -1 stack | wc -c`
	if [ $x -eq '0' ]; then rm stack; else
		truncate -s `head -n -1 stack | wc -c` stack
	fi
}
empty() { head -n -1 stack |wc -l; }
stack_top() { tail -1 stack; }

test it:

% push me; push you; push us; push them
% pop;pop;pop;pop
them
us
you
me

UNIX Shell

Works with: Bourne Again SHell
Works with: Zsh
Works with: Korn Shell

Here's a simple single-stack solution:

init() { 
  if [[ -n $KSH_VERSION ]]; then
    set -A stack
  else
    stack=(); # this sets stack to '()' in ksh
  fi
}

push() {
  stack=("$1" "${stack[@]}")
}

stack_top() {
  # this approach sidesteps zsh indexing difference
  set -- "${stack[@]}"
  printf '%s\n' "$1"
}

pop() {
  stack_top
  stack=("${stack[@]:1}")
}

empty() {
  (( ${#stack[@]} == 0 ))
}

# Demo
push fred; push wilma; push betty; push barney
printf 'peek(stack)==%s\n' "$(stack_top)"
while ! empty; do
  pop
done
Output:
peek(stack)==barney
barney
betty
wilma
fred

You can generalize it to multiple stacks with some judicious use of the twin evils of pass-by-name and eval:

init_stack() {
  if [[ -n $KSH_VERSION ]]; then
    eval 'set -A '"$1"
  else
    eval "$1=()"
  fi
}

push() {
  eval "$1"'=("$2" "${'"$1"'[@]}")'
}

stack_top() {
  eval 'set -- "${'"$1"'[@]}"';
  printf '%s\n' "$1"
}

pop() {
  stack_top "$1";
  eval "$1"'=("${'"$1"'[@]:1}")'
}

empty() {
  eval '(( ${#'"$1"'[@]} == 0 ))'
}

init_stack mystack
push mystack fred; push mystack wilma; push mystack betty; push mystack barney
printf 'peek(mystack)==%s\n' "$(stack_top mystack)"
while ! empty mystack; do
  pop mystack
done
Output:
peek(mystack)==barney
barney
betty
wilma
fred

VBA

Define a class Stack in a class module with that name.

'Simple Stack class

'uses a dynamic array of Variants to stack the values
'has read-only property "Size"
'and methods "Push", "Pop", "IsEmpty"

Private myStack()
Private myStackHeight As Integer

'method Push
Public Function Push(aValue)
  'increase stack height
  myStackHeight = myStackHeight + 1
  ReDim Preserve myStack(myStackHeight)
  myStack(myStackHeight) = aValue
End Function

'method Pop
Public Function Pop()
  'check for nonempty stack
  If myStackHeight > 0 Then
    Pop = myStack(myStackHeight)
    myStackHeight = myStackHeight - 1
  Else
    MsgBox "Pop: stack is empty!"
  End If
End Function

'method IsEmpty
Public Function IsEmpty() As Boolean
  IsEmpty = (myStackHeight = 0)
End Function

'property Size
Property Get Size() As Integer
  Size = myStackHeight
End Property

Usage example:

'stack test
Public Sub stacktest()
  Dim aStack As New Stack
  With aStack
    'push and pop some value
    .Push 45
    .Push 123.45
    .Pop
    .Push "a string"
    .Push "another string"
    .Pop
    .Push Cos(0.75)
    Debug.Print "stack size is "; .Size
    While Not .IsEmpty
      Debug.Print "pop: "; .Pop
    Wend
    Debug.Print "stack size is "; .Size
    'try to continue popping
    .Pop
  End With
End Sub
Output:
stacktest
stack size is  3 
pop:  0,731688868873821 
pop: a string
pop:  45 
stack size is  0 

(after wich a message box will pop up)

VBScript

Stack class

class stack
	dim tos
	dim stack()
	dim stacksize
	
	private sub class_initialize
		stacksize = 100
		redim stack( stacksize )
		tos = 0
	end sub

	public sub push( x )
		stack(tos) = x
		tos = tos + 1
	end sub
	
	public property get stackempty
		stackempty = ( tos = 0 )
	end property
	
	public property get stackfull
		stackfull = ( tos > stacksize )
	end property
	
	public property get stackroom
		stackroom = stacksize - tos
	end property
	
	public function pop()
		pop = stack( tos - 1 )
		tos = tos - 1
	end function

	public sub resizestack( n )
		redim preserve stack( n )
		stacksize = n
		if tos > stacksize then
			tos = stacksize
		end if
	end sub
end class

dim s
set s = new stack
s.resizestack 10
wscript.echo s.stackempty
dim i
for i = 1 to 10
	s.push rnd
	wscript.echo s.stackroom
	if s.stackroom = 0 then exit for
next
for i = 1 to 10
	wscript.echo s.pop
	if s.stackempty then exit for
next
Output:
(changes every time)
-1
9
8
7
6
5
4
3
2
1
0
0.7090379
0.81449
0.7607236
1.401764E-02
0.7747401
0.301948
0.2895625
0.5795186
0.533424
0.7055475

Using an ArrayList.

' Stack Definition - VBScript
 
Option Explicit

Dim stack, i, x
Set stack = CreateObject("System.Collections.ArrayList")
If Not empty_(stack) Then Wscript.Echo stack.Count
push stack, "Banana"
push stack, "Apple"
push stack, "Pear"
push stack, "Strawberry"
Wscript.Echo "Count=" & stack.Count 		    ' --> Count=4
Wscript.Echo pop(stack) & " - Count=" & stack.Count ' --> Strawberry - Count=3
Wscript.Echo "Tail=" & stack.Item(0) 		    ' --> Tail=Banana
Wscript.Echo "Head=" & stack.Item(stack.Count-1)    ' --> Head=Pear
Wscript.Echo stack.IndexOf("Apple", 0)   	    ' --> 1
For i=1 To stack.Count
	Wscript.Echo join(stack.ToArray(), ", ")
	x = pop(stack)
Next 'i

Sub push(s, what)
    s.Add what
End Sub 'push
 
Function pop(s)
	Dim what
    If s.Count > 0 Then
        what = s(s.Count-1)
        s.RemoveAt s.Count-1
    Else
        what = ""
    End If
    pop = what
End Function 'pop
 
Function empty_(s)
    empty_ = s.Count = 0
End Function 'empty_
Output:
Count=4
Strawberry - Count=3
Tail=Banana
Head=Pear
1
Banana, Apple, Pear
Banana, Apple
Banana

V (Vlang)

const (
    max_depth = 256
)

struct Stack {
mut:
    data  []f32 = []f32{len: max_depth}
    depth int
}

fn (mut s Stack) push(v f32) {
    if s.depth >= max_depth {
        return
    }
    println('Push: ${v:3.2f}')
    s.data[s.depth] = v
    s.depth++
}

fn (mut s Stack) pop() ?f32 {
    if s.depth > 0 {
        s.depth--
        result := s.data[s.depth]
        println('Pop: top of stack was ${result:3.2f}')
        return result
    }
    return error('Stack Underflow!!')
}

fn (s Stack) peek() ?f32 {
    if s.depth > 0 {
        result := s.data[s.depth - 1]
        println('Peek: top of stack is ${result:3.2f}')
        return result
    }
    return error('Out of Bounds...')
}

fn (s Stack) empty() bool {
    return s.depth == 0
}

fn main() {
    mut stack := Stack{}
    println('Stack is empty? ' + if stack.empty() { 'Yes' } else { 'No' })
    stack.push(5.0)
    stack.push(4.2)
    println('Stack is empty? ' + if stack.empty() { 'Yes' } else { 'No' })
    stack.peek() or { return }
    stack.pop() or { return }
    stack.pop() or { return }
}
Output:
Stack is empty? Yes
Push: 5.00
Push: 4.20
Stack is empty? No
Peek: top of stack is 4.20
Pop: top of stack was 4.20
Pop: top of stack was 5.00

Wart

Stacks as user-defined objects backed by a list.

def (stack)
  (tag 'stack nil)

mac (push! x s) :qcase `(isa stack ,s)
  `(push! ,x (rep ,s))

mac (pop! s) :qcase `(isa stack ,s)
  `(pop! (rep ,s))

def (empty? s) :case (isa stack s)
  (empty? rep.s)

Example usage:

s <- (stack)
=> (object stack nil)
push! 3 s
=> (object stack (3))
push! 4 s
=> (object stack (4 3))
push! 5 s
=> (object stack (5 4 3))
pop! s
=> 5
(empty? s)
=> nil
pop! s
=> 4
pop! s
=> 3
(empty? s)
=> 1  # true

Wren

Library: Wren-seq

This uses the Stack class in the above module.

import "./seq" for Stack

var s = Stack.new()
s.push(1)
s.push(2)
System.print("Stack contains %(s.toList)")
System.print("Number of elements in stack = %(s.count)")
var item = s.pop()
System.print("'%(item)' popped from the stack")
System.print("Last element is now %(s.peek())")
s.clear()
System.print("Stack cleared")
System.print("Is stack now empty? %((s.isEmpty) ? "yes" : "no")")
Output:
Stack contains [1, 2]
Number of elements in stack = 2
'2' popped from the stack
Last element is now 1
Stack cleared
Is stack now empty? yes

X86 Assembly

; x86_64 linux nasm

struc Stack
  maxSize: resb 8
  currentSize: resb 8
  contents:
endStruc

section .data

soError: db "Stack Overflow Exception", 10
seError: db "Stack Empty Error", 10


section .text

createStack:
; IN: max number of elements (rdi)
; OUT: pointer to new stack (rax)
  push rdi
  xor rdx, rdx
  mov rbx, 8
  mul rbx
  mov rcx, rax
  mov rax, 12
  mov rdi, 0
  syscall
  push rax
  mov rdi, rax
  add rdi, rcx
  mov rax, 12
  syscall
  pop rax
  pop rbx
  mov qword [rax + maxSize], rbx
  mov qword [rax + currentSize], 0
  ret


push:
; IN: stack to operate on (stack argument), element to push (rdi)
; OUT: void
  mov rax, qword [rsp + 8]
  mov rbx, qword [rax + currentSize]
  cmp rbx, qword [rax + maxSize]
  je stackOverflow
  lea rsi, [rax + contents + 8*rbx]
  mov qword [rsi], rdi
  add qword [rax + currentSize], 1
  ret


pop:
; pop
; IN: stack to operate on (stack argument)
; OUT: element from stack top
  mov rax, qword [rsp + 8]
  mov rbx, qword [rax + currentSize]
  cmp rbx, 0
  je stackEmpty
  sub rbx, 1
  lea rsi, [rax + contents + 8*rbx]
  mov qword [rax + currentSize], rbx
  mov rax, qword [rsi]
  ret


; stack operation exceptions
stackOverflow:
  mov rsi, soError
  mov rdx, 25
  jmp errExit
stackEmpty:
  mov rsi, seError
  mov rdx, 18
errExit:
  mov rax, 1
  mov rdi, 1
  syscall
  mov rax, 60
  mov rdi, 1
  syscall

XLISP

This is a fairly straightforward implementation, representing a stack as a linked list inside an object.

(define-class stack
    (instance-variables vals))

(define-method (stack 'initialize)
    (setq vals '())
    self)

(define-method (stack 'push x)
    (setq vals (cons x vals)))

(define-method (stack 'pop)
    (define tos (car vals))
    (setq vals (cdr vals))
    tos)

(define-method (stack 'emptyp)
    (null vals))

A sample REPL session:

; Loading 'stack.lsp'
[1] (define st (stack 'new))

ST
[2] (st 'push 1)

(1)
[3] (st 'push 2)

(2 1)
[4] (st 'emptyp)

()
[5] (st 'pop)

2
[6] (st 'pop)

1
[7] (st 'emptyp)

#T
[8]

XPL0

include c:\cxpl\codes;  \intrinsic 'code' declarations
int Stack(100), SP;

proc Push(I);           \Push an integer onto the Stack
int  I;
[SP:= SP+1;
Stack(SP):= I;
]; \Push

func Pop;               \Pop an integer from the Stack
int  I;
[I:= Stack(SP);
SP:= SP-1;
return I;
]; \Pop

func Empty;             \Return 'true' if Stack is empty
return SP<0;

func Top;               \Return the integer at top of Stack
return Stack(SP);

int I;
[SP:= -1;               \initialize stack pointer
for I:= 0 to 10 do Push(I*I);
IntOut(0, Top);  CrLf(0);
while not Empty do [IntOut(0, Pop);  ChOut(0, ^ )];
CrLf(0);
]
Output:
100
100 81 64 49 36 25 16 9 4 1 0 

Yabasic

limit = 1000
dim stack(limit)

top = 0

sub push(n)
    if top < limit then
        top = top + 1 : stack(top) = n
    else
        print "stack full - ";
    end if
end sub

sub pop()
    if top then
        top = top - 1 : return stack(top + 1)
    else
        print "stack empty - ";
    end if
end sub

sub empty()
    return not top
end sub

// ======== test ========

for n = 3 to 5
    print "Push ", n : push(n)
next

print "Pop ", pop()

print "Push ", 6 : push(6)

while(not empty())
    print "Pop ", pop()
wend

print "Pop ", pop()

Z80 Assembly

The stack can be initialized by loading it directly with an immediate value. Z80-based home computers such as the Amstrad CPC and ZX Spectrum do this for you. Messing with the stack on those systems is a bad idea, since an assembly program stored on a floppy disk or cassette tape begins with the return address of BASIC on top of the stack. However, on embedded systems like the Game Boy or the Sega Master System, this step is a must, as the CPU does not have an initial stack pointer value in its vector table and thus does not guarantee the value of SP upon startup. Unlike the 6502, the Z80's stack does not have a fixed size or memory location, and is only limited by the address space of the CPU. From a practical standpoint, however, it's very unlikely you'll need more than 256 bytes.

LD SP,&FFFF


Registers must be pushed in pairs. If you push/pop the accumulator, the processor flags go with it. This can make certain functions difficult to write without using a temporary variable to hold the accumulator, which doesn't allow for recursion or arbitrary nesting.

push af
push bc
push de
push hl

Popping is very similar. To properly pop values, they must be popped in the reverse order they were pushed.

pop hl
pop de
pop bc
pop af

The stack is empty if its value equals the original starting value of the stack pointer. This is a little difficult, since the stack doesn't necessarily start in a fixed location like it does on the 6502. There are two ways to do this:

ld (&nnnn),SP ;&nnnn represents a memory location that the programmer will later read from to use as a
              ;comparison for the current stack pointer
ld hl,0
add hl,sp    ;the z80 doesn't allow you to load SP directly into HL, so this is the quickest way

From there it's a matter of comparing this value to the current stack pointer, which in itself is tricky since the built-in compare instruction forces you to use the accumulator as one of the operands, and works natively in terms of 8-bit values.

Peek can be achieved with the EX (SP),HL command which exchanges HL with the top item of the stack.

On the Game Boy, the stack can also be manually adjusted by a signed 8-bit constant. A Zilog Z80 cannot do this in a single command. The code below only works on a Game Boy or any other hardware running on a Sharp LR35902 CPU:

 ADD SP,&FE  ;subtract two from the stack pointer. Remember that the stack grows "down" in memory.

It should be noted that although the "heap" and the "stack" are considered separate areas of memory by the programmer, in the eyes of the CPU there is no boundary between them. The CPU doesn't care if you push enough words onto the stack so that the stack pointer is now pointing to the heap, or even ROM space. Most of the time this isn't an issue, as long as your push/pop operations are properly balanced. It's just something to look out for.

zkl

Lists have stack methods so this class is somewhat reduntant

class Stack{
   var [const] stack=L();
   fcn push(x){stack.append(x); self}
   fcn pop    {stack.pop()}
   fcn empty  {(not stack.len())}
   var [proxy] isEmpty = empty;
}
Output:
var s=Stack();
s.push(5).push("five");
s.isEmpty //-->False
s.pop()   //-->"five"