module Frames.CoRec where
import Data.Maybe(fromJust)
import Data.Proxy
import Data.Vinyl
import Data.Vinyl.Functor (Compose(..), (:.), Identity(..), Const(..))
import Data.Vinyl.TypeLevel (RIndex, RecAll)
import Frames.RecF (reifyDict)
import Frames.TypeLevel (LAll, HasInstances, AllHave)
#if __GLASGOW_HASKELL__ < 800
import GHC.Prim (Constraint)
#else
import Data.Kind (Constraint)
#endif
data CoRec :: (* -> *) -> [*] -> * where
Col :: RElem a ts (RIndex a ts) => !(f a) -> CoRec f ts
foldCoRec :: (forall a. RElem a ts (RIndex a ts) => f a -> b) -> CoRec f ts -> b
foldCoRec f (Col x) = f x
type Field = CoRec Identity
col :: (Show a, a ∈ ts) => a -> CoRec (Dict Show) ts
col = Col . Dict
instance Show (CoRec (Dict Show) ts) where
show (Col (Dict x)) = "Col "++show x
newtype Op b a = Op { runOp :: a -> b }
instance forall ts. (LAll Show ts, RecApplicative ts)
=> Show (CoRec Identity ts) where
show (Col (Identity x)) = "(Col "++show' x++")"
where shower :: Rec (Op String) ts
shower = reifyDict (Proxy::Proxy Show) (Op show)
show' = runOp (rget Proxy shower)
instance forall ts. (RecAll Maybe ts Eq, RecApplicative ts)
=> Eq (CoRec Identity ts) where
crA == crB = and . recordToList
$ zipRecsWith f (toRec crA) (corecToRec' crB)
where
f :: forall a. (Dict Eq :. Maybe) a -> Maybe a -> Const Bool a
f (Compose (Dict a)) b = Const $ a == b
toRec = reifyConstraint (Proxy :: Proxy Eq) . corecToRec'
zipRecsWith :: (forall a. f a -> g a -> h a) -> Rec f as -> Rec g as -> Rec h as
zipRecsWith _ RNil _ = RNil
zipRecsWith f (r :& rs) (s :& ss) = f r s :& zipRecsWith f rs ss
dictId :: Dict c a -> Identity a
dictId (Dict x) = Identity x
showDict :: Show a => a -> Dict Show a
showDict = Dict
corecToRec :: RecApplicative ts => CoRec f ts -> Rec (Maybe :. f) ts
corecToRec (Col x) = rput (Compose $ Just x) (rpure (Compose Nothing))
corecToRec' :: RecApplicative ts => CoRec Identity ts -> Rec Maybe ts
corecToRec' = rmap (fmap getIdentity . getCompose) . corecToRec
class FoldRec ss ts where
foldRec :: (CoRec f ss -> CoRec f ss -> CoRec f ss)
-> CoRec f ss
-> Rec f ts
-> CoRec f ss
instance FoldRec ss '[] where foldRec _ z _ = z
instance (t ∈ ss, FoldRec ss ts) => FoldRec ss (t ': ts) where
foldRec f z (x :& xs) = foldRec f (f z (Col x)) xs
corecMap :: (forall x. f x -> g x) -> CoRec f ts -> CoRec g ts
corecMap nt (Col x) = Col (nt x)
corecTraverse :: Functor h
=> (forall x. f x -> h (g x)) -> CoRec f ts -> h (CoRec g ts)
corecTraverse f (Col x) = fmap Col (f x)
foldRec1 :: FoldRec (t ': ts) ts
=> (CoRec f (t ': ts) -> CoRec f (t ': ts) -> CoRec f (t ': ts))
-> Rec f (t ': ts)
-> CoRec f (t ': ts)
foldRec1 f (x :& xs) = foldRec f (Col x) xs
firstField :: FoldRec ts ts
=> Rec (Maybe :. f) ts -> Maybe (CoRec f ts)
firstField RNil = Nothing
firstField v@(x :& _) = corecTraverse getCompose $ foldRec aux (Col x) v
where aux :: CoRec (Maybe :. f) (t ': ts)
-> CoRec (Maybe :. f) (t ': ts)
-> CoRec (Maybe :. f) (t ': ts)
aux c@(Col (Compose (Just _))) _ = c
aux _ c = c
lastField :: FoldRec ts ts
=> Rec (Maybe :. f) ts -> Maybe (CoRec f ts)
lastField RNil = Nothing
lastField v@(x :& _) = corecTraverse getCompose $ foldRec aux (Col x) v
where aux :: CoRec (Maybe :. f) (t ': ts)
-> CoRec (Maybe :. f) (t ': ts)
-> CoRec (Maybe :. f) (t ': ts)
aux _ c@(Col (Compose (Just _))) = c
aux c _ = c
onCoRec :: forall (cs :: [* -> Constraint]) f ts b.
(AllHave cs ts, Functor f, RecApplicative ts)
=> Proxy cs
-> (forall a. HasInstances a cs => a -> b)
-> CoRec f ts -> f b
onCoRec p f (Col x) = fmap meth x
where meth = runOp $
rget Proxy (reifyDicts p (Op f) :: Rec (Op b) ts)
onField :: forall cs ts b.
(AllHave cs ts, RecApplicative ts)
=> Proxy cs
-> (forall a. HasInstances a cs => a -> b)
-> Field ts -> b
onField p f x = getIdentity (onCoRec p f x)
reifyDicts :: forall cs f proxy ts. (AllHave cs ts, RecApplicative ts)
=> proxy cs -> (forall a. HasInstances a cs => f a) -> Rec f ts
reifyDicts _ f = go (rpure Nothing)
where go :: AllHave cs ts' => Rec Maybe ts' -> Rec f ts'
go RNil = RNil
go (_ :& xs) = f :& go xs
asA :: (t ∈ ts, RecApplicative ts) => proxy t -> CoRec Identity ts -> Maybe t
asA p c@(Col _) = rget p $ corecToRec' c
match :: RecApplicative (t ': ts)
=> CoRec Identity (t ': ts) -> Handlers (t ': ts) b -> b
match c hs = fromJust $ match' c hs
match' :: RecApplicative ts => CoRec Identity ts -> Handlers ts b -> Maybe b
match' c hs = match'' hs $ corecToRec' c
where
match'' :: Handlers ts b -> Rec Maybe ts -> Maybe b
match'' RNil RNil = Nothing
match'' (H f :& _) (Just x :& _) = Just $ f x
match'' (H _ :& fs) (Nothing :& c') = match'' fs c'
newtype Handler b a = H (a -> b)
type Handlers ts b = Rec (Handler b) ts