module Main where

import Control.Monad.Trans (lift)
-- useful for building the parent-children structure for the hierarchical CRUD
import RESTng.Resources (commentProxy, ratingVoteProxy, userProxy)

-- useful for building the application grid context
import qualified Text.CxML as Cx (t, h1logo, vertNav, CxML)
import Text.YuiGrid

import RESTng.RqHandlers
import RESTng.System

import Config
import Resource
import FrontPage (frontPage)
import Tags (tagsHandler)
import Search (searchForm, searchHandler)


-----------------------------------------------
-- CRUD hierarchy
-----------------------------------------------
resList = [
           CB authorProxy [CCB bookProxy, CCB exampleAppTagProxy],
           CB bookProxy [CCB commentProxy, CCB ratingVoteProxy, CCB exampleAppTagProxy],

           CB userProxy [],
           CB commentProxy [],
           CB ratingVoteProxy [],
           CB exampleAppTagProxy []
          ]

-----------------------------------------------
-- Application GRID context
-----------------------------------------------
appCtx :: RqHandlerT RESTng RESTngResp -> RqHandlerT RESTng RESTngResp
appCtx h = afterSettingAuthUser $ do
              usrName <- lift authdUsername
              inGridWithElems [
                   boxInFooter (Cx.t "Footer goes here."),
                   boxInHeader (Cx.h1logo "Header image goes in the URL" "/images/header.gif"),
                   smallMarginBottomCSS $ nearLeft $ setColumnsVote 2 $ nearBottom $ boxInHeader (loginControl usrName),
                   smallMarginBottomCSS $ nearRight $ setColumnsVote 2 $ nearBottom $ boxInHeader searchForm,
                   boxInLeftSidebar ( Cx.vertNav [("Home", "/"),
                                                  ("About", "/about"),
                                                  ("Contact", "/contact")])
                  ] $ withTitle "Hello World" h


loginControl ::String -> Cx.CxML RequestContext
loginControl userName = Cx.t ("User: " ++ userName)

-----------------------------------------------
-- Routes and handlers
-----------------------------------------------
mainHandlers :: [IORqHandler BasicRsp]
mainHandlers = [modResp restngRespToRsp applicationPages, imgFilesHandler]

imgFilesHandler = under "images" $ mapDir publicFilesDir

applicationPages :: IORqHandler RESTngResp
applicationPages = db $ appCtx $ anyOf [anyLoginHandler, resourcesHandler resList, tagsHandler, searchHandler, frontPage]
                   where
                     db = safeDbRqHandler connString okNonCxMLStrRsp

-----------------------------------------------
-- Main daemon and port
-----------------------------------------------
main :: IO ()
main = runHttpServer 8080 mainHandlers