HaskRel-0.1.0.2: HaskRel, Haskell as a DBMS with support for the relational algebra

Copyright© Thor Michael Støre, 2015
LicenseGPL v2 without "any later version" clause
Maintainerthormichael át gmail døt com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Database.HaskRel.HFWTabulation

Description

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.

Synopsis

Documentation

class HFWPresent r where Source

Minimal complete definition

hfwPrint, hfwPrintTypedTS

Methods

hfwPrint :: r -> IO () Source

hfwPrintTyped :: r -> IO () Source

hfwPrintTypedTS :: HListTypeSynonym ts => ts -> r -> IO () Source

Instances

(Typeable [*] a, RecordValues a, HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) => HFWPresent (Set (Record a)) Source 
(HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]], HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]], Typeable [*] r, RecordValues r) => HFWPresent (Record r) 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

Instances

((~) * (FWPPred a) flag, FWPresent' flag a) => FWPresent a Source 

class Show a => FWPresent' flag a where Source

Methods

fwPresent' :: flag -> a -> [String] Source

fwPresentTyped' :: flag -> a -> [String] Source

Instances

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

showTR :: TypeRep -> String Source

Show a TypeRep

showTRTS :: HListTypeSynonym ts => ts -> TypeRep -> String Source

Show a TypeRep, using the given type synonyms

showHListSetType :: forall a r. (Typeable r, Typeable a) => Set (r a) -> String Source

data HFWRec Source

Instances

(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

Instances

HListTypeSynonym HaskRelTS Source

HaskRel type synonyms

type family FWPPred a Source

Equations

FWPPred (Set (Record a)) = HFWRecSet 
FWPPred (Record a) = HFWRec 
FWPPred (Set (TIP a)) = HFWTIPSet 
FWPPred (TIP a) = HFWTIP 
FWPPred String = HFWString 
FWPPred a = HFWOther 

data HPresentRecAttr Source

Constructors

HPresentRecAttr 

Instances

((~) * [String] stringL, FWPresent' (FWPPred a) a) => ApplyAB HPresentRecAttr a stringL Source 

data HPresentTypedRecAttr Source

Constructors

HPresentTypedRecAttr 

Instances

((~) * [String] stringL, FWPresent' (FWPPred a) a) => ApplyAB HPresentTypedRecAttr a stringL Source