composite-base-0.2.0.0: Shared utilities for composite-* packages.

Safe HaskellNone
LanguageHaskell2010

Composite.Record

Synopsis

Documentation

data Rec u a b :: forall u. (u -> *) -> [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

TestCoercion u f => TestCoercion [u] (Rec u f) 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec u f) a b) #

TestEquality u f => TestEquality [u] (Rec u f) 

Methods

testEquality :: f a -> f b -> Maybe ((Rec u f :~: a) b) #

Eq (Rec u f ([] u)) 

Methods

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

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

(Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) 

Methods

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

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

Ord (Rec u f ([] u)) 

Methods

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

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

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

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

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

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

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

(Ord (f r), Ord (Rec a f rs)) => Ord (Rec a f ((:) a r rs)) 

Methods

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

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

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

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

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

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

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

RecAll u f rs Show => Show (Rec u f rs)

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

Methods

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

show :: Rec u f rs -> String #

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

Monoid (Rec u f ([] u)) 

Methods

mempty :: Rec u f [u] #

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

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

(Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) 

Methods

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

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

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

Storable (Rec u f ([] u)) 

Methods

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

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

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

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

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

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

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

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

(Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) 

Methods

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

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

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

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

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

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

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

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

type Record = Rec * Identity #

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

newtype Identity a :: * -> * #

This is identical to the Identity from Data.Functor.Identity in "base" except for its Show instance.

Constructors

Identity a 

Instances

Monad Identity 

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity 

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

Applicative Identity 

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity 

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity 

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

Eq a => Eq (Identity a) 

Methods

(==) :: Identity a -> Identity a -> Bool #

(/=) :: Identity a -> Identity a -> Bool #

Ord a => Ord (Identity a) 

Methods

compare :: Identity a -> Identity a -> Ordering #

(<) :: Identity a -> Identity a -> Bool #

(<=) :: Identity a -> Identity a -> Bool #

(>) :: Identity a -> Identity a -> Bool #

(>=) :: Identity a -> Identity a -> Bool #

max :: Identity a -> Identity a -> Identity a #

min :: Identity a -> Identity a -> Identity a #

Show a => Show (Identity a) 

Methods

showsPrec :: Int -> Identity a -> ShowS #

show :: Identity a -> String #

showList :: [Identity a] -> ShowS #

Storable a => Storable (Identity a) 

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

peekElemOff :: Ptr (Identity a) -> Int -> IO (Identity a) #

pokeElemOff :: Ptr (Identity a) -> Int -> Identity a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Identity a) #

pokeByteOff :: Ptr b -> Int -> Identity a -> IO () #

peek :: Ptr (Identity a) -> IO (Identity a) #

poke :: Ptr (Identity a) -> Identity a -> IO () #

pattern (:*:) :: forall a rs s. a -> Rec * Identity rs -> Rec * Identity ((:) * ((:->) s a) rs) infixr 5 Source #

Bidirectional pattern matching the first field of a record using :-> values and the Identity functor.

This pattern is bidirectional meaning you can use it either as a pattern or a constructor, e.g.

  let rec = 123 :*: Just "foo" :*: Nil
      foo :*: bar :*: Nil = rec

Mnemonic: * for products.

pattern (:^:) :: forall f a rs s. Functor f => f a -> Rec * f rs -> Rec * f ((:) * ((:->) s a) rs) infixr 5 Source #

Bidirectional pattern matching the first field of a record using :-> values and any functor.

This pattern is bidirectional meaning you can use it either as a pattern or a constructor, e.g.

  let rec = Just 123 :^: Just "foo" :^: Nil
      Just foo :^: Just bar :^: Nil = rec

Mnemonic: ^ for products (record) of products (functor).

pattern Nil :: forall u f. Rec u f ([] u) Source #

Pattern synonym equivalent to the empty record RNil.

This pattern is bidirectional meaning you can use it either a pattern or as a constructor, e.g.

  let Nil = Nil :: Record '[]

is valid.

pattern Val :: forall a s. a -> Identity ((:->) s a) Source #

Bidirectional pattern unwrapping Identity (s :-> a) to a.

newtype s :-> a :: Symbol -> * -> * #

A column's type includes a textual name and the data type of each element.

Constructors

Col 

Fields

Instances

Eq a => Eq ((:->) s a) 

Methods

(==) :: (s :-> a) -> (s :-> a) -> Bool #

(/=) :: (s :-> a) -> (s :-> a) -> Bool #

Floating a => Floating ((:->) s a) 

Methods

pi :: s :-> a #

exp :: (s :-> a) -> s :-> a #

log :: (s :-> a) -> s :-> a #

sqrt :: (s :-> a) -> s :-> a #

(**) :: (s :-> a) -> (s :-> a) -> s :-> a #

logBase :: (s :-> a) -> (s :-> a) -> s :-> a #

sin :: (s :-> a) -> s :-> a #

cos :: (s :-> a) -> s :-> a #

tan :: (s :-> a) -> s :-> a #

asin :: (s :-> a) -> s :-> a #

acos :: (s :-> a) -> s :-> a #

atan :: (s :-> a) -> s :-> a #

sinh :: (s :-> a) -> s :-> a #

cosh :: (s :-> a) -> s :-> a #

tanh :: (s :-> a) -> s :-> a #

asinh :: (s :-> a) -> s :-> a #

acosh :: (s :-> a) -> s :-> a #

atanh :: (s :-> a) -> s :-> a #

log1p :: (s :-> a) -> s :-> a #

expm1 :: (s :-> a) -> s :-> a #

log1pexp :: (s :-> a) -> s :-> a #

log1mexp :: (s :-> a) -> s :-> a #

Fractional a => Fractional ((:->) s a) 

Methods

(/) :: (s :-> a) -> (s :-> a) -> s :-> a #

recip :: (s :-> a) -> s :-> a #

fromRational :: Rational -> s :-> a #

Num a => Num ((:->) s a) 

Methods

(+) :: (s :-> a) -> (s :-> a) -> s :-> a #

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

(*) :: (s :-> a) -> (s :-> a) -> s :-> a #

negate :: (s :-> a) -> s :-> a #

abs :: (s :-> a) -> s :-> a #

signum :: (s :-> a) -> s :-> a #

fromInteger :: Integer -> s :-> a #

Ord a => Ord ((:->) s a) 

Methods

compare :: (s :-> a) -> (s :-> a) -> Ordering #

(<) :: (s :-> a) -> (s :-> a) -> Bool #

(<=) :: (s :-> a) -> (s :-> a) -> Bool #

(>) :: (s :-> a) -> (s :-> a) -> Bool #

(>=) :: (s :-> a) -> (s :-> a) -> Bool #

max :: (s :-> a) -> (s :-> a) -> s :-> a #

min :: (s :-> a) -> (s :-> a) -> s :-> a #

Real a => Real ((:->) s a) 

Methods

toRational :: (s :-> a) -> Rational #

RealFloat a => RealFloat ((:->) s a) 

Methods

floatRadix :: (s :-> a) -> Integer #

floatDigits :: (s :-> a) -> Int #

floatRange :: (s :-> a) -> (Int, Int) #

decodeFloat :: (s :-> a) -> (Integer, Int) #

encodeFloat :: Integer -> Int -> s :-> a #

exponent :: (s :-> a) -> Int #

significand :: (s :-> a) -> s :-> a #

scaleFloat :: Int -> (s :-> a) -> s :-> a #

isNaN :: (s :-> a) -> Bool #

isInfinite :: (s :-> a) -> Bool #

isDenormalized :: (s :-> a) -> Bool #

isNegativeZero :: (s :-> a) -> Bool #

isIEEE :: (s :-> a) -> Bool #

atan2 :: (s :-> a) -> (s :-> a) -> s :-> a #

RealFrac a => RealFrac ((:->) s a) 

Methods

properFraction :: Integral b => (s :-> a) -> (b, s :-> a) #

truncate :: Integral b => (s :-> a) -> b #

round :: Integral b => (s :-> a) -> b #

ceiling :: Integral b => (s :-> a) -> b #

floor :: Integral b => (s :-> a) -> b #

(KnownSymbol s, Show a) => Show ((:->) s a) 

Methods

showsPrec :: Int -> (s :-> a) -> ShowS #

show :: (s :-> a) -> String #

showList :: [s :-> a] -> ShowS #

Monoid a => Monoid ((:->) s a) 

Methods

mempty :: s :-> a #

mappend :: (s :-> a) -> (s :-> a) -> s :-> a #

mconcat :: [s :-> a] -> s :-> a #

KnownSymbol s => NamedField ((:->) s a) Source # 

Methods

fieldName :: proxy (s :-> a) -> Text Source #

(MVector (VectorMFor a) a, Vector (VectorFor a) a, RecVec rs) => RecVec ((:) * ((:->) s a) rs) 

Methods

allocRec :: PrimMonad m => proxy ((* ': (s :-> a)) rs) -> m (Record (VectorMs m ((* ': (s :-> a)) rs))) #

freezeRec :: PrimMonad m => proxy ((* ': (s :-> a)) rs) -> Int -> Record (VectorMs m ((* ': (s :-> a)) rs)) -> m (Record (Vectors ((* ': (s :-> a)) rs))) #

growRec :: PrimMonad m => proxy ((* ': (s :-> a)) rs) -> Record (VectorMs m ((* ': (s :-> a)) rs)) -> m (Record (VectorMs m ((* ': (s :-> a)) rs))) #

writeRec :: PrimMonad m => proxy ((* ': (s :-> a)) rs) -> Int -> Record (VectorMs m ((* ': (s :-> a)) rs)) -> Record ((* ': (s :-> a)) rs) -> m () #

indexRec :: proxy ((* ': (s :-> a)) rs) -> Int -> Record (Vectors ((* ': (s :-> a)) rs)) -> Record ((* ': (s :-> a)) rs) #

produceRec :: proxy ((* ': (s :-> a)) rs) -> Record (Vectors ((* ': (s :-> a)) rs)) -> Rec * ((->) Int) ((* ': (s :-> a)) rs) #

type Unwrapped ((:->) s a) # 
type Unwrapped ((:->) s a) = a

rlens :: (Functor g, RElem (s :-> a) rs (RIndex (s :-> a) rs), Functor g) => proxy (s :-> a) -> (a -> g a) -> Rec Identity rs -> g (Rec Identity rs) Source #

Lens to a particular field of a record using the Identity functor.

For example, given:

  type FFoo = "foo" :-> Int
  type FBar = "bar" :-> String
  fBar_ :: Proxy FBar
  fBar_ = Proxy

  rec :: Rec Identity '[FFoo, FBar]
  rec = 123 :*: "hello!" :*: Nil

Then:

  view (rlens fBar_)               rec == "hello!"
  set  (rlens fBar_) "goodbye!"    rec == 123 :*: "goodbye!" :*: Nil
  over (rlens fBar_) (map toUpper) rec == 123 :*: "HELLO!"   :*: Nil

rlens' :: (Functor f, Functor g, RElem (s :-> a) rs (RIndex (s :-> a) rs), Functor g) => proxy (s :-> a) -> (f a -> g (f a)) -> Rec f rs -> g (Rec f rs) Source #

Lens to a particular field of a record using any functor.

For example, given:

  type FFoo = "foo" :-> Int
  type FBar = "bar" :-> String
  fBar_ :: Proxy FBar
  fBar_ = Proxy

  rec :: Rec Maybe '[FFoo, FBar]
  rec = Just 123 :^: Just "hello!" :^: Nil

Then:

  view (rlens' fBar_)                      rec == Just "hello!"
  set  (rlens' fBar_) Nothing              rec == Just 123 :^: Nothing       :^: Nil
  over (rlens' fBar_) (fmap (map toUpper)) rec == Just 123 :^: Just "HELLO!" :^: Nil