module Frames.Exploration (pipePreview, select, lenses, recToList,
pr, pr1) where
import Data.Char (isSpace, isUpper)
import Data.Proxy
import qualified Data.Vinyl as V
import Data.Vinyl.Functor (Identity(..))
import Frames.Rec
import Frames.RecF (AsVinyl(toVinyl), UnColumn)
import Frames.TypeLevel (AllAre)
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Pipes hiding (Proxy)
import qualified Pipes.Prelude as P
pipePreview :: (MonadIO m, Show b)
=> Producer a m () -> Int -> Pipe a b m () -> m ()
pipePreview src n f = runEffect $ src >-> f >-> P.take n >-> P.print
select :: (fs V.⊆ rs) => proxy fs -> Record rs -> Record fs
select _ = V.rcast
lenses :: (fs V.⊆ rs, Functor f)
=> proxy fs -> (Record fs -> f (Record fs)) -> Record rs -> f (Record rs)
lenses _ = V.rsubset
pr :: QuasiQuoter
pr = QuasiQuoter mkProxy undefined undefined undefined
where mkProxy s = let ts = map strip $ splitOn ',' s
cons = mapM (conT . mkName) ts
mkList = foldr (AppT . AppT PromotedConsT) PromotedNilT
in case ts of
[h@(t:_)]
| isUpper t -> [|Proxy::Proxy $(fmap head cons)|]
| otherwise -> [|Proxy::Proxy $(varT $ mkName h)|]
_ -> [|Proxy::Proxy $(fmap mkList cons)|]
pr1 :: QuasiQuoter
pr1 = QuasiQuoter mkProxy undefined undefined undefined
where mkProxy s = let sing x = AppT (AppT PromotedConsT x) PromotedNilT
in case s of
t:_
| isUpper t ->
[|Proxy::Proxy $(fmap sing (conT (mkName s)))|]
| otherwise ->
[|Proxy::Proxy $(fmap sing (varT $ mkName s))|]
_ -> error "Empty string passed to pr1"
recToList :: (AsVinyl rs, AllAre a (UnColumn rs)) => Record rs -> [a]
recToList = go . toVinyl
where go :: AllAre a rs => V.Rec Identity rs -> [a]
go V.RNil = []
go (Identity x V.:& xs) = x : go xs
splitOn :: Eq a => a -> [a] -> [[a]]
splitOn d = go
where go [] = []
go xs = let (h,t) = break (== d) xs
in case t of
[] -> [h]
(_:t') -> h : go t'
strip :: String -> String
strip = takeWhile (not . isSpace) . dropWhile isSpace