Copyright | © Thor Michael Støre, 2015 |
---|---|
License | GPL v2 without "any later version" clause |
Maintainer | thormichael át gmail døt com |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
HList fixed-width tabular presentation. Presentation of HList values in a two-dimensional, tabular fixed-width font form with a header consisting of labels and optionally types. Only records are supported by this module, see TIPFWTabulation
for support for TIPs.
- class HFWPresent r where
- hfwPrint :: r -> IO ()
- hfwPrintTyped :: r -> IO ()
- hfwPrintTypedTS :: HListTypeSynonym ts => ts -> r -> IO ()
- class Show a => FWPresent a where
- fwPresent :: a -> [String]
- fwPresentTyped :: a -> [String]
- class Show a => FWPresent' flag a where
- fwPresent' :: flag -> a -> [String]
- fwPresentTyped' :: flag -> a -> [String]
- printHRecSetTab :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> IO ()
- printHRecSetTabTyped :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> IO ()
- printHRecSetTabTypedTS :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]], HListTypeSynonym ts) => ts -> Set (Record a) -> IO ()
- showHRecSetTab :: (Typeable a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> String
- showTR :: TypeRep -> String
- showTRTS :: HListTypeSynonym ts => ts -> TypeRep -> String
- showHTypeTS :: HListTypeSynonym ts => ts -> TypeRep -> String
- showHListSetType :: forall a r. (Typeable r, Typeable a) => Set (r a) -> String
- data HFWTIPSet
- data HFWTIP
- data HFWRec
- data HFWString
- data HFWOther
- class HListTypeSynonym s where
- type family FWPPred a
- data HPresentRecAttr = HPresentRecAttr
- data HPresentTypedRecAttr = HPresentTypedRecAttr
Documentation
class HFWPresent r where Source
hfwPrintTyped :: r -> IO () Source
hfwPrintTypedTS :: HListTypeSynonym ts => ts -> r -> IO () Source
(HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]], Typeable [*] r, RecordValues r) => HFWPresent (Record r) Source | |
(Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) => HFWPresent (Set (Record a)) Source | |
(Ord (HList b), Read (HList (RecordValuesR b)), Typeable [*] b, RecordValues b, HMapAux HList TaggedFn (RecordValuesR b) b, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR b) [[String]], HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR b) [[String]]) => HFWPresent (Relvar b) Source |
class Show a => FWPresent a where Source
((~) * (FWPPred a) flag, FWPresent' flag a) => FWPresent a Source |
class Show a => FWPresent' flag a where Source
fwPresent' :: flag -> a -> [String] Source
fwPresentTyped' :: flag -> a -> [String] Source
Show a => FWPresent' HFWOther a Source | |
FWPresent' HFWString String Source | |
(HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]], Typeable [*] r, RecordValues r, ShowComponents r) => FWPresent' HFWRec (Record r) Source |
printHRecSetTab :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> IO () Source
Prints a set of HList records in a table format
printHRecSetTabTyped :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> IO () Source
Prints a set of HList records in a table format, with types in the header
printHRecSetTabTypedTS :: (Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]], HListTypeSynonym ts) => ts -> Set (Record a) -> IO () Source
Prints a set of HList records in a table format, with types that use the given type synonyms in the header
showHRecSetTab :: (Typeable a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) => Set (Record a) -> String Source
showTRTS :: HListTypeSynonym ts => ts -> TypeRep -> String Source
Show a TypeRep, using the given type synonyms
showHTypeTS :: HListTypeSynonym ts => ts -> TypeRep -> String Source
(HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]], Typeable [*] r, RecordValues r, ShowComponents r) => FWPresent' HFWRec (Record r) Source |
class HListTypeSynonym s where Source
Type synoyms used when building the table header with type names
HListTypeSynonym HaskRelTS Source | HaskRel type synonyms |
data HPresentRecAttr Source
((~) * [String] stringL, FWPresent' (FWPPred a) a) => ApplyAB HPresentRecAttr a stringL Source |
data HPresentTypedRecAttr Source
((~) * [String] stringL, FWPresent' (FWPPred a) a) => ApplyAB HPresentTypedRecAttr a stringL Source |