module Database.HaskRel.HFWTabulation (
HFWPresent ( hfwPrint, hfwPrintTyped, hfwPrintTypedTS ),
FWPresent ( fwPresent, fwPresentTyped ),
FWPresent' ( fwPresent', fwPresentTyped' ),
printHRecSetTab, printHRecSetTabTyped, printHRecSetTabTypedTS,
showHRecSetTab,
showTR, showTRTS, showHTypeTS, showHListSetType,
HFWTIPSet, HFWTIP, HFWRec, HFWString, HFWOther,
HListTypeSynonym ( hRecTS, hRecSetTS, hTIPTS, hTIPSetTS ), FWPPred,
HPresentRecAttr(HPresentRecAttr), HPresentTypedRecAttr(HPresentTypedRecAttr)
) where
import Data.HList.CommonMain
import Data.Typeable
import Data.Set ( Set, toList )
import Data.List ( intercalate )
import Database.HaskRel.FWTabulation
data HFWTIPSet
data HFWTIP
data HFWRecSet
data HFWRec
data HFWString
data HFWOther
type family FWPPred a where
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 EmptyTS = EmptyTS
class HListTypeSynonym s where
hRecTS :: s -> String
hRecSetTS :: s -> String
hTIPTS :: s -> String
hTIPSetTS :: s -> String
instance HListTypeSynonym EmptyTS where
hRecTS _ = "Record"
hRecSetTS _ = "Set-Record"
hTIPTS _ = "TIP"
hTIPSetTS _ = "Set-TIP"
showTR :: TypeRep -> String
showTR = showTRTS EmptyTS
showTRTS :: HListTypeSynonym ts => ts -> TypeRep -> String
showTRTS ts t
| t == stringType = "String"
| tyCon == recTyCon = hRecTS ts ++ showHListType app
| tyCon == tipTyCon = hTIPTS ts ++ showHListType app
| tyCon == setTyCon && typeRepTyCon ( head app ) == recTyCon =
hRecSetTS ts ++ showHListType ( typeRepArgs $ head app )
| tyCon == setTyCon && typeRepTyCon ( head app ) == tipTyCon =
hTIPSetTS ts ++ showHListType ( typeRepArgs $ head app )
| otherwise = show t
where
( tyCon, app ) = splitTyConApp t
stringType = typeRep ( Proxy :: Proxy String )
setTyCon = typeRepTyCon $ typeRep ( Proxy :: Proxy ( Set Int ) )
recTyCon = typeRepTyCon $ typeRep ( Proxy :: Proxy ( Record '[] ) )
tipTyCon = typeRepTyCon $ typeRep ( Proxy :: Proxy ( TIP '[] ) )
showHListSetType :: forall a (r :: [*] -> *) .
( Typeable r, Typeable a ) =>
Set (r a) -> String
showHListSetType = showHListType . typeRepArgs . head . typeRepArgs . typeOf
showHListType :: [TypeRep] -> String
showHListType = (++) " '" . show . hListTypeToTRList
hListTypeToTRList :: [TypeRep] -> [TypeRep]
hListTypeToTRList = parseHListType . typeRepArgs . head
parseHListType :: [TypeRep] -> [TypeRep]
parseHListType [] = []
parseHListType [_] = error "Not a valid TIP/Record type"
parseHListType (tr:trx) = head ( typeRepArgs tr ) : parseHListType ( typeRepArgs $ head trx )
tagFName :: TypeRep -> String
tagFName = tail . init . show . head . typeRepArgs
hRecFNames :: Typeable a => a -> [String]
hRecFNames = map tagFName . flatHRec
tagQFName :: TypeRep -> String
tagQFName = tagQFNameTS EmptyTS
tagQFNameTS :: HListTypeSynonym ts => ts -> TypeRep -> String
tagQFNameTS ts a = tagFName a ++ " :: " ++ showHTypeTS ts a
hRecQFNames :: Typeable a => a -> [String]
hRecQFNames = map tagQFName . flatHRec
hRecQFNamesTS :: ( HListTypeSynonym ts, Typeable a ) => ts -> a -> [String]
hRecQFNamesTS ts = map ( tagQFNameTS ts ) . flatHRec
showHTypeTS :: HListTypeSynonym ts => ts -> TypeRep -> String
showHTypeTS ts = showTRTS ts . head . tail . typeRepArgs
flatHRec :: Typeable a => a -> [TypeRep]
flatHRec = flatHRec' . typeRepArgs . head . typeRepArgs . typeOf
flatHRec' :: [TypeRep] -> [TypeRep]
flatHRec' [] = []
flatHRec' [m] = [m]
flatHRec' (m:mx) = m : flatHRec' ( typeRepArgs $ head mx )
class HFWPresent r where
hfwPrint :: r -> IO ()
hfwPrintTyped :: r -> IO ()
hfwPrintTyped = hfwPrintTypedTS EmptyTS
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]
instance (FWPPred a ~ flag, FWPresent' flag a) => FWPresent a where
fwPresent = fwPresent' ( undefined :: flag )
fwPresentTyped = fwPresentTyped' ( undefined :: flag )
instance Show a => FWPresent' HFWOther a where
fwPresent' _ x = [show x]
fwPresentTyped' _ x = [show x]
instance FWPresent' HFWString String where
fwPresent' _ x = [x]
fwPresentTyped' _ x = [x]
buildHRec
:: (Typeable r, RecordValues r,
HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]]) =>
Record r -> [String]
buildHRec rrTup = present1LineValue ( listPresentRec rrTup ) ( hRecFNames rrTup )
buildHRecTyped
:: (Typeable r, RecordValues r,
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]]) =>
Record r -> [String]
buildHRecTyped rrTup = present1LineValue ( listPresentTypedRec rrTup ) ( hRecQFNames rrTup )
buildHRecTypedTS
:: (HListTypeSynonym ts, Typeable r, RecordValues r,
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]]) =>
ts -> Record r -> [String]
buildHRecTypedTS ts rrTup = present1LineValue ( listPresentTypedRec rrTup ) ( hRecQFNamesTS ts rrTup )
listPresentRec :: (RecordValues r,
HFoldr (Mapcar HPresentRecAttr) [e] (RecordValuesR r) [e]) =>
Record r -> [e]
listPresentRec = hMapOut HPresentRecAttr . recordValues
listPresentTypedRec :: (RecordValues r,
HFoldr (Mapcar HPresentTypedRecAttr) [e] (RecordValuesR r) [e]) =>
Record r -> [e]
listPresentTypedRec = hMapOut HPresentTypedRecAttr . recordValues
data HPresentRecAttr = HPresentRecAttr
instance ([String] ~ stringL, FWPresent' (FWPPred a) a) =>
ApplyAB HPresentRecAttr a stringL
where
applyAB _ = fwPresent
data HPresentTypedRecAttr = HPresentTypedRecAttr
instance ([String] ~ stringL, FWPresent' (FWPPred a) a) =>
ApplyAB HPresentTypedRecAttr a stringL
where
applyAB _ = fwPresentTyped
instance (HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]],
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]],
Typeable r, RecordValues r
) =>
HFWPresent ( Record r )
where
hfwPrint = putStrLn . intercalate "\n" . buildHRec
hfwPrintTyped = putStrLn . intercalate "\n" . buildHRecTyped
hfwPrintTypedTS ts = putStrLn . intercalate "\n" . buildHRecTypedTS ts
instance ( HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR r) [[String]],
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR r) [[String]],
Typeable r, RecordValues r, ShowComponents r
) =>
FWPresent' HFWRec ( Record r )
where
fwPresent' _ = buildHRec
fwPresentTyped' _ = buildHRecTyped
showHRecSetTab ::
(Typeable a, RecordValues a,
HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) =>
Set (Record a) -> String
showHRecSetTab = intercalate "\n" . buildHRecSet
printHRecSetTab a = putStrLn $ intercalate "\n" $ buildHRecSet a
printHRecSetTabTyped a = putStrLn $ intercalate "\n" $ buildHRecSetTyped a
printHRecSetTabTypedTS ts a = putStrLn $ intercalate "\n" $ buildHRecSetTypedTS ts a
instance (Typeable a, RecordValues a,
HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]],
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) =>
HFWPresent ( Set ( Record a ) ) where
hfwPrint = printHRecSetTab
hfwPrintTyped = printHRecSetTabTyped
hfwPrintTypedTS = printHRecSetTabTypedTS
instance (Typeable a, RecordValues a, ShowComponents a,
HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]],
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) =>
FWPresent' HFWRecSet ( Set ( Record a ) )
where
fwPresent' _ = buildHRecSet
fwPresentTyped' _ = buildHRecSetTyped
unwrap :: x (Record a) -> Record a
unwrap = undefined
buildHRecSet ::
(Typeable a, RecordValues a,
HFoldr (Mapcar HPresentRecAttr) [[String]] (RecordValuesR a) [[String]]) =>
Set (Record a) -> [String]
buildHRecSet rs =
presentNLineValue ( map listPresentRec $ toList rs ) ( hRecFNames $ unwrap rs )
buildHRecSetTyped ::
(Typeable a, RecordValues a,
HFoldr (Mapcar HPresentTypedRecAttr) [[String]] (RecordValuesR a) [[String]]) =>
Set (Record a) -> [String]
buildHRecSetTyped rs =
presentNLineValue ( map listPresentTypedRec $ toList rs ) ( hRecQFNames $ unwrap rs )
buildHRecSetTypedTS
:: (Typeable a, RecordValues a,
HFoldr
(Mapcar HPresentTypedRecAttr)
[[String]]
(RecordValuesR a)
[[String]],
HListTypeSynonym ts) =>
ts -> Set (Record a) -> [String]
buildHRecSetTypedTS ts rs =
presentNLineValue ( map listPresentTypedRec $ toList rs ) ( hRecQFNamesTS ts $ unwrap rs )