module Airship.Internal.Route where
import Airship.Resource
import Data.Monoid
import Data.Foldable (foldr')
import Data.Text (Text)
import Data.HashMap.Strict (HashMap, insert)
#if __GLASGOW_HASKELL__ < 710
import           Control.Applicative
#endif
import Control.Monad.Writer (Writer, execWriter)
import Control.Monad.Writer.Class (MonadWriter)
import Data.String (IsString, fromString)
newtype Route = Route { getRoute :: [BoundOrUnbound] } deriving (Show, Monoid)
data BoundOrUnbound = Bound Text
                    | Var Text
                    | RestUnbound deriving (Show)
instance IsString Route where
    fromString s = Route [Bound (fromString s)]
runRouter :: RoutingSpec s m a -> [(Route, Resource s m)]
runRouter routes = execWriter (getRouter routes)
(</>) :: Route -> Route -> Route
(</>) = (<>)
root :: Route
root = Route []
var :: Text -> Route
var t = Route [Var t]
star :: Route
star = Route [RestUnbound]
newtype RoutingSpec s m a = RoutingSpec { getRouter :: Writer [(Route, Resource s m)] a }
    deriving (Functor, Applicative, Monad, MonadWriter [(Route, Resource s m)])
route :: [(Route, a)] -> [Text] -> a -> (a, HashMap Text Text)
route routes pInfo resource404 = foldr' (matchRoute pInfo) (resource404, mempty) routes
matchRoute :: [Text] -> (Route, a) -> (a, HashMap Text Text) -> (a, HashMap Text Text)
matchRoute paths (rSpec, resource) (previousMatch, previousMap) =
    case matchesRoute paths rSpec of
      Nothing -> (previousMatch, previousMap)
      Just m  -> (resource, m)
matchesRoute :: [Text] -> Route -> Maybe (HashMap Text Text)
matchesRoute paths spec = matchesRoute' paths (getRoute spec) mempty where
    
    matchesRoute' []        []              acc     = Just acc
    
    matchesRoute' (_ph:_ptl) []             _       = Nothing
    
    matchesRoute' _         (RestUnbound:_) acc     = Just acc
    
    
    matchesRoute' (ph:ptl)  (Bound sh:stt)  acc
        | ph == sh
                                                    = matchesRoute' ptl stt acc
    matchesRoute' (ph:ptl)  (Var t:stt)     acc     = matchesRoute' ptl stt (insert t ph acc)
    matchesRoute' _         _               _acc    = Nothing