slug-0.1.7: Type-safe slugs for Yesod ecosystem

Copyright© 2015–2017 Mark Karpov
LicenseBSD 3 clause
MaintainerMark Karpov <markkarpov92@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Web.Slug

Description

Type-safe slug implementation for Yesod ecosystem.

Synopsis

Documentation

data Slug Source #

Slug. Textual value inside is always guaranteed to have the following qualities:

  • it's not empty;
  • it consists only of alpha-numeric groups of characters (words) separated by '-' dashes in such a way that entire slug cannot start or end in a dash and also two dashes in a row cannot be found;
  • every character with defined notion of case is lower-cased.

Slugs are good for semantic URLs and also can be used as identifier of a sort in some cases.

Instances

Eq Slug Source # 

Methods

(==) :: Slug -> Slug -> Bool #

(/=) :: Slug -> Slug -> Bool #

Data Slug Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Slug -> c Slug #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Slug #

toConstr :: Slug -> Constr #

dataTypeOf :: Slug -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Slug) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Slug) #

gmapT :: (forall b. Data b => b -> b) -> Slug -> Slug #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Slug -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Slug -> r #

gmapQ :: (forall d. Data d => d -> u) -> Slug -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Slug -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Slug -> m Slug #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Slug -> m Slug #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Slug -> m Slug #

Ord Slug Source # 

Methods

compare :: Slug -> Slug -> Ordering #

(<) :: Slug -> Slug -> Bool #

(<=) :: Slug -> Slug -> Bool #

(>) :: Slug -> Slug -> Bool #

(>=) :: Slug -> Slug -> Bool #

max :: Slug -> Slug -> Slug #

min :: Slug -> Slug -> Slug #

Read Slug Source # 
Show Slug Source # 

Methods

showsPrec :: Int -> Slug -> ShowS #

show :: Slug -> String #

showList :: [Slug] -> ShowS #

Semigroup Slug Source # 

Methods

(<>) :: Slug -> Slug -> Slug #

sconcat :: NonEmpty Slug -> Slug #

stimes :: Integral b => b -> Slug -> Slug #

Arbitrary Slug Source # 

Methods

arbitrary :: Gen Slug #

shrink :: Slug -> [Slug] #

ToJSON Slug Source # 
FromJSON Slug Source # 
ToHttpApiData Slug Source # 
FromHttpApiData Slug Source # 
PathPiece Slug Source # 
PersistFieldSql Slug Source # 

Methods

sqlType :: Proxy * Slug -> SqlType #

PersistField Slug Source # 

mkSlug :: MonadThrow m => Text -> m Slug Source #

Create a Slug from a Text value, all necessary transformations are applied. The argument of this function can be title of an article or something like that.

Note that the result is inside MonadThrow, that means you can just get it in Maybe, in more complex contexts it will throw SlugException exception using InvalidInput constructor.

This function also has a useful property:

mkSlug = mkSlug >=> mkSlug . unSlug

unSlug :: Slug -> Text Source #

Get textual representation of a Slug.

parseSlug :: MonadThrow m => Text -> m Slug Source #

Convert a Text into a Slug only when it is already valid slug.

This function can throw the SlugException exception using InvalidSlug constructor.

truncateSlug Source #

Arguments

:: MonadThrow m 
=> Int

Maximum length of slug, must be greater than 0

-> Slug

Original non-truncated slug

-> m Slug

Truncated slug

Ensure that given Slug is not longer than given maximum number of characters. If truncated slug ends in a dash, remove that dash too. (Dash at the end would violate properties described in documentation for Slug.)

If the first argument is not a positive number, SlugException is thrown using InvalidLength constructor.

data SlugException Source #

This exception is thrown by mkSlug when its input cannot be converted into a proper Slug.

Constructors

InvalidInput Text

Slug cannot be generated for given text

InvalidSlug Text

Input is not a valid slug, see parseSlug

InvalidLength Int

Requested slug length is not a positive number