module Data.HList.Data (
DataHListFlatCxt,
DataRecordCxt,
TypeRepsList(..),
RecordLabelsStr(..),
GfoldlK(..),
GunfoldK(..),
HListFlat(..),
TypeablePolyK,
) where
import Data.HList.FakePrelude
import Data.HList.HList
import Data.HList.Record
import Data.HList.Variant
import Data.Data
import Data.HList.TIC
import Data.HList.TIP
import Data.Orphans ()
#if OLD_TYPEABLE
import Data.List
#endif
import Unsafe.Coerce
deriving instance Typeable (HList '[]) => Data (HList '[])
deriving instance
(Data x,
Data (HList xs),
TypeablePolyK (x ': xs),
Typeable (HList (x ': xs)
)) => Data (HList (x ': xs))
deriving instance
(TypeablePolyK xs,
Typeable (HList xs),
Data (HList xs)) => Data (TIP xs)
deriving instance
(TypeablePolyK xs,
Typeable (Variant xs),
Data (Variant xs)) => Data (TIC xs)
newtype HListFlat a = HListFlat (HList a)
type DataHListFlatCxt na g a = (
g ~ FoldRArrow a (HList a),
HBuild' '[] g,
Typeable (HListFlat a),
TypeablePolyK a,
HFoldl (GfoldlK C) (C g) a (C (HList a)),
HFoldr
(GunfoldK C)
(C g)
(HReplicateR na ())
(C (HList a)),
HLengthEq a na,
HReplicate na ())
type family FoldRArrow (xs :: [*]) (r :: *)
type instance FoldRArrow '[] r = r
type instance FoldRArrow (x ': xs) r = x -> FoldRArrow xs r
instance DataHListFlatCxt na g a => Data (HListFlat a) where
gfoldl k z (HListFlat xs) = c3 $
hFoldl
(c1 (GfoldlK k))
(c2 (z hBuild))
xs
where
c1 :: forall c. GfoldlK c -> GfoldlK C
c1 = unsafeCoerce
c2 :: forall c. c g -> C g
c2 = unsafeCoerce
c3 :: forall c. C (HList a) -> c (HListFlat a)
c3 = unsafeCoerce
gunfold k z _ =
c3 $ withSelf $ \self ->
hFoldr
(c1 (GunfoldK k))
(c2 (z hBuild))
(hReplicate (hLength self) ())
where
withSelf :: forall t c. (t -> c t) -> c t
withSelf x = x undefined
c1 :: forall c. GunfoldK c -> GunfoldK C
c1 = unsafeCoerce
c2 :: forall c. c g -> C g
c2 = unsafeCoerce
c3 :: forall c. C (HList a) -> c (HListFlat a)
c3 = unsafeCoerce
dataTypeOf _ = hListFlatDataRep
toConstr _ = hListFlatConRep
hListFlatDataRep = mkDataType "Data.HList.HList" [hListFlatConRep]
hListFlatConRep = mkConstr hListFlatDataRep "HListFlat" [] Prefix
type DataRecordCxt a =
(Data (HListFlat (RecordValuesR a)),
TypeablePolyK a,
TypeRepsList (Record a),
RecordValues a,
RecordLabelsStr a)
instance DataRecordCxt a => Data (Record a) where
gfoldl k z xs = c1 (gfoldl k z (HListFlat (recordValues xs)))
where
c1 :: forall c. c (HListFlat (RecordValuesR a)) -> c (Record a)
c1 = unsafeCoerce
gunfold k z con = c1 (gunfold k z con)
where
c1 :: forall c. c (HListFlat (RecordValuesR a)) -> c (Record a)
c1 = unsafeCoerce
dataTypeOf x = snd (recordReps (recordLabelsStr x))
toConstr x = fst (recordReps (recordLabelsStr x))
recordReps fields =
let c = mkConstr d "Record" fields Prefix
d = mkDataType "Data.HList.Record" [c]
in (c,d)
class RecordLabelsStr (xs :: [*]) where
recordLabelsStr :: Record xs -> [String]
instance RecordLabelsStr '[] where
recordLabelsStr _ = []
instance (RecordLabelsStr xs,
ShowLabel x) => RecordLabelsStr (Tagged x t ': xs) where
recordLabelsStr _ = showLabel (Label :: Label x) :
recordLabelsStr (undefined :: Record xs)
class RecordLabelsStr2 (xs :: [k]) where
recordLabelsStr2 :: proxy xs -> [String]
instance RecordLabelsStr2 '[] where
recordLabelsStr2 _ = []
instance (RecordLabelsStr2 xs,
ShowLabel x) => RecordLabelsStr2 (x ': xs) where
recordLabelsStr2 _ = showLabel (Label :: Label x) :
recordLabelsStr2 (Proxy :: Proxy xs)
data C a
#if !OLD_TYPEABLE
deriving instance Typeable Record
deriving instance Typeable HList
deriving instance Typeable HListFlat
deriving instance Typeable Variant
deriving instance Typeable TIC
deriving instance Typeable TIP
deriving instance Typeable 'HZero
deriving instance Typeable 'HSucc
#else
instance TypeRepsList (Record xs) => Typeable (HList xs) where
typeOf x = mkTyConApp (mkTyCon3 "HList" "Data.HList.HList" "HList")
[ tyConList (typeRepsList (Record x)) ]
instance (TypeRepsList (Record xs)) => Typeable (Record xs) where
typeOf x = mkTyConApp (mkTyCon3 "HList" "Data.HList.Record" "Record")
[ tyConList (typeRepsList x) ]
instance TypeRepsList (Record xs) => Typeable (Variant xs) where
typeOf _ = mkTyConApp (mkTyCon3 "HList" "Data.HList.Variant" "Variant")
[ tyConList (typeRepsList (error "Data.HList.Data:Typeable Variant" :: Record xs)) ]
instance Typeable (Variant xs) => Typeable (TIC xs) where
typeOf (TIC xs) = mkTyConApp (mkTyCon3 "HList" "Data.HList.TIC" "TIC")
[typeOf xs]
instance Typeable (HList xs) => Typeable (TIP xs) where
typeOf (TIP xs) = mkTyConApp (mkTyCon3 "HList" "Data.HList.TIP" "TIP")
[typeOf xs]
instance ShowLabel sy => Typeable1 (Tagged sy) where
typeOf1 _ = mkTyConApp
(mkTyCon3 "HList" "Data.HList.Data" (showLabel (Label :: Label sy)))
[]
instance (ShowLabel sy, Typeable x) => Typeable (Tagged sy x) where
typeOf _ = mkTyConApp
(mkTyCon3 "GHC" "GHC.TypeLits" (showLabel (Label :: Label sy)))
[mkTyConApp (mkTyCon3 "HList" "Data.HList.Record" "=") [],
typeOf (error "Data.HList.Data:Typeable Tagged" :: x)
]
instance Typeable (HList a) => Typeable (HListFlat a) where
typeOf _ = mkTyConApp (mkTyCon3 "HList" "Data.HList.Data" "HListFlat")
[typeOf (error "Typeable HListFlat" :: HList a)]
tyConList xs = mkTyConApp open ( intersperse comma xs ++ [close] )
where
open = mkTyCon3 "GHC" "GHC.TypeLits" "["
close = mkTyConApp (mkTyCon3 "GHC" "GHC.TypeLits" "]") []
comma = mkTyConApp (mkTyCon3 "GHC" "GHC.TypeLits" ",") []
#endif
class TypeRepsList a where
typeRepsList :: a -> [TypeRep]
instance (TypeRepsList (HList xs)) => TypeRepsList (Record xs) where
typeRepsList (Record xs) = typeRepsList xs
instance (TypeRepsList (HList xs), Typeable x) => TypeRepsList (HList (x ': xs)) where
typeRepsList (~(x `HCons` xs))
= typeOf x : typeRepsList xs
instance TypeRepsList (HList '[]) where
typeRepsList _ = []
data GfoldlK c where
GfoldlK :: (forall d b . Data d => c (d -> b) -> d -> c b) -> GfoldlK c
instance (Data d, (c (d -> b), d) ~ x, c b ~ y) =>
ApplyAB (GfoldlK c) x y where
applyAB (GfoldlK f) (u,v) = f u v
data GunfoldK c where
GunfoldK :: (forall b r. Data b => c (b -> r) -> c r) -> GunfoldK c
instance (Data b, x ~ (t, c (b -> r)), y ~ c r) =>
ApplyAB (GunfoldK c) x y where
applyAB (GunfoldK f) (_, u) = f u