-- | -- Module: Web.Page.GenId -- Copyright: (c) 2014 Ertugrul Soeylemez -- License: BSD3 -- Maintainer: Ertugrul Soeylemez -- -- This module offers a monad transformer and a class for page-unique -- identifier generation. To use it, simply add a state monad to your -- monad stack with a state type that is an instance of the -- 'HasIdStream' class (you can simply use @'Stream' 'Identifier'@, if -- you don't need any other state). See the 'newId' action to see the -- exact type of stack you need. -- -- To construct the initial state you can use the predefined 'idsFrom' -- function. It constructs a stream of unique identifiers from its -- argument character set. -- -- To generate a new identifier use the 'newId' action within your monad -- stack. The generated identifiers are of type 'Identifier'. There -- are helper functions for integrating an identifer into markup and the -- stylesheet. See the DOM helpers and the CSS helpers sections in this -- module. Also see the documentation for 'Identifier' for more -- detailed information and an example. -- -- Hint: It is perfectly valid to combine a widget writer and an -- identifier generator, so you don't need to alternate between -- constructing widgets and generating identifiers. module Web.Page.GenId ( -- * Unique identifiers Identifier(..), HasIdStream(..), idsFrom, newId, -- * DOM helpers classId, customId, dataId, domId, -- * CSS helpers idRef, idSel, classRef, classSel ) where import qualified Clay as Css import qualified Data.Stream as Str import qualified Data.Text as T import qualified Data.Vector.Unboxed as Vu import qualified Text.Blaze.Html5.Attributes as A import Control.Lens import Control.Monad.State.Class import Data.Data import Data.Stream (Stream(..)) import Language.Javascript.JMacro (ToJExpr(..), JExpr(..), JVal(..)) import Text.Blaze.Html -- | Instances of this class are types that embed an identifier stream. class HasIdStream a where -- | Lens into the identifier stream. idStream :: Lens' a (Stream Identifier) instance HasIdStream (Stream Identifier) where idStream = id -- | Identifiers that can be used with clay, jmacro and blaze-html. -- -- An identifier of this type is supposed to be used for DOM ids, -- classes or similar names. Note that the 'ToJExpr' instance converts -- it to a JavaScript string, so that you can use it with jQuery or -- functions like @getElementById@. When using jQuery, remember that it -- expects selector syntax as in the following example: -- -- > myWidget :: -- > ( HasIdStream s, -- > MonadState s m, -- > MonadWidget url (MySection -> Html) m ) -- > => m () -- > myWidget = do -- > myId <- newId -- > addSection MySection (H.p "My boring paragraph." ! domId myId) -- > addStyle $ idSel myId ? background gray -- > addStyle $ idSel myId # ".groovy" ? do -- > background darkblue -- > color pink -- > fontWeight bold -- > addScriptLink "static/jquery.js" -- > addScript [jmacro| -- > fun init -> -- > window.setTimeout -- > (\() { -- > $("#" + `myId`).addClass("groovy"); -- > $(".groovy").text("My groooovy paragraph!") }) -- > 2500; -- > $(init) |] newtype Identifier = Identifier { identifier :: String } deriving (Data, Eq, Ord, Show, ToValue, Typeable) instance ToJExpr Identifier where toJExpr (Identifier name) = ValExpr (JStr name) -- | HTML5 @class@ attribute containing the given identifier. classId :: Identifier -> Attribute classId (Identifier n) = A.class_ (toValue n) -- | Class refinement for the given identifier. classRef :: Identifier -> Css.Refinement classRef = Css.byClass . T.pack . identifier -- | Class selector for the given identifier. classSel :: Identifier -> Css.Selector classSel n = Css.star Css.# classRef n -- | Custom attribute containing the given identifier. customId :: Tag -> Identifier -> Attribute customId attr (Identifier n) = customAttribute attr (toValue n) -- | HTML5 @id@ attribute containing the given identifier. domId :: Identifier -> Attribute domId (Identifier n) = A.id (toValue n) -- | HTML5 data attribute (@data-*@) containing the given identifier. dataId :: Tag -> Identifier -> Attribute dataId attr (Identifier n) = dataAttribute attr (toValue n) -- | Id refinement for the given identifier. idRef :: Identifier -> Css.Refinement idRef = Css.byId . T.pack . identifier -- | Id selector for the given identifier. idSel :: Identifier -> Css.Selector idSel n = Css.star Css.# idRef n -- | Infinite stream of identifiers built from the given character set. -- The stream is sorted by identifier length, shortest first. idsFrom :: [Char] -> Stream Identifier idsFrom charList = fmap (Identifier . map (chars Vu.!)) (Str.iterate next [0]) where chars = Vu.fromList charList numChars = Vu.length chars next [] = [0] next (x':xs) | x < numChars = x : xs | otherwise = 0 : next xs where x = succ x' -- | Fetches the next identifier. newId :: (HasIdStream a, MonadState a m) => m Identifier newId = idStream %%= \(Cons x xs) -> (x, xs)