Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype VCObjectHash = VCObjectHash {}
- class VCHashUpdate obj where
- hashUpdateVia :: ByteArrayAccess ba => (obj -> ba) -> Context SHA256 -> obj -> Context SHA256
- newtype VCHashUpdateViaShow a = VCHashUpdateViaShow {}
- class GenericVCHashUpdate f where
- genHashUpdate :: Context SHA256 -> f p -> Context SHA256
- data Pinned a
- = Local
- | Builtin VCObjectHash
- | UnderVC a
- pinnedToMaybe :: Pinned VCObjectHash -> Maybe VCObjectHash
- pinnedUnderVCToMaybe :: Pinned a -> Maybe a
- vcObjectHashToByteString :: VCObjectHash -> ByteString
- byteStringToVCObjectHash :: ByteString -> Maybe VCObjectHash
- vcHash :: VCHashUpdate obj => obj -> VCObjectHash
Documentation
newtype VCObjectHash Source #
Instances
class VCHashUpdate obj where Source #
Typeclass of hashable objects
Nothing
Instances
hashUpdateVia :: ByteArrayAccess ba => (obj -> ba) -> Context SHA256 -> obj -> Context SHA256 Source #
newtype VCHashUpdateViaShow a Source #
Instances
Show a => VCHashUpdate (VCHashUpdateViaShow a) Source # | |
Defined in Inferno.Types.VersionControl |
class GenericVCHashUpdate f where Source #
Instances
GenericVCHashUpdate (U1 :: Type -> Type) Source # | |
Defined in Inferno.Types.VersionControl | |
GenericVCHashUpdate f => GenericVCHashUpdate (Rec1 f) Source # | |
Defined in Inferno.Types.VersionControl | |
(GenericVCHashUpdate a, GenericVCHashUpdate b) => GenericVCHashUpdate (a :*: b) Source # | |
Defined in Inferno.Types.VersionControl | |
(GenericVCHashUpdate a, GenericVCHashUpdate b) => GenericVCHashUpdate (a :+: b) Source # | |
Defined in Inferno.Types.VersionControl | |
(Constructor c, GenericVCHashUpdate f) => GenericVCHashUpdate (C1 c f) Source # | |
Defined in Inferno.Types.VersionControl | |
GenericVCHashUpdate f => GenericVCHashUpdate (D1 c f) Source # | |
Defined in Inferno.Types.VersionControl | |
VCHashUpdate a => GenericVCHashUpdate (K1 i a :: Type -> Type) Source # | |
Defined in Inferno.Types.VersionControl | |
GenericVCHashUpdate f => GenericVCHashUpdate (S1 c f) Source # | |
Defined in Inferno.Types.VersionControl |
Instances
Functor Pinned Source # | |
FromJSON a => FromJSON (Pinned a) Source # | |
ToJSON a => ToJSON (Pinned a) Source # | |
Defined in Inferno.Types.VersionControl | |
Data a => Data (Pinned a) Source # | |
Defined in Inferno.Types.VersionControl gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Pinned a -> c (Pinned a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Pinned a) # toConstr :: Pinned a -> Constr # dataTypeOf :: Pinned a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Pinned a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Pinned a)) # gmapT :: (forall b. Data b => b -> b) -> Pinned a -> Pinned a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Pinned a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Pinned a -> r # gmapQ :: (forall d. Data d => d -> u) -> Pinned a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Pinned a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Pinned a -> m (Pinned a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Pinned a -> m (Pinned a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Pinned a -> m (Pinned a) # | |
Generic (Pinned a) Source # | |
Show a => Show (Pinned a) Source # | |
Eq a => Eq (Pinned a) Source # | |
Ord a => Ord (Pinned a) Source # | |
Defined in Inferno.Types.VersionControl | |
VCHashUpdate a => VCHashUpdate (Pinned a) Source # | |
type Rep (Pinned a) Source # | |
Defined in Inferno.Types.VersionControl type Rep (Pinned a) = D1 ('MetaData "Pinned" "Inferno.Types.VersionControl" "inferno-types-0.1.0.0-EKMmIlZ8z5b3mVEUhFR81D" 'False) (C1 ('MetaCons "Local" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Builtin" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VCObjectHash)) :+: C1 ('MetaCons "UnderVC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
pinnedUnderVCToMaybe :: Pinned a -> Maybe a Source #
vcHash :: VCHashUpdate obj => obj -> VCObjectHash Source #