-- | functions to help making lists for consumption on the R side module RlangQQ.MakeRecord where import GHC.TypeLits -- prevents a panic lookupVers2 <
> with ghc 7.6. Fixed later probably from #7502 import Control.Monad.State import Control.Monad.Identity import Data.HList.CommonMain import HListExtras -- | convert a haskell list into a record with labels all of type \"\". The length -- of the list is decided by the (type of the) first argument which is a 'HNat' listToRecN :: ListToRecN __ (n :: HNat) x r => Proxy n -> [x] -> Record r listToRecN n xs = Record $ hMap NoLabel $ flip evalState xs $ hSequence $ hReplicate n comp where comp = do x : xs' <- get return () :: State [x] () put (xs' `asTypeOf` xs) return (x `asTypeOf` head xs) type ListToRecN __ (n :: HNat) x r = (HReplicate n (StateT [x] Identity x), HSequence (StateT [x] Identity) (HReplicateR n (StateT [x] Identity x)) __, HMapCxt NoLabel (HList __) (HList r) __ r) data NoLabel = NoLabel instance (Tagged "" a ~ la) => ApplyAB NoLabel a la where applyAB _ x = Tagged x