{-# LANGUAGE CPP, DataKinds, GeneralizedNewtypeDeriving, PatternSynonyms,
KindSignatures, ScopedTypeVariables, TypeFamilies,
TypeOperators #-}
module Frames.Col where
import Data.Vinyl (ElField(Field), getField)
import GHC.TypeLits
type (a :: Symbol) :-> b = '(a,b)
pattern Col :: KnownSymbol s => t -> ElField '(s,t)
pattern $bCol :: forall (s :: Symbol) t. KnownSymbol s => t -> ElField '(s, t)
$mCol :: forall {r} {s :: Symbol} {t}.
KnownSymbol s =>
ElField '(s, t) -> (t -> r) -> ((# #) -> r) -> r
Col x = Field x
getCol :: ElField '(s, t) -> t
getCol :: forall (s :: Symbol) t. ElField '(s, t) -> t
getCol = forall (s :: Symbol) t. ElField '(s, t) -> t
getField
newtype Col' s a = Col' (ElField (s :-> a))
col' :: KnownSymbol s => a -> Col' s a
col' :: forall (s :: Symbol) a. KnownSymbol s => a -> Col' s a
col' = forall (s :: Symbol) a. ElField (s :-> a) -> Col' s a
Col' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: (Symbol, *)). Snd t -> ElField t
Field
instance (KnownSymbol s, Show a) => Show (Col' s a) where
show :: Col' s a -> String
show (Col' ElField (s :-> a)
c) = String
"(" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ElField (s :-> a)
c forall a. [a] -> [a] -> [a]
++ String
")"
type family ReplaceColumns x ys where
ReplaceColumns x '[] = '[]
ReplaceColumns x (c :-> y ': ys) = c :-> x ': ReplaceColumns x ys