{-
 -
 - Copyright (c) 2009-2010 Johnny Morrice
 -
 - Permission is hereby granted, free of charge, to any person
 - obtaining a copy of this software and associated documentation 
 - files (the "Software"), to deal in the Software without 
 - restriction, including without limitation the rights to use, copy, 
 - modify, merge, publish, distribute, sublicense, and/or sell copies 
 - of the Software, and to permit persons to whom the Software is 
 - furnished to do so, subject to the following conditions:
 -
 - The above copyright notice and this permission notice shall be 
 - included in all copies or substantial portions of the Software.
 -
 - THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, 
 - EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
 - MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND 
 - NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS
 - BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN
 - ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN
 - CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE
 - SOFTWARE.
 -
-}

-- | This module provides a nice syntax for defining a list of pairs.
{-# OPTIONS -XFlexibleInstances -XRankNTypes #-}
module Network.Shpider.Pairs 
   ( PairsWriter
   , (=:)
   , pairs
   ) where

import Control.Monad.State

-- | The abstract type describing the monadic state of a list of pairs.
type PairsWriter a b =
   State [ ( a , b ) ]

-- | Take a monadic PairsWriter and return a list of pairs.
pairs :: forall a b c. PairsWriter a b c -> [ ( a , b ) ]
pairs =
   reverse . snd . flip runState [ ]

-- | Make a list of pairs of pairs like
--
-- @
--    pairs $ do $ 3 =: ( \" is my favourite number or \" , 5 )
--                 10 =: ( \" pints have I drunk or was it \" , 11 )
-- @
(=:) :: forall a b. a -> b -> PairsWriter a b ( )
(=:) k v = do
   st <- get
   put $ ( k , v ) : st