yesod-table-2.0.3: HTML tables for Yesod

Safe HaskellNone
LanguageHaskell2010

Yesod.Table

Description

Table building library for yesod

This library is intended to be brought in by a qualified import along with type import as follows:

import qualified Yesod.Table as Table
import Yesod.Table (Table)

There are two types in this module: Table and Column. Roughly, a Table is just a list of Columns. Except in the case of rendering a Table, you should not need to use the data constructors of either of these types. (In fact, you should not need to refer to the type Column either). Instead, you should use the functions singleton, text, int, etc. to build singleton Tables (a Table with only one Column) and use monoidal concatenation to combine these.

It is important to note that, as defined in this library, Table refers to a blueprint for an HTML table, not a complete table with content.

If you want to define your own table rendering function (and it's likely that you will), then you will need the aforementioned data constructors. You can look at the source of buildBootstrap for an example of how to do this.

Synopsis

Documentation

newtype Table site a Source

Constructors

Table (Seq (Column site a)) 

Instances

data Column site a Source

Constructors

Column 

Fields

header :: !(WidgetT site IO ())
 
cell :: !(a -> WidgetT site IO ())
 

Instances

buildBootstrap :: Table site a -> [a] -> WidgetT site IO () Source

From a Table blueprint and a list of the data that it accepts, build the actual html needed to visualize this data. This particular rendering of the data applies the classes table and table-striped to the table element. If you are using bootstrap, this means that it will be formatted in the bootstrap way. If not, the table will still render correctly, but the classes will be renamed. I'm open to pull requests for supporting other common table formats out of the box.

singleton :: WidgetT site IO () -> (a -> WidgetT site IO ()) -> Table site a Source

This is the most primitive and essential operation for building a Table. All other table-building functions (such as widget, text, and linked) build on top of singleton. One common trend in the convenience functions is that they accept Text as the table header. This is done because I have found that it is uncommon to need the full power of HTML in the header. Just know that if you need it, this function is the only way to get it. The first argument is a widget that is the content to be displayed in the table header. The second argument is the a function that consumes a value to produce the content shown in a row of the table body. These widgets need to be wrapped in a th/td if you are using this function.

widget :: Text -> (a -> WidgetT site IO ()) -> Table site a Source

This is the same as singleton, with the convenience of accepting the table header as Text. It also wraps the header widget in a th element and wraps the cell widget in a td element.

const :: Text -> WidgetT site IO () -> Table site a Source

This is the same as widget, but the table cell content it produces is constant, meaning that the table cell in this column will be the same for all rows.

text :: Text -> (a -> Text) -> Table site a Source

Identical to widget, with the convenience of accepting the table cell content as Text.

string :: Text -> (a -> String) -> Table site a Source

Identical to widget, with the convenience of accepting the table cell content as String.

bytestring :: Text -> (a -> ByteString) -> Table site a Source

Identical to widget, with the convenience of accepting the table cell content as ByteString. If the ByteString is not encoded as UTF8-encoded text, the cell will display text indicating that non-text data was given.

show :: Show b => Text -> (a -> b) -> Table site a Source

Identical to widget, with the convenience of accepting the table cell content as any type with an instance of Show.

printf :: PrintfArg b => Text -> String -> (a -> b) -> Table site a Source

Identical to widget, but allow to format the output with the syntax of printf The datatype used must be an instance of PrintfArg

int :: Text -> (a -> Int) -> Table site a Source

Identical to widget, with the convenience of accepting the table cell content as Int.

linked Source

Arguments

:: Text

Column name

-> (a -> Text)

Text extracting function

-> (a -> Route site)

Route extracting function

-> Table site a 

Convenience function for building a plaintext link where the link text and the route are determined by the row of data. If you are working with an Entity (from persistent) and your foundation type is named App you may want something like this:

myTable :: Table App (Entity Foo)
myTable = mempty
  <> Table.linked "Name" (fooName . entityVal) (FooEditR . entityKey)
  <> Table.int    "Size" (fooSize . entityVal)

This is the blueprint for a two-column table. The first column is a link for editing the Foo, and the linked text is the Foo name. The second column is just a number representing the size of the Foo shown as plaintext.

when Source

Arguments

:: (a -> Bool)

Predicate

-> Table site a

Existing table

-> Table site a 

Prevents showing values in a Table if a condition is not met. Example

myTable :: Table App Person
myTable = mempty
  <> Table.text "Name" personName
  <> Table.when (\p -> personAge p > 21) (Table.int "Age" personAge)

In this example, the table header Age will always show up with its corresponding column, but any row for a person under 21 will have a empty value for that column. The effect can be more profound:

myTable :: Table App Person
myTable = mempty
  <> Table.text "Name" personName
  <> Table.when (\p -> personAge p > 21) (mempty
    <> Table.text "Favorite Color" personFavoriteColor
    <> Table.text "Address" personAddress
    <> Table.linked "Profile Page" (const "Profile") (ProfileR . personUsername)
    )

This second example does not show information for any of the last three columns if the person is under 21. The columns themselves though are always present regardless of whether or not any values satisfy the predicate.

whenWith Source

Arguments

:: WidgetT site IO ()

Contents when predicate is false

-> (a -> Bool)

Predicate

-> Table site a

Existing table

-> Table site a 

maybe :: Table site a -> Table site (Maybe a) Source

Promote a Table to take Maybe values. When the data passed in matches the Just data constructor, the row is presented as it would be with the original table. When it is Nothing, the row is empty.

As an example, imagine that in the data model for some application, there exists a User and an Item. Each Item can belong to either one or zero Users. We may build a table as follows:

userTable :: Table site User
userTable = ...

itemTable :: Table site Item
itemTable = ...

itemWithUserTable :: Table site (Item, Maybe User)
itemWithUserTable = mconcat
  [ contramap fst itemTable
  , contramap snd (Table.maybe peopleTable)
  ]

maybeWith :: WidgetT site IO () -> Table site a -> Table site (Maybe a) Source

columns :: (b -> a -> WidgetT site IO ()) -> (b -> Text) -> [b] -> Table site a Source

This builds a multicolumn table. Here is an example of how this could be used:

import Data.List (lookup)
import qualified Data.Text as Text

data Color = Red | Green | Blue
  deriving (Enum,Show,Bounded)

data Age = Child | Teen | Adult | Elder
  deriving (Enum,Show,Bounded)

preferenceLevel :: Age -> Color -> WidgetT site IO ()
preferenceLevel age color = intToWidget $ fromMaybe 0 $ lookup (age,color)
  [ ((Child,Red),   36), ((Child,Green, 10)), ((Teen,Green), 16)
  , ((Teen,Blue),    8), ((Teen,Red),    31), ((Adult,Blue), 18)
  , ((Adult,Green), 17), ((Elder,Blue),  41)
  ]
  where intToWidget :: Int -> WidgetT site IO ()
        intToWidget = toWidget . toHtml . Text.pack . show

myTable :: Table App Color
myTable = mconcat
  [ Table.text "" (Text.pack . show)
  , Table.columns preferenceLevel (Text.pack . show) [minBound..maxBound]
  ]

myWidget :: WidgetT App IO ()
myWidget = Table.buildBootstrap myTable [minBound..maxBound]

The appearance of myWidget would be:

      | Child | Teen | Adult | Elder
-------------------------------------
Red   |   36  |  31  |   0   |   0
Green |   10  |  16  |  17   |   0
Blue  |    0  |   8  |  18   |  41

columns' :: (b -> a -> WidgetT site IO ()) -> (b -> WidgetT site IO ()) -> [b] -> Table site a Source

This function is identical to columns except that it does not wrap the cell contents with th and td for you.

bool :: Text -> (a -> Bool) -> (a -> WidgetT site IO ()) -> (a -> WidgetT site IO ()) -> Table site a Source

Then is roughly an if-then-else construct with the latter two clauses (then and else) reversed. The name is taken from the bool function in Bool.