-------------------------------------------------------------------------
--  
--     Store.hs
--  
--         An abstract data type of stores of integers, implemented as
--         a list of pairs of variables and values.         
--                                  
--         (c) Addison-Wesley, 1996-2011.                   
--  
-------------------------------------------------------------------------

module Store 
   ( Store, 
     initial,     -- Store
     value,       -- Store -> Var -> Integer
     update       -- Store -> Var -> Integer -> Store
    ) where

-- Var is the type of variables.                    

type Var = Char

-- The implementation is given by a newtype declaration, with one
-- constructor, taking an argument of type [ (Integer,Var) ].

data Store = Store [ (Integer,Var) ] 

instance Eq Store where 
  (Store [(Integer, Var)]
sto1) == :: Store -> Store -> Bool
== (Store [(Integer, Var)]
sto2) = ([(Integer, Var)]
sto1 [(Integer, Var)] -> [(Integer, Var)] -> Bool
forall a. Eq a => a -> a -> Bool
== [(Integer, Var)]
sto2)                 

instance Show Store where
  showsPrec :: Int -> Store -> ShowS
showsPrec Int
n (Store [(Integer, Var)]
sto) = Int -> [(Integer, Var)] -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
n [(Integer, Var)]
sto                 
--  
initial :: Store 

initial :: Store
initial = [(Integer, Var)] -> Store
Store []

value  :: Store -> Var -> Integer

value :: Store -> Var -> Integer
value (Store []) Var
v         = Integer
0
value (Store ((Integer
n,Var
w):[(Integer, Var)]
sto)) Var
v 
  | Var
vVar -> Var -> Bool
forall a. Eq a => a -> a -> Bool
==Var
w            = Integer
n
  | Bool
otherwise       = Store -> Var -> Integer
value ([(Integer, Var)] -> Store
Store [(Integer, Var)]
sto) Var
v

update  :: Store -> Var -> Integer -> Store

update :: Store -> Var -> Integer -> Store
update (Store [(Integer, Var)]
sto) Var
v Integer
n = [(Integer, Var)] -> Store
Store ((Integer
n,Var
v)(Integer, Var) -> [(Integer, Var)] -> [(Integer, Var)]
forall a. a -> [a] -> [a]
:[(Integer, Var)]
sto)