Safe Haskell | None |
---|---|
Language | GHC2021 |
Skeletest.Internal.Snapshot
Synopsis
- data SnapshotContext = SnapshotContext {}
- data SnapshotResult
- updateSnapshot :: (Typeable a, MonadIO m) => SnapshotContext -> a -> m ()
- checkSnapshot :: (Typeable a, MonadIO m) => SnapshotContext -> a -> m SnapshotResult
- data SnapshotRenderer = Typeable a => SnapshotRenderer {
- render :: a -> Text
- snapshotLang :: Maybe Text
- defaultSnapshotRenderers :: [SnapshotRenderer]
- setSnapshotRenderers :: [SnapshotRenderer] -> IO ()
- getSnapshotRenderers :: MonadIO m => m [SnapshotRenderer]
- plainRenderer :: Typeable a => (a -> Text) -> SnapshotRenderer
- renderWithShow :: (Typeable a, Show a) => SnapshotRenderer
- data SnapshotFile = SnapshotFile {
- moduleName :: Text
- snapshots :: Map TestIdentifier [SnapshotValue]
- data SnapshotValue = SnapshotValue {}
- decodeSnapshotFile :: Text -> Maybe SnapshotFile
- encodeSnapshotFile :: SnapshotFile -> Text
- normalizeSnapshotFile :: SnapshotFile -> SnapshotFile
- getAndIncSnapshotIndex :: MonadIO m => m Int
- newtype SnapshotUpdateFlag = SnapshotUpdateFlag Bool
Running snapshot
data SnapshotContext Source #
Constructors
SnapshotContext | |
Fields |
data SnapshotResult Source #
Constructors
SnapshotMissing | |
SnapshotMatches | |
SnapshotDiff | |
Fields |
Instances
Show SnapshotResult Source # | |
Defined in Skeletest.Internal.Snapshot Methods showsPrec :: Int -> SnapshotResult -> ShowS # show :: SnapshotResult -> String # showList :: [SnapshotResult] -> ShowS # | |
Eq SnapshotResult Source # | |
Defined in Skeletest.Internal.Snapshot Methods (==) :: SnapshotResult -> SnapshotResult -> Bool # (/=) :: SnapshotResult -> SnapshotResult -> Bool # |
updateSnapshot :: (Typeable a, MonadIO m) => SnapshotContext -> a -> m () Source #
checkSnapshot :: (Typeable a, MonadIO m) => SnapshotContext -> a -> m SnapshotResult Source #
Rendering
data SnapshotRenderer Source #
Constructors
Typeable a => SnapshotRenderer | |
Fields
|
setSnapshotRenderers :: [SnapshotRenderer] -> IO () Source #
getSnapshotRenderers :: MonadIO m => m [SnapshotRenderer] Source #
plainRenderer :: Typeable a => (a -> Text) -> SnapshotRenderer Source #
renderWithShow :: (Typeable a, Show a) => SnapshotRenderer Source #
SnapshotFile
data SnapshotFile Source #
Constructors
SnapshotFile | |
Fields
|
Instances
Show SnapshotFile Source # | |
Defined in Skeletest.Internal.Snapshot Methods showsPrec :: Int -> SnapshotFile -> ShowS # show :: SnapshotFile -> String # showList :: [SnapshotFile] -> ShowS # | |
Eq SnapshotFile Source # | |
Defined in Skeletest.Internal.Snapshot |
data SnapshotValue Source #
Constructors
SnapshotValue | |
Fields
|
Instances
Show SnapshotValue Source # | |
Defined in Skeletest.Internal.Snapshot Methods showsPrec :: Int -> SnapshotValue -> ShowS # show :: SnapshotValue -> String # showList :: [SnapshotValue] -> ShowS # | |
Eq SnapshotValue Source # | |
Defined in Skeletest.Internal.Snapshot Methods (==) :: SnapshotValue -> SnapshotValue -> Bool # (/=) :: SnapshotValue -> SnapshotValue -> Bool # |
Infrastructure
getAndIncSnapshotIndex :: MonadIO m => m Int Source #
newtype SnapshotUpdateFlag Source #
Constructors
SnapshotUpdateFlag Bool |