Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Roboservant.Types.Internal
Synopsis
- data Provenance = Provenance SomeTypeRep Int
- data StashValue a = StashValue {
- getStashValue :: NonEmpty ([Provenance], a)
- stashHash :: IntSet
- newtype Stash = Stash {}
- newtype Atom x = Atom {
- unAtom :: x
- newtype Compound x = Compound {
- unCompound :: x
- hashedDyn :: (Hashable a, Typeable a) => a -> (Dynamic, Int)
Documentation
data Provenance Source #
Constructors
Provenance SomeTypeRep Int |
Instances
Generic Provenance Source # | |
Defined in Roboservant.Types.Internal Associated Types type Rep Provenance :: Type -> Type # | |
Show Provenance Source # | |
Defined in Roboservant.Types.Internal Methods showsPrec :: Int -> Provenance -> ShowS # show :: Provenance -> String # showList :: [Provenance] -> ShowS # | |
Eq Provenance Source # | |
Defined in Roboservant.Types.Internal | |
Hashable Provenance Source # | |
Defined in Roboservant.Types.Internal | |
type Rep Provenance Source # | |
Defined in Roboservant.Types.Internal type Rep Provenance = D1 ('MetaData "Provenance" "Roboservant.Types.Internal" "roboservant-0.1.0.3-DSuUXjun6GbE6D2WyRVAMJ" 'False) (C1 ('MetaCons "Provenance" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SomeTypeRep) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) |
data StashValue a Source #
Constructors
StashValue | |
Fields
|
Instances
Functor StashValue Source # | |
Defined in Roboservant.Types.Internal Methods fmap :: (a -> b) -> StashValue a -> StashValue b # (<$) :: a -> StashValue b -> StashValue a # | |
Show a => Show (StashValue a) Source # | |
Defined in Roboservant.Types.Internal Methods showsPrec :: Int -> StashValue a -> ShowS # show :: StashValue a -> String # showList :: [StashValue a] -> ShowS # |
Constructors
Stash | |
Fields |
Can't be built up from parts, can't be broken down further.
Instances
can be broken down and built up from generic pieces
Constructors
Compound | |
Fields
|
Instances
Eq x => Eq (Compound x) Source # | |
Hashable x => Hashable (Compound x) Source # | |
Defined in Roboservant.Types.Internal | |
(Hashable x, Typeable x, Generic x, GBreakdown (Rep x)) => Breakdown (Compound x) Source # | |
Defined in Roboservant.Types.Breakdown | |
(Hashable x, Typeable x, Generic x, GBuildFrom (Rep x)) => BuildFrom (Compound x) Source # | |
Defined in Roboservant.Types.BuildFrom |