module Web.Slug
( Slug
, mkSlug
, unSlug
, SlugException (..) )
where
import Control.Exception (Exception)
import Control.Monad (mzero, (>=>))
import Control.Monad.Catch (MonadThrow (..))
import Data.Aeson.Types (ToJSON (..), FromJSON (..))
import Data.Char (isAlphaNum)
import Data.Text (Text)
import Data.Typeable (Typeable)
import Database.Persist.Class (PersistField (..))
import Database.Persist.Sql (PersistFieldSql (..))
import Database.Persist.Types (SqlType (..))
import Web.PathPieces
import qualified Data.Aeson.Types as A
import qualified Data.Text as T
data SlugException = InvalidInput Text deriving (Typeable)
instance Show SlugException where
show (InvalidInput text) = "Cannot build slug for " ++ show text
instance Exception SlugException
newtype Slug = Slug
{ unSlug :: Text
} deriving (Eq, Show, Typeable)
mkSlug :: MonadThrow m => Text -> m Slug
mkSlug text =
let ws = getSlugWords text
in if null ws
then throwM (InvalidInput text)
else return . Slug . T.intercalate "-" $ ws
getSlugWords :: Text -> [Text]
getSlugWords = T.words . T.toLower . T.map f . T.replace "'" ""
where f x = if isAlphaNum x then x else ' '
instance ToJSON Slug where
toJSON = toJSON . unSlug
instance FromJSON Slug where
parseJSON (A.String v) = maybe mzero return (mkSlug v)
parseJSON _ = mzero
instance PersistField Slug where
toPersistValue = toPersistValue . unSlug
fromPersistValue =
fromPersistValue >=> either (Left . T.pack . show) Right . mkSlug
instance PersistFieldSql Slug where
sqlType = const SqlString
instance PathPiece Slug where
fromPathPiece v = mkSlug v >>= check
where check s = if unSlug s == T.toLower v then Just s else Nothing
toPathPiece = unSlug