{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE ImpredicativeTypes #-}

module Main (main) where

import Thermoprint.Server

import Thermoprint.Server.Printer.Generic

import Control.Monad.Trans.Resource
import Control.Monad.Logger
import Control.Monad.Reader

import Data.Function ((&))

import Database.Persist.Postgresql

import qualified Network.Wai.Handler.Warp as Warp

type ServerM = ReaderT ConnectionPool (LoggingT IO)

main :: IO ()
main = thermoprintServer True (NT runDb) $ configure <$> def `withPrinters` printers'
  where
    runDb :: ServerM a -> IO a
    runDb = runStderrLoggingT . filterLogger (\_ lvl -> lvl >= LevelInfo) . withPostgresqlPool "" 5 . runReaderT

    printers' = [ (pure $ genericPrint "/dev/usb/lp0", def :: QMConfig (ResourceT ServerM))
                ]

    configure c = c
      { queueManagers = queueManagers
      , warpSettings  = warpSettings
      }

    queueManagers _ = QMConfig
      { manager = union [ limitHistorySize 100
                        , limitHistoryAge 3600
                        ]
      , collapse = standardCollapse
      }

    warpSettings = Warp.defaultSettings
      & Warp.setHost "::1"
      & Warp.setPort 8080