-- |
-- Module       : Web.Saferoute
-- Description  : Type-safe routing for web applications.
-- Copyright    : 2014, Peter Harpending.
-- License      : BSD3
-- Maintainer   : Peter Harpending <pharpend2@gmail.com>
-- Stability    : experimental
-- Portability  : archlinux
--

module Web.Saferoute where

import qualified Data.Map.Lazy  as M
import qualified Data.Text as S

-- |The type for a route - just an alias for 'S.Text'
type Route = S.Text

-- |The type class for a resource.
class Eq r => Resource r where
  {-# MINIMAL getRoute, (resourceList | routeResourceMap) #-}

  -- Get the 'Route' for a 'Resource'. This is in place to avoid
  -- @fmap@ stuff. Giving a 'Resource' to this function will
  -- invariably return a 'Route', as opposed to 'Maybe Route', which
  -- would be the case if I used a 'M.Map' lookup.
  getRoute :: r -> Route

  -- |A list of all of the constructors for your resource type.
  resourceList :: [r]
  resourceList = M.elems routeResourceMap

  -- |A map from a route to it's resource.
  routeResourceMap :: M.Map Route r
  routeResourceMap = M.fromList [(route, resource) | resource <- resourceList,
                                                     let route = getRoute resource ]

  -- |Given a 'Route', find the 'Resource' behind it. If the route
  -- isn't associated with any 'Resource', this returns 'Nothing'.
  lookupRoute :: Route -> Maybe r
  lookupRoute route = M.lookup route routeResourceMap