Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.Vessel.Class
Synopsis
- class View (v :: (* -> *) -> *) where
- condenseV :: (Foldable t, Filterable t, Functor t) => t (v g) -> v (Compose t g)
- disperseV :: Align t => v (Compose t g) -> t (v g)
- cropV :: (forall a. s a -> i a -> r a) -> v s -> v i -> Maybe (v r)
- nullV :: v i -> Bool
- mapV :: (forall a. f a -> g a) -> v f -> v g
- traverseV :: Applicative m => (forall a. f a -> m (g a)) -> v f -> m (v g)
- mapMaybeV :: (forall a. f a -> Maybe (g a)) -> v f -> Maybe (v g)
- alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> v f -> v g -> Maybe (v h)
- alignWithV :: (forall a. These (f a) (g a) -> h a) -> v f -> v g -> v h
- class View v => EmptyView v where
- emptyV :: v f
- maybeEmptyView :: View v => v f -> Maybe (v f)
- class Empty1 a where
- empty :: a p
- type GCondenseView t f v = (Generic (v f), Generic (v (Compose t f)), CondenseView t (Rep (v f)) (Rep (v (Compose t f))))
- class (Foldable t, Filterable t, Functor t) => CondenseView t vf vtf where
- condenseView :: t (vf p) -> vtf p
- type GDisperseView t f v = (Generic (v f), Generic (v (Compose t f)), DisperseView t (Rep (v f)) (Rep (v (Compose t f))))
- class Align t => DisperseView t vf vtf where
- disperseView :: vtf p -> t (vf p)
- type GMapView f g v = (Generic (v f), Generic (v g), MapView f g (Rep (v f)) (Rep (v g)))
- class MapView f g vf vg where
- mapViewM :: Applicative m => (forall v'. (View v', EmptyView v') => v' f -> m (v' g)) -> vf p -> m (vg p)
- mapView :: MapView f g vf vg => (forall v'. (View v', EmptyView v') => v' f -> v' g) -> vf p -> vg p
- type GZipView f g h v = (Generic (v f), Generic (v g), Generic (v h), ZipView f g h (Rep (v f)) (Rep (v g)) (Rep (v h)))
- class ZipView f g h vf vg vh where
- zipViewM :: Applicative m => (forall v'. (View v', EmptyView v') => v' f -> v' g -> m (v' h)) -> vf p -> vg p -> m (vh p)
- zipView :: ZipView f g h vf vg vh => (forall v'. (View v', EmptyView v') => v' f -> v' g -> v' h) -> vf p -> vg p -> vh p
- collapseNullV :: View v => v f -> Maybe (v f)
- subtractV :: View v => v f -> v g -> Maybe (v f)
- alignWithMV :: forall m v f g h. (View v, Applicative m) => (forall a. These (f a) (g a) -> m (h a)) -> v f -> v g -> m (Maybe (v h))
- transposeView :: (View v, Foldable t, Filterable t, Functor t, Align t, QueryResult (t (v g)) ~ t (v g'), QueryResult (v (Compose t g)) ~ v (Compose t g'), Monoid (v g), Monoid (v (Compose t g))) => QueryMorphism (t (v g)) (v (Compose t g))
- mapDecomposedV :: (Functor m, View v) => (v Proxy -> m (v Identity)) -> v (Compose (MonoidalMap c) g) -> m (Maybe (v (Compose (MonoidalMap c) Identity)))
- filterV :: View v => (forall a. f a -> Bool) -> v f -> Maybe (v f)
Documentation
class View (v :: (* -> *) -> *) where Source #
Our containers are parameterised by a choice of functor to apply at the leaves of their structure. By applying them to Identity, we obtain ordinary containers for data, called "views". By applying them to Proxy, we obtain what are effectively blank forms to be filled in, called "queries" or "view selectors". By using a functor such as Map k, information about many queries or their results may be aggregated together into a single container.
This class codifies the operations we need to be able to perform on these container types in order to transpose various Map-like structures into and out of them.
This is done for the purposes of, on the one hand collecting many users' view selectors into a single aggregated selector containing information about who is interested in each part (condenseV), and on the other hand, taking the resulting aggregated views and splitting them into a Map of views for each user (disperseV).
It also specifies the cropV operation which restricts a view to a particular selection, as well as operations for mapping functions over all the leaves of the container.
Minimal complete definition
Nothing
Methods
condenseV :: (Foldable t, Filterable t, Functor t) => t (v g) -> v (Compose t g) Source #
Transpose a sufficiently-Map-like structure into a container, effectively aggregating many structures into a single one containing information about which keys each part of it came from originally.
condenseV :: GCondenseView t g v => t (v g) -> v (Compose t g) Source #
Transpose a sufficiently-Map-like structure into a container, effectively aggregating many structures into a single one containing information about which keys each part of it came from originally.
disperseV :: Align t => v (Compose t g) -> t (v g) Source #
Transpose a sufficiently-Map-like structure out of a container, the inverse of condenseV.
disperseV :: GDisperseView t g v => v (Compose t g) -> t (v g) Source #
Transpose a sufficiently-Map-like structure out of a container, the inverse of condenseV.
cropV :: (forall a. s a -> i a -> r a) -> v s -> v i -> Maybe (v r) Source #
Given a structure specifying a query, and a structure representing a view of data, restrict the view to only those parts which satisfy the query. (Essentially intersection of Maps.)
cropV :: forall s i r. GZipView s i r v => (forall a. s a -> i a -> r a) -> v s -> v i -> Maybe (v r) Source #
Given a structure specifying a query, and a structure representing a view of data, restrict the view to only those parts which satisfy the query. (Essentially intersection of Maps.)
We also want a way to determine if the container is empty, because shipping empty containers around is a bad idea.
nullV :: forall i. GMapView i i v => v i -> Bool Source #
We also want a way to determine if the container is empty, because shipping empty containers around is a bad idea.
mapV :: (forall a. f a -> g a) -> v f -> v g Source #
Map a natural transformation over all the leaves of a container, changing the functor which has been applied.
mapV :: GMapView f g v => (forall a. f a -> g a) -> v f -> v g Source #
Map a natural transformation over all the leaves of a container, changing the functor which has been applied.
traverseV :: Applicative m => (forall a. f a -> m (g a)) -> v f -> m (v g) Source #
Traverse over the leaves of a container.
traverseV :: (GMapView f g v, Applicative m) => (forall a. f a -> m (g a)) -> v f -> m (v g) Source #
Traverse over the leaves of a container.
mapMaybeV :: (forall a. f a -> Maybe (g a)) -> v f -> Maybe (v g) Source #
Map over all the leaves of a container, keeping only the Just
results
and returing Nothing
if no leaves are kept.
mapMaybeV :: forall f g. GMapView f g v => (forall a. f a -> Maybe (g a)) -> v f -> Maybe (v g) Source #
Map over all the leaves of a container, keeping only the Just
results
and returing Nothing
if no leaves are kept.
alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> v f -> v g -> Maybe (v h) Source #
Map over all the leaves of two containers, combining the leaves with the
provided function, keeping only the Just
results and returing Nothing
if no leaves are kept.
alignWithMaybeV :: forall f g h. GZipView f g h v => (forall a. These (f a) (g a) -> Maybe (h a)) -> v f -> v g -> Maybe (v h) Source #
Map over all the leaves of two containers, combining the leaves with the
provided function, keeping only the Just
results and returing Nothing
if no leaves are kept.
alignWithV :: (forall a. These (f a) (g a) -> h a) -> v f -> v g -> v h Source #
Map over all the leaves of two containers, combining the leaves with the provided function
alignWithV :: GZipView f g h v => (forall a. These (f a) (g a) -> h a) -> v f -> v g -> v h Source #
Map over all the leaves of two containers, combining the leaves with the provided function
Instances
View (Proxy :: (Type -> Type) -> Type) Source # | a completely empty view. |
Defined in Data.Vessel.Class Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (Proxy g) -> Proxy (Compose t g) Source # disperseV :: Align t => Proxy (Compose t g) -> t (Proxy g) Source # cropV :: (forall a. s a -> i a -> r a) -> Proxy s -> Proxy i -> Maybe (Proxy r) Source # nullV :: Proxy i -> Bool Source # mapV :: (forall a. f a -> g a) -> Proxy f -> Proxy g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> Proxy f -> m (Proxy g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> Proxy f -> Maybe (Proxy g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> Proxy f -> Proxy g -> Maybe (Proxy h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> Proxy f -> Proxy g -> Proxy h Source # | |
(Has View k, GCompare k) => View (Vessel k) Source # | |
Defined in Data.Vessel.Vessel Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (Vessel k g) -> Vessel k (Compose t g) Source # disperseV :: Align t => Vessel k (Compose t g) -> t (Vessel k g) Source # cropV :: (forall a. s a -> i a -> r a) -> Vessel k s -> Vessel k i -> Maybe (Vessel k r) Source # nullV :: Vessel k i -> Bool Source # mapV :: (forall a. f a -> g a) -> Vessel k f -> Vessel k g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> Vessel k f -> m (Vessel k g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> Vessel k f -> Maybe (Vessel k g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> Vessel k f -> Vessel k g -> Maybe (Vessel k h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> Vessel k f -> Vessel k g -> Vessel k h Source # | |
View (SingleV a) Source # | |
Defined in Data.Vessel.Single Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (SingleV a g) -> SingleV a (Compose t g) Source # disperseV :: Align t => SingleV a (Compose t g) -> t (SingleV a g) Source # cropV :: (forall a0. s a0 -> i a0 -> r a0) -> SingleV a s -> SingleV a i -> Maybe (SingleV a r) Source # nullV :: SingleV a i -> Bool Source # mapV :: (forall a0. f a0 -> g a0) -> SingleV a f -> SingleV a g Source # traverseV :: Applicative m => (forall a0. f a0 -> m (g a0)) -> SingleV a f -> m (SingleV a g) Source # mapMaybeV :: (forall a0. f a0 -> Maybe (g a0)) -> SingleV a f -> Maybe (SingleV a g) Source # alignWithMaybeV :: (forall a0. These (f a0) (g a0) -> Maybe (h a0)) -> SingleV a f -> SingleV a g -> Maybe (SingleV a h) Source # alignWithV :: (forall a0. These (f a0) (g a0) -> h a0) -> SingleV a f -> SingleV a g -> SingleV a h Source # | |
View (IdentityV a) Source # | |
Defined in Data.Vessel.Identity Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (IdentityV a g) -> IdentityV a (Compose t g) Source # disperseV :: Align t => IdentityV a (Compose t g) -> t (IdentityV a g) Source # cropV :: (forall a0. s a0 -> i a0 -> r a0) -> IdentityV a s -> IdentityV a i -> Maybe (IdentityV a r) Source # nullV :: IdentityV a i -> Bool Source # mapV :: (forall a0. f a0 -> g a0) -> IdentityV a f -> IdentityV a g Source # traverseV :: Applicative m => (forall a0. f a0 -> m (g a0)) -> IdentityV a f -> m (IdentityV a g) Source # mapMaybeV :: (forall a0. f a0 -> Maybe (g a0)) -> IdentityV a f -> Maybe (IdentityV a g) Source # alignWithMaybeV :: (forall a0. These (f a0) (g a0) -> Maybe (h a0)) -> IdentityV a f -> IdentityV a g -> Maybe (IdentityV a h) Source # alignWithV :: (forall a0. These (f a0) (g a0) -> h a0) -> IdentityV a f -> IdentityV a g -> IdentityV a h Source # | |
GCompare k => View (MonoidalDMap k) Source # | |
Defined in Data.Vessel.Class Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (MonoidalDMap k g) -> MonoidalDMap k (Compose t g) Source # disperseV :: Align t => MonoidalDMap k (Compose t g) -> t (MonoidalDMap k g) Source # cropV :: (forall a. s a -> i a -> r a) -> MonoidalDMap k s -> MonoidalDMap k i -> Maybe (MonoidalDMap k r) Source # nullV :: MonoidalDMap k i -> Bool Source # mapV :: (forall a. f a -> g a) -> MonoidalDMap k f -> MonoidalDMap k g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> MonoidalDMap k f -> m (MonoidalDMap k g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> MonoidalDMap k f -> Maybe (MonoidalDMap k g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> MonoidalDMap k f -> MonoidalDMap k g -> Maybe (MonoidalDMap k h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> MonoidalDMap k f -> MonoidalDMap k g -> MonoidalDMap k h Source # | |
GCompare k => View (DMapV k v) Source # | |
Defined in Data.Vessel.DependentMap Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (DMapV k v g) -> DMapV k v (Compose t g) Source # disperseV :: Align t => DMapV k v (Compose t g) -> t (DMapV k v g) Source # cropV :: (forall a. s a -> i a -> r a) -> DMapV k v s -> DMapV k v i -> Maybe (DMapV k v r) Source # nullV :: DMapV k v i -> Bool Source # mapV :: (forall a. f a -> g a) -> DMapV k v f -> DMapV k v g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> DMapV k v f -> m (DMapV k v g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> DMapV k v f -> Maybe (DMapV k v g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> DMapV k v f -> DMapV k v g -> Maybe (DMapV k v h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> DMapV k v f -> DMapV k v g -> DMapV k v h Source # | |
(Ord k, View v) => View (SubVessel k v) Source # | |
Defined in Data.Vessel.SubVessel Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (SubVessel k v g) -> SubVessel k v (Compose t g) Source # disperseV :: Align t => SubVessel k v (Compose t g) -> t (SubVessel k v g) Source # cropV :: (forall a. s a -> i a -> r a) -> SubVessel k v s -> SubVessel k v i -> Maybe (SubVessel k v r) Source # nullV :: SubVessel k v i -> Bool Source # mapV :: (forall a. f a -> g a) -> SubVessel k v f -> SubVessel k v g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> SubVessel k v f -> m (SubVessel k v g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> SubVessel k v f -> Maybe (SubVessel k v g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> SubVessel k v f -> SubVessel k v g -> Maybe (SubVessel k v h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> SubVessel k v f -> SubVessel k v g -> SubVessel k v h Source # | |
Ord k => View (MapV k v) Source # | |
Defined in Data.Vessel.Map Methods condenseV :: (Foldable t, Filterable t, Functor t) => t (MapV k v g) -> MapV k v (Compose t g) Source # disperseV :: Align t => MapV k v (Compose t g) -> t (MapV k v g) Source # cropV :: (forall a. s a -> i a -> r a) -> MapV k v s -> MapV k v i -> Maybe (MapV k v r) Source # nullV :: MapV k v i -> Bool Source # mapV :: (forall a. f a -> g a) -> MapV k v f -> MapV k v g Source # traverseV :: Applicative m => (forall a. f a -> m (g a)) -> MapV k v f -> m (MapV k v g) Source # mapMaybeV :: (forall a. f a -> Maybe (g a)) -> MapV k v f -> Maybe (MapV k v g) Source # alignWithMaybeV :: (forall a. These (f a) (g a) -> Maybe (h a)) -> MapV k v f -> MapV k v g -> Maybe (MapV k v h) Source # alignWithV :: (forall a. These (f a) (g a) -> h a) -> MapV k v f -> MapV k v g -> MapV k v h Source # |
class View v => EmptyView v where Source #
A type v
supports EmptyView iff it is able to contain no information.
Instances
(Has View k, GCompare k) => EmptyView (Vessel k) Source # | |
Defined in Data.Vessel.Vessel | |
GCompare k => EmptyView (MonoidalDMap k) Source # | |
Defined in Data.Vessel.Class Methods emptyV :: MonoidalDMap k f Source # | |
GCompare k => EmptyView (DMapV k v) Source # | |
Defined in Data.Vessel.DependentMap | |
(Ord k, View v) => EmptyView (SubVessel k v) Source # | |
Defined in Data.Vessel.SubVessel | |
Ord k => EmptyView (MapV k v) Source # | |
Defined in Data.Vessel.Map |
maybeEmptyView :: View v => v f -> Maybe (v f) Source #
Instances
Empty1 (U1 :: k -> Type) Source # | |
Defined in Data.Vessel.Class | |
(Empty1 a, Empty1 b) => Empty1 (a :*: b :: k -> Type) Source # | |
Defined in Data.Vessel.Class | |
EmptyView v => Empty1 (K1 i (v f) :: k -> Type) Source # | |
Defined in Data.Vessel.Class | |
Empty1 a => Empty1 (M1 i t a :: k -> Type) Source # | |
Defined in Data.Vessel.Class |
type GCondenseView t f v = (Generic (v f), Generic (v (Compose t f)), CondenseView t (Rep (v f)) (Rep (v (Compose t f)))) Source #
class (Foldable t, Filterable t, Functor t) => CondenseView t vf vtf where Source #
Methods
condenseView :: t (vf p) -> vtf p Source #
Instances
(Foldable t, Filterable t, Functor t) => CondenseView t (U1 :: k -> Type) (U1 :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods condenseView :: t (U1 p) -> U1 p Source # | |
(CondenseView t avf avtf, CondenseView t bvf bvtf, Empty1 avf, Empty1 bvf) => CondenseView t (avf :*: bvf :: k -> Type) (avtf :*: bvtf :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods condenseView :: t ((avf :*: bvf) p) -> (avtf :*: bvtf) p Source # | |
(View v, Foldable t, Filterable t, Functor t) => CondenseView t (K1 i (v f) :: k -> Type) (K1 i (v (Compose t f)) :: k -> Type) Source # | |
Defined in Data.Vessel.Class | |
CondenseView t vf vtf => CondenseView t (M1 i t' vf :: k -> Type) (M1 i t' vtf :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods condenseView :: t (M1 i t' vf p) -> M1 i t' vtf p Source # |
type GDisperseView t f v = (Generic (v f), Generic (v (Compose t f)), DisperseView t (Rep (v f)) (Rep (v (Compose t f)))) Source #
class Align t => DisperseView t vf vtf where Source #
Methods
disperseView :: vtf p -> t (vf p) Source #
Instances
Align t => DisperseView t (U1 :: k -> Type) (U1 :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods disperseView :: U1 p -> t (U1 p) Source # | |
(DisperseView t avf avtf, DisperseView t bvf bvtf, Empty1 avf, Empty1 bvf) => DisperseView t (avf :*: bvf :: k -> Type) (avtf :*: bvtf :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods disperseView :: (avtf :*: bvtf) p -> t ((avf :*: bvf) p) Source # | |
(View v, Align t) => DisperseView t (K1 i (v f) :: k -> Type) (K1 i (v (Compose t f)) :: k -> Type) Source # | |
Defined in Data.Vessel.Class | |
DisperseView t vf vtf => DisperseView t (M1 i t' vf :: k -> Type) (M1 i t' vtf :: k -> Type) Source # | |
Defined in Data.Vessel.Class Methods disperseView :: M1 i t' vtf p -> t (M1 i t' vf p) Source # |
class MapView f g vf vg where Source #
Methods
mapViewM :: Applicative m => (forall v'. (View v', EmptyView v') => v' f -> m (v' g)) -> vf p -> m (vg p) Source #
Instances
MapView f g (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
MapView f g (V1 :: Type -> Type) (V1 :: Type -> Type) Source # | |
(MapView f g avf avg, MapView f g bvf bvg) => MapView f g (avf :*: bvf) (avg :*: bvg) Source # | |
(View v, EmptyView v) => MapView f g (K1 i (v f) :: Type -> Type) (K1 i (v g) :: Type -> Type) Source # | |
MapView f g vf vg => MapView f g (M1 i t vf) (M1 i t vg) Source # | |
mapView :: MapView f g vf vg => (forall v'. (View v', EmptyView v') => v' f -> v' g) -> vf p -> vg p Source #
type GZipView f g h v = (Generic (v f), Generic (v g), Generic (v h), ZipView f g h (Rep (v f)) (Rep (v g)) (Rep (v h))) Source #
class ZipView f g h vf vg vh where Source #
Methods
zipViewM :: Applicative m => (forall v'. (View v', EmptyView v') => v' f -> v' g -> m (v' h)) -> vf p -> vg p -> m (vh p) Source #
Instances
ZipView f g h (U1 :: Type -> Type) (U1 :: Type -> Type) (U1 :: Type -> Type) Source # | |
ZipView f g h (V1 :: Type -> Type) (V1 :: Type -> Type) (V1 :: Type -> Type) Source # | |
(ZipView f g h avf avg avh, ZipView f g h bvf bvg bvh) => ZipView f g h (avf :*: bvf) (avg :*: bvg) (avh :*: bvh) Source # | |
(View v, EmptyView v) => ZipView f g h (K1 i (v f) :: Type -> Type) (K1 i (v g) :: Type -> Type) (K1 i (v h) :: Type -> Type) Source # | |
ZipView f g h vf vg vh => ZipView f g h (M1 i t vf) (M1 i t vg) (M1 i t vh) Source # | |
zipView :: ZipView f g h vf vg vh => (forall v'. (View v', EmptyView v') => v' f -> v' g -> v' h) -> vf p -> vg p -> vh p Source #
collapseNullV :: View v => v f -> Maybe (v f) Source #
alignWithMV :: forall m v f g h. (View v, Applicative m) => (forall a. These (f a) (g a) -> m (h a)) -> v f -> v g -> m (Maybe (v h)) Source #
transposeView :: (View v, Foldable t, Filterable t, Functor t, Align t, QueryResult (t (v g)) ~ t (v g'), QueryResult (v (Compose t g)) ~ v (Compose t g'), Monoid (v g), Monoid (v (Compose t g))) => QueryMorphism (t (v g)) (v (Compose t g)) Source #
A main point of the View class is to be able to produce this QueryMorphism.
mapDecomposedV :: (Functor m, View v) => (v Proxy -> m (v Identity)) -> v (Compose (MonoidalMap c) g) -> m (Maybe (v (Compose (MonoidalMap c) Identity))) Source #