{-# LANGUAGE MultiParamTypeClasses, FlexibleInstances, FlexibleContexts #-} {-| Module : Data.Representation Description : Represent various data in a common type, such as text or tables Copyright : (c) Olaf Klinke License : GPL-3 Maintainer : olaf.klinke@phymetric.de Stability : experimental Haskell has no dependent types, whence we can store only one type of value at each node of the data dependency graph. If in addition to Pandoc you want to extract the data in a machine-readable format, then set the @alt@ type parameter of your Provenience actions accordingly and provide 'Representation' instances for all your variable values. Each call to @render@ or @renderWith@ automatically invokes a call to 'representation'. In order to keep the dependency list of this package small beyond the dependencies of pandoc, we have omitted many useful instances. Add your own instances as you see fit, for example @ instance Serializable a => Representation a ByteString where representation = toByteString @ For spreadsheet-like representations, - basic values become single cells in a single row, - foldable structures of basic values become single columns, - doubly-nested structures of basic values become proper tables. -} module Data.Representation where import Data.Spreadsheet import Data.Time import Data.Sequence import Data.Ratio import Data.Aeson.Types (Value,ToJSON(..)) import Text.Blaze (Markup,ToMarkup(..)) -- | A representation of type @a@ as type @b@, not necessarily invertible. class Representation a b where representation :: a -> b -- | The Prelude provides a 'String' representation instance Show a => Representation a String where representation = show -- | Representation as JSON 'Value's instance ToJSON a => Representation a Value where representation = toJSON -- | Representation via blaze instance ToMarkup a => Representation a Markup where representation = toMarkup -- | Dummy instance when no alternative representation is required. -- @'representation' = 'const' ()@ instance Representation a () where representation = const () -- @()@ is the terminal object of the category @Hask@ -- single values are single cells in a single row instance (ToRow StaticCellValue row) => Representation (Ratio Integer) (Seq row) where -- needed to resolve overlap because Ratio could be Foldable representation x = pure (cellList [CellNumber x]) instance {-# OVERLAPPABLE #-} (ToRow StaticCellValue row, Real a) => Representation a (Seq row) where representation x = pure (cellList [CellNumber (toRational x)]) instance ToRow StaticCellValue row => Representation String (Seq row) where representation txt = pure (cellList [CellText txt]) instance ToRow StaticCellValue row => Representation Bool (Seq row) where representation b = pure (cellList [CellBool b]) instance ToRow StaticCellValue row => Representation ZonedTime (Seq row) where representation t = pure (cellList [CellTime t]) -- lists are single columns instance {-# OVERLAPPABLE #-} (Foldable f, ToRow StaticCellValue row, Real a) => Representation (f a) (Seq row) where representation = foldr (\x rows -> (cellList [CellNumber (toRational x)]) <| rows) empty instance (Foldable f, ToRow StaticCellValue row) => Representation (f String) (Seq row) where representation = foldr (\t rows -> (cellList [CellText t]) <| rows) empty instance (Foldable f, ToRow StaticCellValue row) => Representation (f Bool) (Seq row) where representation = foldr (\b rows -> (cellList [CellBool b]) <| rows) empty instance (Foldable f, ToRow StaticCellValue row) => Representation (f ZonedTime) (Seq row) where representation = foldr (\t rows -> (cellList [CellTime t]) <| rows) empty -- nested lists become tables instance {-# OVERLAPPABLE #-} (Foldable r, ToRow StaticCellValue row, Traversable c, Real a) => Representation (r (c a)) (Seq row) where representation = foldr (\xs rows -> cellList (fmap (CellNumber . toRational) xs) <| rows) empty instance (Foldable r, ToRow StaticCellValue row, Traversable c) => Representation (r (c String)) (Seq row) where representation = foldr (\xs rows -> cellList (fmap CellText xs) <| rows) empty instance (Foldable r, ToRow StaticCellValue row, Traversable c) => Representation (r (c Bool)) (Seq row) where representation = foldr (\xs rows -> cellList (fmap CellBool xs) <| rows) empty instance (Foldable r, ToRow StaticCellValue row, Traversable c) => Representation (r (c ZonedTime)) (Seq row) where representation = foldr (\xs rows -> cellList (fmap CellTime xs) <| rows) empty