Frames-0.7.1: Data frames For working with tabular data files
Safe HaskellNone
LanguageHaskell2010

Frames

Description

User-friendly, type safe, runtime efficient tooling for working with tabular data deserialized from comma-separated values (CSV) files. The type of each row of data is inferred from data, which can then be streamed from disk, or worked with in memory.

Synopsis

Documentation

class Readable a where #

ByteString and Text reading using MonadPlus to handle parse failure. On error, fromText and fromBS will return mzero. You can use mplus to provide fallback defaults.

Minimal complete definition

fromText

Methods

fromText :: MonadPlus m => Text -> m a #

Reads data from a Text representation.

fromBS :: MonadPlus m => ByteString -> m a #

Reads data from a UTF8 encoded ByteString. The default implementation of this function simply decodes with UTF-8 and then calls the fromText function. If decoding fails, mzero will be returned. You can provide your own implementation if you need different behavior such as not decoding to UTF8.

Instances

Instances details
Readable Bool 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Bool #

fromBS :: MonadPlus m => ByteString -> m Bool #

Readable Double 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Double #

fromBS :: MonadPlus m => ByteString -> m Double #

Readable Float 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Float #

fromBS :: MonadPlus m => ByteString -> m Float #

Readable Int 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Int #

fromBS :: MonadPlus m => ByteString -> m Int #

Readable Int8 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Int8 #

fromBS :: MonadPlus m => ByteString -> m Int8 #

Readable Int16 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Int16 #

fromBS :: MonadPlus m => ByteString -> m Int16 #

Readable Int32 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Int32 #

fromBS :: MonadPlus m => ByteString -> m Int32 #

Readable Int64 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Int64 #

fromBS :: MonadPlus m => ByteString -> m Int64 #

Readable Integer 
Instance details

Defined in Data.Readable

Readable Word8 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Word8 #

fromBS :: MonadPlus m => ByteString -> m Word8 #

Readable Word16 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Word16 #

fromBS :: MonadPlus m => ByteString -> m Word16 #

Readable Word32 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Word32 #

fromBS :: MonadPlus m => ByteString -> m Word32 #

Readable Word64 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Word64 #

fromBS :: MonadPlus m => ByteString -> m Word64 #

Readable ByteString 
Instance details

Defined in Data.Readable

Readable Text 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Text #

fromBS :: MonadPlus m => ByteString -> m Text #

rcast :: forall k1 k2 (rs :: [k1]) (ss :: [k1]) (f :: k2 -> Type) record (is :: [Nat]). (RecSubset record rs ss is, RecSubsetFCtx record f) => record f ss -> record f rs #

Takes a larger record to a smaller one by forgetting fields. This is rcastC with the type arguments reordered for more convenient usage with TypeApplications.

rsubset :: forall k1 k2 (rs :: [k2]) (ss :: [k2]) (f :: k1 -> Type) g record (is :: [Nat]). (RecSubset record rs ss is, Functor g, RecSubsetFCtx record f) => (record f rs -> g (record f rs)) -> record f ss -> g (record f ss) #

A lens into a slice of the larger record. This is rsubsetC with the type arguments reordered for more convenient usage with TypeApplications.

(<+>) :: forall k (f :: k -> Type) (as :: [k]) (bs :: [k]). Rec f as -> Rec f bs -> Rec f (as ++ bs) infixr 5 #

A shorthand for rappend.

data Rec (a :: u -> Type) (b :: [u]) #

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Instances

Instances details
RecSubset (Rec :: (k -> Type) -> [k] -> Type) ('[] :: [k]) (ss :: [k]) ('[] :: [Nat]) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f '[] -> g (Rec f '[])) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f '[] #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f '[] -> Rec f ss -> Rec f ss #

(RElem r ss i, RSubset rs ss is) => RecSubset (Rec :: (k -> Type) -> [k] -> Type) (r ': rs :: [k]) (ss :: [k]) (i ': is) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecSubsetFCtx Rec f #

Methods

rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx Rec f) => (Rec f (r ': rs) -> g (Rec f (r ': rs))) -> Rec f ss -> g (Rec f ss) #

rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f ss -> Rec f (r ': rs) #

rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx Rec f => Rec f (r ': rs) -> Rec f ss -> Rec f ss #

RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (r ': rs :: [a]) (r' ': rs :: [a]) 'Z 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (r ': rs) -> g (Rec f (r' ': rs)) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (r ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (r ': rs) -> Rec f (r' ': rs) #

(RIndex r (s ': rs) ~ 'S i, RecElem (Rec :: (a -> Type) -> [a] -> Type) r r' rs rs' i) => RecElem (Rec :: (a -> Type) -> [a] -> Type) (r :: a) (r' :: a) (s ': rs :: [a]) (s ': rs' :: [a]) ('S i) 
Instance details

Defined in Data.Vinyl.Lens

Associated Types

type RecElemFCtx Rec f #

Methods

rlensC :: (Functor g, RecElemFCtx Rec f) => (f r -> g (f r')) -> Rec f (s ': rs) -> g (Rec f (s ': rs')) #

rgetC :: (RecElemFCtx Rec f, r ~ r') => Rec f (s ': rs) -> f r #

rputC :: RecElemFCtx Rec f => f r' -> Rec f (s ': rs) -> Rec f (s ': rs') #

(AllCols Grouping rs, Grouping (Record rs), Grouping (ElField (s :-> r)), Grouping r) => Grouping (Record ((s :-> r) ': rs)) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group (Record ((s :-> r) ': rs)) #

Grouping (Record ('[] :: [(Symbol, Type)])) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group (Record '[]) #

TestCoercion f => TestCoercion (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testCoercion :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (Coercion a b) #

TestEquality f => TestEquality (Rec f :: [u] -> Type) 
Instance details

Defined in Data.Vinyl.Core

Methods

testEquality :: forall (a :: k) (b :: k). Rec f a -> Rec f b -> Maybe (a :~: b) #

Eq (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f '[] -> Rec f '[] -> Bool #

(/=) :: Rec f '[] -> Rec f '[] -> Bool #

(Eq (f r), Eq (Rec f rs)) => Eq (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(==) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(/=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

Ord (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f '[] -> Rec f '[] -> Ordering #

(<) :: Rec f '[] -> Rec f '[] -> Bool #

(<=) :: Rec f '[] -> Rec f '[] -> Bool #

(>) :: Rec f '[] -> Rec f '[] -> Bool #

(>=) :: Rec f '[] -> Rec f '[] -> Bool #

max :: Rec f '[] -> Rec f '[] -> Rec f '[] #

min :: Rec f '[] -> Rec f '[] -> Rec f '[] #

(Ord (f r), Ord (Rec f rs)) => Ord (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

compare :: Rec f (r ': rs) -> Rec f (r ': rs) -> Ordering #

(<) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(<=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

(>=) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Bool #

max :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

min :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

(RMap rs, ReifyConstraint Show f rs, RecordToList rs) => Show (Rec f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

Instance details

Defined in Data.Vinyl.Core

Methods

showsPrec :: Int -> Rec f rs -> ShowS #

show :: Rec f rs -> String #

showList :: [Rec f rs] -> ShowS #

Generic (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f '[]) :: Type -> Type #

Methods

from :: Rec f '[] -> Rep (Rec f '[]) x #

to :: Rep (Rec f '[]) x -> Rec f '[] #

Generic (Rec f rs) => Generic (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Associated Types

type Rep (Rec f (r ': rs)) :: Type -> Type #

Methods

from :: Rec f (r ': rs) -> Rep (Rec f (r ': rs)) x #

to :: Rep (Rec f (r ': rs)) x -> Rec f (r ': rs) #

Semigroup (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f '[] -> Rec f '[] -> Rec f '[] #

sconcat :: NonEmpty (Rec f '[]) -> Rec f '[] #

stimes :: Integral b => b -> Rec f '[] -> Rec f '[] #

(Semigroup (f r), Semigroup (Rec f rs)) => Semigroup (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

(<>) :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

sconcat :: NonEmpty (Rec f (r ': rs)) -> Rec f (r ': rs) #

stimes :: Integral b => b -> Rec f (r ': rs) -> Rec f (r ': rs) #

Monoid (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f '[] #

mappend :: Rec f '[] -> Rec f '[] -> Rec f '[] #

mconcat :: [Rec f '[]] -> Rec f '[] #

(Monoid (f r), Monoid (Rec f rs)) => Monoid (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

mempty :: Rec f (r ': rs) #

mappend :: Rec f (r ': rs) -> Rec f (r ': rs) -> Rec f (r ': rs) #

mconcat :: [Rec f (r ': rs)] -> Rec f (r ': rs) #

Storable (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f '[] -> Int #

alignment :: Rec f '[] -> Int #

peekElemOff :: Ptr (Rec f '[]) -> Int -> IO (Rec f '[]) #

pokeElemOff :: Ptr (Rec f '[]) -> Int -> Rec f '[] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f '[]) #

pokeByteOff :: Ptr b -> Int -> Rec f '[] -> IO () #

peek :: Ptr (Rec f '[]) -> IO (Rec f '[]) #

poke :: Ptr (Rec f '[]) -> Rec f '[] -> IO () #

(Storable (f r), Storable (Rec f rs)) => Storable (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

Methods

sizeOf :: Rec f (r ': rs) -> Int #

alignment :: Rec f (r ': rs) -> Int #

peekElemOff :: Ptr (Rec f (r ': rs)) -> Int -> IO (Rec f (r ': rs)) #

pokeElemOff :: Ptr (Rec f (r ': rs)) -> Int -> Rec f (r ': rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec f (r ': rs)) #

pokeByteOff :: Ptr b -> Int -> Rec f (r ': rs) -> IO () #

peek :: Ptr (Rec f (r ': rs)) -> IO (Rec f (r ': rs)) #

poke :: Ptr (Rec f (r ': rs)) -> Rec f (r ': rs) -> IO () #

NFData (Rec f ('[] :: [u])) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

rnf :: Rec f '[] -> () #

ReifyConstraint NFData f xs => NFData (Rec f xs) 
Instance details

Defined in Data.Vinyl.Core

Methods

rnf :: Rec f xs -> () #

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecSubsetFCtx (Rec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) 
Instance details

Defined in Data.Vinyl.Lens

type RecElemFCtx (Rec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) = ()
type Rep (Rec f (r ': rs)) 
Instance details

Defined in Data.Vinyl.Core

type Rep (Rec f ('[] :: [u])) 
Instance details

Defined in Data.Vinyl.Core

data ElField (field :: (Symbol, Type)) #

A value with a phantom Symbol label. It is not a Haskell Functor, but it is used in many of the same places a Functor is used in vinyl.

Instances

Instances details
Eq t => Eq (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(==) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

(/=) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

(Floating t, KnownSymbol s) => Floating (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

pi :: ElField '(s, t) #

exp :: ElField '(s, t) -> ElField '(s, t) #

log :: ElField '(s, t) -> ElField '(s, t) #

sqrt :: ElField '(s, t) -> ElField '(s, t) #

(**) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

logBase :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

sin :: ElField '(s, t) -> ElField '(s, t) #

cos :: ElField '(s, t) -> ElField '(s, t) #

tan :: ElField '(s, t) -> ElField '(s, t) #

asin :: ElField '(s, t) -> ElField '(s, t) #

acos :: ElField '(s, t) -> ElField '(s, t) #

atan :: ElField '(s, t) -> ElField '(s, t) #

sinh :: ElField '(s, t) -> ElField '(s, t) #

cosh :: ElField '(s, t) -> ElField '(s, t) #

tanh :: ElField '(s, t) -> ElField '(s, t) #

asinh :: ElField '(s, t) -> ElField '(s, t) #

acosh :: ElField '(s, t) -> ElField '(s, t) #

atanh :: ElField '(s, t) -> ElField '(s, t) #

log1p :: ElField '(s, t) -> ElField '(s, t) #

expm1 :: ElField '(s, t) -> ElField '(s, t) #

log1pexp :: ElField '(s, t) -> ElField '(s, t) #

log1mexp :: ElField '(s, t) -> ElField '(s, t) #

(Fractional t, KnownSymbol s) => Fractional (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(/) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

recip :: ElField '(s, t) -> ElField '(s, t) #

fromRational :: Rational -> ElField '(s, t) #

(Num t, KnownSymbol s) => Num (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(+) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

(-) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

(*) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

negate :: ElField '(s, t) -> ElField '(s, t) #

abs :: ElField '(s, t) -> ElField '(s, t) #

signum :: ElField '(s, t) -> ElField '(s, t) #

fromInteger :: Integer -> ElField '(s, t) #

Ord t => Ord (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

compare :: ElField '(s, t) -> ElField '(s, t) -> Ordering #

(<) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

(<=) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

(>) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

(>=) :: ElField '(s, t) -> ElField '(s, t) -> Bool #

max :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

min :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

(Real t, KnownSymbol s) => Real (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

toRational :: ElField '(s, t) -> Rational #

(RealFrac t, KnownSymbol s) => RealFrac (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

properFraction :: Integral b => ElField '(s, t) -> (b, ElField '(s, t)) #

truncate :: Integral b => ElField '(s, t) -> b #

round :: Integral b => ElField '(s, t) -> b #

ceiling :: Integral b => ElField '(s, t) -> b #

floor :: Integral b => ElField '(s, t) -> b #

(Show t, KnownSymbol s) => Show (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

showsPrec :: Int -> ElField '(s, t) -> ShowS #

show :: ElField '(s, t) -> String #

showList :: [ElField '(s, t)] -> ShowS #

KnownSymbol s => Generic (ElField '(s, a)) 
Instance details

Defined in Data.Vinyl.Functor

Associated Types

type Rep (ElField '(s, a)) :: Type -> Type #

Methods

from :: ElField '(s, a) -> Rep (ElField '(s, a)) x #

to :: Rep (ElField '(s, a)) x -> ElField '(s, a) #

Semigroup t => Semigroup (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

(<>) :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

sconcat :: NonEmpty (ElField '(s, t)) -> ElField '(s, t) #

stimes :: Integral b => b -> ElField '(s, t) -> ElField '(s, t) #

(KnownSymbol s, Monoid t) => Monoid (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

mempty :: ElField '(s, t) #

mappend :: ElField '(s, t) -> ElField '(s, t) -> ElField '(s, t) #

mconcat :: [ElField '(s, t)] -> ElField '(s, t) #

(KnownSymbol s, Storable t) => Storable (ElField '(s, t)) 
Instance details

Defined in Data.Vinyl.Functor

Methods

sizeOf :: ElField '(s, t) -> Int #

alignment :: ElField '(s, t) -> Int #

peekElemOff :: Ptr (ElField '(s, t)) -> Int -> IO (ElField '(s, t)) #

pokeElemOff :: Ptr (ElField '(s, t)) -> Int -> ElField '(s, t) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (ElField '(s, t)) #

pokeByteOff :: Ptr b -> Int -> ElField '(s, t) -> IO () #

peek :: Ptr (ElField '(s, t)) -> IO (ElField '(s, t)) #

poke :: Ptr (ElField '(s, t)) -> ElField '(s, t) -> IO () #

NFData a => NFData (ElField (s :-> a)) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

rnf :: ElField (s :-> a) -> () #

Grouping a => Grouping (ElField (s :-> a)) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group (ElField (s :-> a)) #

(AllCols Grouping rs, Grouping (Record rs), Grouping (ElField (s :-> r)), Grouping r) => Grouping (Record ((s :-> r) ': rs)) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group (Record ((s :-> r) ': rs)) #

Grouping (Record ('[] :: [(Symbol, Type)])) Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group (Record '[]) #

KnownSymbol s => IsoHKD ElField ('(s, a) :: (Symbol, Type))

Work with values of type ElField '(s,a) as if they were of type a.

Instance details

Defined in Data.Vinyl.XRec

Associated Types

type HKD ElField '(s, a) #

Methods

unHKD :: HKD ElField '(s, a) -> ElField '(s, a) #

toHKD :: ElField '(s, a) -> HKD ElField '(s, a) #

(i ~ RIndex t ts, NatToInt i, FieldOffset ElField ts t, Storable (Rec ElField ts), AllConstrained (FieldOffset ElField ts) ts) => RecElem (SRec2 ElField) (t :: (Symbol, Type)) (t :: (Symbol, Type)) (ts :: [(Symbol, Type)]) (ts :: [(Symbol, Type)]) i

Field accessors for SRec2 specialized to ElField as the functor.

Instance details

Defined in Data.Vinyl.SRec

Associated Types

type RecElemFCtx (SRec2 ElField) f #

Methods

rlensC :: (Functor g, RecElemFCtx (SRec2 ElField) f) => (f t -> g (f t)) -> SRec2 ElField f ts -> g (SRec2 ElField f ts) #

rgetC :: (RecElemFCtx (SRec2 ElField) f, t ~ t) => SRec2 ElField f ts -> f t #

rputC :: RecElemFCtx (SRec2 ElField) f => f t -> SRec2 ElField f ts -> SRec2 ElField f ts #

(is ~ RImage rs ss, RecSubset (Rec :: ((Symbol, Type) -> Type) -> [(Symbol, Type)] -> Type) rs ss is, Storable (Rec ElField rs), Storable (Rec ElField ss), RPureConstrained (FieldOffset ElField ss) rs, RPureConstrained (FieldOffset ElField rs) rs, RFoldMap rs, RMap rs, RApply rs) => RecSubset (SRec2 ElField) (rs :: [(Symbol, Type)]) (ss :: [(Symbol, Type)]) is 
Instance details

Defined in Data.Vinyl.SRec

Associated Types

type RecSubsetFCtx (SRec2 ElField) f #

Methods

rsubsetC :: forall g (f :: k -> Type). (Functor g, RecSubsetFCtx (SRec2 ElField) f) => (SRec2 ElField f rs -> g (SRec2 ElField f rs)) -> SRec2 ElField f ss -> g (SRec2 ElField f ss) #

rcastC :: forall (f :: k -> Type). RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f ss -> SRec2 ElField f rs #

rreplaceC :: forall (f :: k -> Type). RecSubsetFCtx (SRec2 ElField) f => SRec2 ElField f rs -> SRec2 ElField f ss -> SRec2 ElField f ss #

type Rep (ElField '(s, a)) 
Instance details

Defined in Data.Vinyl.Functor

type Rep (ElField '(s, a)) = C1 ('MetaCons s 'PrefixI 'False) (Rec0 a)
type HKD ElField ('(s, a) :: (Symbol, Type)) 
Instance details

Defined in Data.Vinyl.XRec

type HKD ElField ('(s, a) :: (Symbol, Type)) = a
type RecElemFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) 
Instance details

Defined in Data.Vinyl.SRec

type RecElemFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) = f ~ ElField
type RecSubsetFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) 
Instance details

Defined in Data.Vinyl.SRec

type RecSubsetFCtx (SRec2 ElField) (f :: (Symbol, Type) -> Type) = f ~ ElField

onField :: forall c (ts :: [Type]) b. RPureConstrained c ts => (forall a. (a ts, c a) => a -> b) -> Field ts -> b #

Apply a type class method to a Field. Intended for use with TypeApplications, e.g. onField @Show show r.

onCoRec :: forall k1 k2 c f (ts :: [k1]) (b :: k2) g. RPureConstrained c ts => (forall (a :: k1). (a ts, c a) => f a -> g b) -> CoRec f ts -> g b #

Apply methods from a type class to a CoRec. Intended for use with TypeApplications, e.g. onCoRec @Show show r

type Field = CoRec Identity #

A Field of a Rec Identity is a CoRec Identity.

rfield :: forall f a b (s :: Symbol). Functor f => (a -> f b) -> ElField '(s, a) -> f (ElField '(s, b)) #

Lens for an ElField's data payload.

type (:.) (f :: l -> Type) (g :: k -> l) = Compose f g infixr 9 #

type family RDelete (r :: a) (rs :: [a]) :: [a] where ... #

Remove the first occurence of a type from a type-level list.

Equations

RDelete (r :: a) (r ': rs :: [a]) = rs 
RDelete (r :: a) (s ': rs :: [a]) = s ': RDelete r rs 

type family RecAll (f :: u -> Type) (rs :: [u]) (c :: Type -> Constraint) where ... #

A constraint-former which applies to every field in a record.

Equations

RecAll (f :: u -> Type) ('[] :: [u]) c = () 
RecAll (f :: u -> Type) (r ': rs :: [u]) c = (c (f r), RecAll f rs c) 

type family AllConstrained (c :: u -> Constraint) (ts :: [u]) where ... #

Constraint that all types in a type-level list satisfy a constraint.

Equations

AllConstrained (c :: u -> Constraint) ('[] :: [u]) = () 
AllConstrained (c :: u -> Constraint) (t ': ts :: [u]) = (c t, AllConstrained c ts) 

class AllSatisfied (cs :: k) (t :: k1) #

Constraint that each Constraint in a type-level list is satisfied by a particular type.

Instances

Instances details
AllSatisfied ('[] :: [k2]) (t :: k1) 
Instance details

Defined in Data.Vinyl.TypeLevel

(c t, AllSatisfied cs t) => AllSatisfied (c ': cs :: [k -> Constraint]) (t :: k) 
Instance details

Defined in Data.Vinyl.TypeLevel

type family AllAllSat (cs :: k) (ts :: [k1]) where ... #

Constraint that all types in a type-level list satisfy each constraint from a list of constraints.

AllAllSat cs ts should be equivalent to AllConstrained (AllSatisfied cs) ts if partial application of type families were legal.

Equations

AllAllSat (cs :: k1) ('[] :: [k2]) = () 
AllAllSat (cs :: k1) (t ': ts :: [k2]) = (AllSatisfied cs t, AllAllSat cs ts) 

type (:->) (a :: Symbol) b = '(a, b) Source #

pattern Col :: KnownSymbol s => t -> ElField '(s, t) Source #

readTableMaybe :: (MonadSafe m, ReadRec rs, RMap rs) => FilePath -> Producer (Rec (Maybe :. ElField) rs) m () Source #

Produce rows where any given entry can fail to parse.

pipeTableMaybe :: (Monad m, ReadRec rs, RMap rs) => Pipe [Text] (Rec (Maybe :. ElField) rs) m () Source #

Stream lines of CSV data into rows of ’Rec’ values where any given entry can fail to parse.

readTableOpt :: (MonadSafe m, ReadRec rs, RMap rs) => ParserOptions -> FilePath -> Producer (Record rs) m () Source #

Returns a producer of rows for which each column was successfully parsed.

readTable :: (MonadSafe m, ReadRec rs, RMap rs) => FilePath -> Producer (Record rs) m () Source #

Returns a producer of rows for which each column was successfully parsed.

pipeTable :: (ReadRec rs, RMap rs, Monad m) => Pipe [Text] (Record rs) m () Source #

Pipe lines of CSV text into rows for which each column was successfully parsed.

inCoreAoS :: (PrimMonad m, MonadIO m, MonadMask m, RecVec rs) => Producer (Record rs) (SafeT m) () -> m (FrameRec rs) Source #

Stream a finite sequence of rows into an efficient in-memory representation for further manipulation. Each column of the input table will be stored optimally based on its type, making use of the resulting generators a matter of indexing into a densely packed representation. Returns a Frame that provides a function to index into the table.

inCoreAoS' :: (PrimMonad m, MonadIO m, MonadMask m, RecVec rs) => (Rec ((->) Int :. ElField) rs -> Rec ((->) Int :. ElField) ss) -> Producer (Record rs) (SafeT m) () -> m (FrameRec ss) Source #

Like inCoreAoS, but applies the provided function to the record of columns before building the Frame.

inCore :: (PrimMonad m, MonadIO m, MonadMask m, RecVec rs, Monad n) => Producer (Record rs) (SafeT m) () -> m (Producer (Record rs) n ()) Source #

Stream a finite sequence of rows into an efficient in-memory representation for further manipulation. Each column of the input table will be stored optimally based on its type, making use of the resulting generator a matter of indexing into a densely packed representation.

inCoreSoA :: (PrimMonad m, MonadIO m, MonadMask m, RecVec rs) => Producer (Record rs) (SafeT m) () -> m (Int, Rec ((->) Int :. ElField) rs) Source #

Stream a finite sequence of rows into an efficient in-memory representation for further manipulation. Each column of the input table will be stored optimally based on its type, making use of the resulting generators a matter of indexing into a densely packed representation. Returns the number of rows and a record of column indexing functions. See toAoS to convert the result to a Frame which provides an easier-to-use function that indexes into the table in a row-major fashion.

toAoS :: Int -> Rec ((->) Int :. ElField) rs -> FrameRec rs Source #

Convert a structure-of-arrays to an array-of-structures. This can simplify usage of an in-memory representation.

toFrame :: (Foldable f, RecVec rs) => f (Record rs) -> Frame (Record rs) Source #

Build a Frame from a collection of Records using efficient column-based storage.

filterFrame :: RecVec rs => (Record rs -> Bool) -> FrameRec rs -> FrameRec rs Source #

Keep only those rows of a FrameRec that satisfy a predicate.

meltRow :: (vs ts, ss ts, vs ~ RDeleteAll ss ts, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => proxy ss -> Record ts -> [Record (ss ++ '["value" :-> CoRec ElField vs])] Source #

Like melt in the reshape2 package for the R language. It stacks multiple columns into a single column over multiple rows. Takes a specification of the id columns that remain unchanged. The remaining columns will be stacked.

Suppose we have a record, r :: Record [Name,Age,Weight]. If we apply melt [pr1|Name|] r, we get two values with type Record [Name, "value" :-> CoRec Identity [Age,Weight]]. The first will contain Age in the value column, and the second will contain Weight in the value column.

melt :: forall vs ts ss proxy. (vs ts, ss ts, vs ~ RDeleteAll ss ts, HasLength vs, Disjoint ss ts ~ 'True, ts (vs ++ ss), ColumnHeaders vs, RowToColumn vs vs) => proxy ss -> FrameRec ts -> FrameRec (ss ++ '["value" :-> CoRec ElField vs]) Source #

Applies meltRow to each row of a FrameRec.

type family RecordColumns t where ... Source #

Equations

RecordColumns (Record ts) = ts 

type Record = FieldRec Source #

A record with unadorned values. This is Vinyl's Rec ElField. We give this type a name as it is used pervasively for records in Frames.

(&:) :: KnownSymbol s => a -> Record rs -> Record ((s :-> a) ': rs) infixr 5 Source #

A cons function for building Record values.

recUncons :: Record ((s :-> a) ': rs) -> (a, Record rs) Source #

Separate the first element of a Record from the rest of the row.

recMaybe :: Rec (Maybe :. ElField) cs -> Maybe (Record cs) Source #

Undistribute Maybe from a Rec Maybe. This is just a specific usage of rtraverse, but it is quite common.

showFields :: (RecMapMethod Show ElField ts, RecordToList ts) => Record ts -> [String] Source #

Show each field of a Record without its column name.

rgetField :: forall t s a rs. (t ~ '(s, a), t rs) => Record rs -> a Source #

Get the value of a field of a Record. This is intended for use with TypeApplications, as compared to rgetv that is intended for use with OverloadedLabels.

rputField :: forall t s a rs. (t ~ '(s, a), t rs, KnownSymbol s) => a -> Record rs -> Record rs Source #

Replace the value of a field of a Record. This is intended for use with TypeApplications, as compared to rputf that is intended for use with OverloadedLabels.

declareColumn :: Text -> Name -> DecsQ Source #

Splice for manually declaring a column of a given type. For example, declareColumn "x2" ''Double will declare a type synonym type X2 = "x2" :-> Double and a lens x2.

tableTypes :: String -> FilePath -> DecsQ Source #

Like tableType, but additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens @Foo, and foo' = rlens' @Foo.

tableTypes' :: forall a c. (c ~ CoRec ColInfo a, ColumnTypeable c, Monoid c) => RowGen a -> DecsQ Source #

Generate a type for a row of a table. This will be something like Record ["x" :-> a, "y" :-> b, "z" :-> c]. Additionally generates a type synonym for each column, and a proxy value of that type. If the CSV file has column names "foo", "bar", and "baz", then this will declare type Foo = "foo" :-> Int, for example, foo = rlens @Foo, and foo' = rlens' @Foo.

runSafeP :: forall (m :: Type -> Type) r. (MonadMask m, MonadIO m) => Effect (SafeT m) r -> Effect' m r #

Run SafeT in the base monad, executing all unreleased finalizers at the end of the computation

Use runSafeP to safely flush all unreleased finalizers and ensure prompt finalization without exiting the Proxy monad.

runSafeT :: (MonadMask m, MonadIO m) => SafeT m r -> m r #

Run the SafeT monad transformer, executing all unreleased finalizers at the end of the computation

data SafeT (m :: Type -> Type) r #

SafeT is a monad transformer that extends the base monad with the ability to register and release finalizers.

All unreleased finalizers are called at the end of the SafeT block, even in the event of exceptions.

Instances

Instances details
MonadTrans SafeT 
Instance details

Defined in Pipes.Safe

Methods

lift :: Monad m => m a -> SafeT m a #

MonadBase b m => MonadBase b (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

liftBase :: b α -> SafeT m α #

MonadBaseControl b m => MonadBaseControl b (SafeT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type StM (SafeT m) a #

Methods

liftBaseWith :: (RunInBase (SafeT m) b -> b a) -> SafeT m a #

restoreM :: StM (SafeT m) a -> SafeT m a #

MonadWriter w m => MonadWriter w (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

writer :: (a, w) -> SafeT m a #

tell :: w -> SafeT m () #

listen :: SafeT m a -> SafeT m (a, w) #

pass :: SafeT m (a, w -> w) -> SafeT m a #

MonadState s m => MonadState s (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

get :: SafeT m s #

put :: s -> SafeT m () #

state :: (s -> (a, s)) -> SafeT m a #

MonadError e m => MonadError e (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

throwError :: e -> SafeT m a #

catchError :: SafeT m a -> (e -> SafeT m a) -> SafeT m a #

Monad m => Monad (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

(>>=) :: SafeT m a -> (a -> SafeT m b) -> SafeT m b #

(>>) :: SafeT m a -> SafeT m b -> SafeT m b #

return :: a -> SafeT m a #

Functor m => Functor (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

fmap :: (a -> b) -> SafeT m a -> SafeT m b #

(<$) :: a -> SafeT m b -> SafeT m a #

MonadFix m => MonadFix (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

mfix :: (a -> SafeT m a) -> SafeT m a #

MonadFail m => MonadFail (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

fail :: String -> SafeT m a #

Applicative m => Applicative (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

pure :: a -> SafeT m a #

(<*>) :: SafeT m (a -> b) -> SafeT m a -> SafeT m b #

liftA2 :: (a -> b -> c) -> SafeT m a -> SafeT m b -> SafeT m c #

(*>) :: SafeT m a -> SafeT m b -> SafeT m b #

(<*) :: SafeT m a -> SafeT m b -> SafeT m a #

MonadIO m => MonadIO (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

liftIO :: IO a -> SafeT m a #

Alternative m => Alternative (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

empty :: SafeT m a #

(<|>) :: SafeT m a -> SafeT m a -> SafeT m a #

some :: SafeT m a -> SafeT m [a] #

many :: SafeT m a -> SafeT m [a] #

MonadPlus m => MonadPlus (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

mzero :: SafeT m a #

mplus :: SafeT m a -> SafeT m a -> SafeT m a #

MonadThrow m => MonadThrow (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

throwM :: Exception e => e -> SafeT m a #

MonadCatch m => MonadCatch (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

catch :: Exception e => SafeT m a -> (e -> SafeT m a) -> SafeT m a #

MonadMask m => MonadMask (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

mask :: ((forall a. SafeT m a -> SafeT m a) -> SafeT m b) -> SafeT m b #

uninterruptibleMask :: ((forall a. SafeT m a -> SafeT m a) -> SafeT m b) -> SafeT m b #

generalBracket :: SafeT m a -> (a -> ExitCase b -> SafeT m c) -> (a -> SafeT m b) -> SafeT m (b, c) #

MonadCont m => MonadCont (SafeT m) 
Instance details

Defined in Pipes.Safe

Methods

callCC :: ((a -> SafeT m b) -> SafeT m a) -> SafeT m a #

(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (SafeT m) :: Type -> Type #

Methods

liftBase :: Base (SafeT m) r -> SafeT m r #

register :: Base (SafeT m) () -> SafeT m ReleaseKey #

release :: ReleaseKey -> SafeT m () #

PrimMonad m => PrimMonad (SafeT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type PrimState (SafeT m) #

Methods

primitive :: (State# (PrimState (SafeT m)) -> (# State# (PrimState (SafeT m)), a #)) -> SafeT m a #

type Base (SafeT m) 
Instance details

Defined in Pipes.Safe

type Base (SafeT m) = m
type PrimState (SafeT m) 
Instance details

Defined in Pipes.Safe

type StM (SafeT m) a 
Instance details

Defined in Pipes.Safe

type StM (SafeT m) a = StM m a

class (MonadCatch m, MonadMask m, MonadIO m, MonadIO (Base m)) => MonadSafe (m :: Type -> Type) #

MonadSafe lets you register and release finalizers that execute in a Base monad

Minimal complete definition

liftBase, register, release

Instances

Instances details
MonadSafe m => MonadSafe (CatchT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (CatchT m) :: Type -> Type #

Methods

liftBase :: Base (CatchT m) r -> CatchT m r #

register :: Base (CatchT m) () -> CatchT m ReleaseKey #

release :: ReleaseKey -> CatchT m () #

(MonadIO m, MonadCatch m, MonadMask m) => MonadSafe (SafeT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (SafeT m) :: Type -> Type #

Methods

liftBase :: Base (SafeT m) r -> SafeT m r #

register :: Base (SafeT m) () -> SafeT m ReleaseKey #

release :: ReleaseKey -> SafeT m () #

MonadSafe m => MonadSafe (IdentityT m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (IdentityT m) :: Type -> Type #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (WriterT w m) :: Type -> Type #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey #

release :: ReleaseKey -> WriterT w m () #

MonadSafe m => MonadSafe (StateT s m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (StateT s m) :: Type -> Type #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r #

register :: Base (StateT s m) () -> StateT s m ReleaseKey #

release :: ReleaseKey -> StateT s m () #

MonadSafe m => MonadSafe (ReaderT i m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (ReaderT i m) :: Type -> Type #

Methods

liftBase :: Base (ReaderT i m) r -> ReaderT i m r #

register :: Base (ReaderT i m) () -> ReaderT i m ReleaseKey #

release :: ReleaseKey -> ReaderT i m () #

MonadSafe m => MonadSafe (StateT s m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (StateT s m) :: Type -> Type #

Methods

liftBase :: Base (StateT s m) r -> StateT s m r #

register :: Base (StateT s m) () -> StateT s m ReleaseKey #

release :: ReleaseKey -> StateT s m () #

(MonadSafe m, Monoid w) => MonadSafe (WriterT w m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (WriterT w m) :: Type -> Type #

Methods

liftBase :: Base (WriterT w m) r -> WriterT w m r #

register :: Base (WriterT w m) () -> WriterT w m ReleaseKey #

release :: ReleaseKey -> WriterT w m () #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (RWST i w s m) :: Type -> Type #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey #

release :: ReleaseKey -> RWST i w s m () #

(MonadSafe m, Monoid w) => MonadSafe (RWST i w s m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (RWST i w s m) :: Type -> Type #

Methods

liftBase :: Base (RWST i w s m) r -> RWST i w s m r #

register :: Base (RWST i w s m) () -> RWST i w s m ReleaseKey #

release :: ReleaseKey -> RWST i w s m () #

MonadSafe m => MonadSafe (Proxy a' a b' b m) 
Instance details

Defined in Pipes.Safe

Associated Types

type Base (Proxy a' a b' b m) :: Type -> Type #

Methods

liftBase :: Base (Proxy a' a b' b m) r -> Proxy a' a b' b m r #

register :: Base (Proxy a' a b' b m) () -> Proxy a' a b' b m ReleaseKey #

release :: ReleaseKey -> Proxy a' a b' b m () #

runSafeEffect :: (MonadIO m, MonadMask m) => Effect (SafeT m) r -> m r Source #

Run a self-contained ’Pipes.Effect’ and execute the finalizers associated with the ’SafeT’ transformer.

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Grouping Text Source # 
Instance details

Defined in Frames.ExtraInstances

Methods

grouping :: Group Text #

Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

Readable Text 
Instance details

Defined in Data.Readable

Methods

fromText :: MonadPlus m => Text -> m Text #

fromBS :: MonadPlus m => ByteString -> m Text #

Parseable Text Source # 
Instance details

Defined in Frames.ColumnTypeable

ShowCSV Text Source # 
Instance details

Defined in Frames.ShowCSV

Methods

showCSV :: Text -> Text Source #

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char
type VectorFor Text Source # 
Instance details

Defined in Frames.InCore