{-| Module: IHP.View.Classes Description: Provides the classes view helper function Copyright: (c) digitally induced GmbH, 2020 -} module IHP.View.Classes where import IHP.Prelude -- | Helper for dynamically generating the @class=".."@ attribute. -- -- Given a list like -- -- > [("a", True), ("b", False), ("c", True)] -- -- builds a class name string for all parts where the second value is @True@. -- -- E.g. -- -- >>> classes [("a", True), ("b", False), ("c", True)] -- "a c" -- -- When setting @b@ to @True@: -- -- >>> classes [("a", True), ("b", True), ("c", True)] -- "a b c" -- -- __Example:__ -- -- >>>
--
-- -- >>>
--
-- -- >>> forEach projects \project -> [hsx| -- >>>
-- >>> {project} -- >>>
-- >>> |] -- If project is active:
{project}
-- Otherwise:
{project}
classes :: [(Text, Bool)] -> Text classes !classNameBoolPairs = classNameBoolPairs |> filter snd |> map fst |> unwords {-# INLINABLE classes #-} -- | Allows `("my-class", True)` to be written as `"my-class"` -- -- Useful together with 'classes' instance IsString (Text, Bool) where fromString string = (cs string, True) {-# INLINABLE fromString #-}