Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Aztecs.ECS.Query.Internal
Documentation
type family AccessToComponents (accesses :: [Type]) :: [Type] where ... Source #
Equations
AccessToComponents ('[] :: [Type]) = '[] :: [Type] | |
AccessToComponents (Read a ': rest) = a ': AccessToComponents rest | |
AccessToComponents (Write a ': rest) = a ': AccessToComponents rest | |
AccessToComponents (With a ': rest) = a ': AccessToComponents rest | |
AccessToComponents (Without a ': rest) = AccessToComponents rest |
type family ReadComponents (accesses :: [Type]) :: [Type] where ... Source #
Equations
ReadComponents ('[] :: [Type]) = '[] :: [Type] | |
ReadComponents (Read a ': rest) = a ': ReadComponents rest | |
ReadComponents (Write a ': rest) = ReadComponents rest | |
ReadComponents (With a ': rest) = ReadComponents rest | |
ReadComponents (Without a ': rest) = ReadComponents rest |
type family WriteComponents (accesses :: [Type]) :: [Type] where ... Source #
Equations
WriteComponents ('[] :: [Type]) = '[] :: [Type] | |
WriteComponents (Read a ': rest) = WriteComponents rest | |
WriteComponents (Write a ': rest) = a ': WriteComponents rest | |
WriteComponents (With a ': rest) = WriteComponents rest | |
WriteComponents (Without a ': rest) = WriteComponents rest |
type family WithComponents (accesses :: [Type]) :: [Type] where ... Source #
Equations
WithComponents ('[] :: [Type]) = '[] :: [Type] | |
WithComponents (Read a ': rest) = WithComponents rest | |
WithComponents (Write a ': rest) = WithComponents rest | |
WithComponents (With a ': rest) = a ': WithComponents rest | |
WithComponents (Without a ': rest) = WithComponents rest |
type family WithoutComponents (accesses :: [Type]) :: [Type] where ... Source #
Equations
WithoutComponents ('[] :: [Type]) = '[] :: [Type] | |
WithoutComponents (Read a ': rest) = WithoutComponents rest | |
WithoutComponents (Write a ': rest) = WithoutComponents rest | |
WithoutComponents (With a ': rest) = WithoutComponents rest | |
WithoutComponents (Without a ': rest) = a ': WithoutComponents rest |
type family HasOverlap (list1 :: [Type]) (list2 :: [Type]) :: Bool where ... Source #
Equations
HasOverlap ('[] :: [Type]) list2 = 'False | |
HasOverlap (a ': rest) list2 = Or (Contains a list2) (HasOverlap rest list2) |
type family HasDuplicates (list :: [Type]) :: Bool where ... Source #
Equations
HasDuplicates ('[] :: [Type]) = 'False | |
HasDuplicates (a ': rest) = Or (Contains a rest) (HasDuplicates rest) |
type family ValidateAccess (accesses :: [Type]) :: Bool where ... Source #
Equations
ValidateAccess accesses = And (Not (HasOverlap (WriteComponents accesses) (ReadComponents accesses))) (Not (HasDuplicates (WriteComponents accesses))) |
type ValidAccess (accesses :: [Type]) = ValidateAccess accesses ~ 'True Source #
Constructors
With |
Instances
(PrimMonad m, Lookup (ComponentStorage m a a) (WorldComponents m cs), Storage m (ComponentStorage m a)) => Queryable (AztecsT cs m) (With a) Source # | |||||
Defined in Aztecs.Internal Associated Types
| |||||
type QueryableAccess (With a) Source # | |||||
Defined in Aztecs.Internal |
Constructors
Without |
Instances
(PrimMonad m, Lookup (ComponentStorage m a a) (WorldComponents m cs), Storage m (ComponentStorage m a)) => Queryable (AztecsT cs m) (Without a) Source # | |||||
Defined in Aztecs.Internal Associated Types
| |||||
type QueryableAccess (Without a) Source # | |||||
Defined in Aztecs.Internal |
type family AccessComponent access where ... Source #
Equations
AccessComponent (Read a) = a | |
AccessComponent (Write a) = a | |
AccessComponent (With a) = a | |
AccessComponent (Without a) = a |
type family GenericQueryableAccess (f :: Type -> Type) :: [Type] where ... Source #
Equations
GenericQueryableAccess (M1 _1 _2 f) = GenericQueryableAccess f | |
GenericQueryableAccess (f :*: g) = GenericQueryableAccess f ++ GenericQueryableAccess g | |
GenericQueryableAccess (K1 _1 a :: Type -> Type) = QueryableAccess a | |
GenericQueryableAccess (U1 :: Type -> Type) = '[] :: [Type] |
class GenericQueryable (m :: Type -> Type) (f :: Type -> Type) where Source #
Methods
genericQueryableRep :: m [Maybe (f p)] Source #
Instances
Monad m => GenericQueryable m (U1 :: Type -> Type) Source # | |
Defined in Aztecs.ECS.Query.Internal Methods genericQueryableRep :: m [Maybe (U1 p)] Source # | |
(Monad m, GenericQueryable m f, GenericQueryable m g) => GenericQueryable m (f :*: g) Source # | |
Defined in Aztecs.ECS.Query.Internal Methods genericQueryableRep :: m [Maybe ((f :*: g) p)] Source # | |
(Functor m, Queryable m a) => GenericQueryable m (K1 i a :: Type -> Type) Source # | |
Defined in Aztecs.ECS.Query.Internal Methods genericQueryableRep :: m [Maybe (K1 i a p)] Source # | |
(Functor m, GenericQueryable m f) => GenericQueryable m (M1 i c f) Source # | |
Defined in Aztecs.ECS.Query.Internal Methods genericQueryableRep :: m [Maybe (M1 i c f p)] Source # |
class Queryable (m :: Type -> Type) a where Source #
Minimal complete definition
Nothing
Associated Types
type QueryableAccess a :: [Type] Source #
type QueryableAccess a = GenericQueryableAccess (Rep a)
Methods
queryable :: m (Query a) Source #
default queryable :: (Functor m, Generic a, GenericQueryable m (Rep a), QueryableAccess a ~ GenericQueryableAccess (Rep a), ValidAccess (QueryableAccess a)) => m (Query a) Source #