Safe Haskell | None |
---|---|
Language | GHC2024 |
Napkin.Run.Effects.Interceptors.LogProgram.Types
Documentation
class DumpPayload a (b :: k) where #
Methods
renderDumpPayload_ :: a -> Doc #
Instances
DumpPayload LText (b :: k) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods renderDumpPayload_ :: LText -> Doc # | |
DumpPayload Text (b :: k) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods renderDumpPayload_ :: Text -> Doc # | |
RenderSql a b => DumpPayload a (b :: k) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods renderDumpPayload_ :: a -> Doc # |
type IsRenderable a (b :: k) = (Show a, Eq a, DumpPayload a b, Typeable a) #
data Renderable (b :: k) #
Constructors
IsRenderable a b => Renderable a |
Instances
Show (Renderable b) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> Renderable b -> ShowS # show :: Renderable b -> String # showList :: [Renderable b] -> ShowS # | |
Eq (Renderable b) # | |
renderDumpPayload :: forall {k} (b :: k). Renderable b -> Doc #
Constructors
DumpItem | |
Fields
|
Instances
renderableDumpItem :: forall {k} a (b :: k). (IsRenderable a b, ToHashComponent b a) => Text -> a -> Doc RenderInfoFormatting -> DumpItem b #
nonRenderableDumpItem :: forall {k} (b :: k). HashComponents b -> Doc RenderInfoFormatting -> DumpItem b #
data RenderInfoFormatting #
Constructors
FormatText | |
FormatTableRef | |
FormatCode |
class ToDumpItem (b :: k) (a :: (Type -> Type) -> k1 -> Type) where #
Methods
toDumpItem :: forall (r :: EffectRow) (x :: k1). a (Sem r) x -> DumpItem b #
Instances
ToDumpItem (b :: k) (Assertion :: (Type -> Type) -> Type -> Type) # | |
ToDumpItem (b :: k) (External :: (Type -> Type) -> Type -> Type) # | |
ToDumpItem (b :: k) (Log :: (Type -> Type) -> Type -> Type) # | |
ToDumpItem (b :: k) (Reader TableMemos) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toDumpItem :: forall (r :: EffectRow) x. Reader TableMemos (Sem r) x -> DumpItem b # | |
(Default (BackendTableMeta b), Default (BackendViewMeta b), Eq (BackendMaterializedViewMeta b), Eq (BackendTableMeta b), Eq (BackendViewMeta b), Eq (YamlBackendMaterializedViewMeta b), IsRenderable Query b, IsRenderable SExp b, IsRenderable Statement b, IsRenderable Text b, IsRenderable UpdateQuery b, MaybeDefault (YamlBackendMaterializedViewMeta b), Show (BackendMaterializedViewMeta b), Show (BackendTableMeta b), Show (BackendViewMeta b), ToHashComponent b (BackendMaterializedViewMeta b), ToHashComponent b (BackendTableMeta b), ToHashComponent b (BackendViewMeta b), Typeable (BackendMaterializedViewMeta b), Typeable (BackendTableMeta b), Typeable (BackendViewMeta b)) => ToDumpItem (b :: Type) (SqlWrite b :: (Type -> Type) -> Type -> Type) # | |
ToDumpItem (b :: k) (Output TableMemo :: (Type -> Type) -> Type -> Type) # | |
ToDumpItem (b :: k) (AnnotateRead b :: (Type -> Type) -> Type -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toDumpItem :: forall (r :: EffectRow) x. AnnotateRead b (Sem r) x -> DumpItem b # | |
ToDumpItem (b :: k) (AnnotateWrite b :: (Type -> Type) -> Type -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toDumpItem :: forall (r :: EffectRow) x. AnnotateWrite b (Sem r) x -> DumpItem b # | |
(IsRenderable Query b, IsRenderable SExp b, IsRenderable Text b) => ToDumpItem (b :: k) (SqlRead b :: (Type -> Type) -> Type -> Type) # | |
toHashComponents :: forall {k} (bk :: k) a. ToHashComponent bk a => Text -> a -> HashComponents bk #
formatRef :: forall {k} (t :: k). Ref t -> Doc RenderInfoFormatting #
formatCode :: ToString a => a -> Doc RenderInfoFormatting #
data HashComponent #
Constructors
Hash Text | |
Unhashable | |
NoHash |
Instances
Monoid HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods mempty :: HashComponent # mappend :: HashComponent -> HashComponent -> HashComponent # mconcat :: [HashComponent] -> HashComponent # | |
Semigroup HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (<>) :: HashComponent -> HashComponent -> HashComponent # sconcat :: NonEmpty HashComponent -> HashComponent # stimes :: Integral b => b -> HashComponent -> HashComponent # | |
IsString HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods fromString :: String -> HashComponent # | |
Show HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> HashComponent -> ShowS # show :: HashComponent -> String # showList :: [HashComponent] -> ShowS # | |
Eq HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (==) :: HashComponent -> HashComponent -> Bool # (/=) :: HashComponent -> HashComponent -> Bool # | |
ToHashComponent (b :: k) HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods |
class ToHashComponent (b :: k) a where #
Methods
toHashComponent :: a -> HashComponent #
Instances
ToHashComponent (b :: k) Int64 # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Int64 -> HashComponent # | |
DumpPayload Query b => ToHashComponent (b :: k) Query # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Query -> HashComponent # | |
DumpPayload SExp b => ToHashComponent (b :: k) SExp # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: SExp -> HashComponent # | |
ToHashComponent (b :: k) Type # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Type -> HashComponent # | |
DumpPayload UpdateQuery b => ToHashComponent (b :: k) UpdateQuery # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) HashComponent # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) AssertionGroup # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) AssertionSeverity # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) Cascade # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Cascade -> HashComponent # | |
ToHashComponent (b :: k) MissingBehavior # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) TableWriteStrategy # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
DumpPayload Statement b => ToHashComponent (b :: k) Statement # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) Text # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Text -> HashComponent # | |
ToHashComponent (b :: k) NominalDiffTime # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent (b :: k) UTCTime # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: UTCTime -> HashComponent # | |
ToHashComponent (b :: k) Integer # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Integer -> HashComponent # | |
ToHashComponent (b :: k) () # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: () -> HashComponent # | |
ToHashComponent (b :: k) Bool # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Bool -> HashComponent # | |
ToHashComponent (b :: k) Double # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Double -> HashComponent # | |
ToHashComponent (b :: k) Int # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Int -> HashComponent # | |
ToHashComponent b a => ToHashComponent (b :: k) (Set a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Set a -> HashComponent # | |
ToHashComponent b a => ToHashComponent (b :: k) (NonEmpty a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: NonEmpty a -> HashComponent # | |
(GToHashComponent b (Rep a), Generic a) => ToHashComponent (b :: k) (Generically a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Generically a -> HashComponent # | |
Show a => ToHashComponent (b :: k) (ShowHashComponent a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods | |
ToHashComponent b a => ToHashComponent (b :: k) (Maybe a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Maybe a -> HashComponent # | |
ToHashComponent b a => ToHashComponent (b :: k) [a] # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: [a] -> HashComponent # | |
(ToHashComponent b x, ToHashComponent b y) => ToHashComponent (b :: k) (Either x y) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Either x y -> HashComponent # | |
(Hashable a, ToHashComponent b a, ToHashComponent b x) => ToHashComponent (b :: k) (HashMap a x) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: HashMap a x -> HashComponent # | |
(ToHashComponent b x, ToHashComponent b y) => ToHashComponent (b :: k) (x, y) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: (x, y) -> HashComponent # | |
ToHashComponent (b :: k1) (Ref a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: Ref a -> HashComponent # | |
DumpPayload a b => ToHashComponent (b :: k) (DumpPayloadHashComponent b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: DumpPayloadHashComponent b a -> HashComponent # | |
(ToHashComponent b x, ToHashComponent b y, ToHashComponent b z) => ToHashComponent (b :: k) (x, y, z) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: (x, y, z) -> HashComponent # | |
(Foldable f, ToHashComponent b a) => ToHashComponent (b :: k) (FoldableHashComponent f b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: FoldableHashComponent f b a -> HashComponent # |
newtype ShowHashComponent a #
Constructors
ShowHashComponent a |
Instances
Show a => ToHashComponent (b :: k) (ShowHashComponent a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods |
newtype DumpPayloadHashComponent (b :: k) a #
Constructors
DumpPayloadHashComponent a |
Instances
DumpPayload a b => ToHashComponent (b :: k) (DumpPayloadHashComponent b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: DumpPayloadHashComponent b a -> HashComponent # | |
Show a => Show (DumpPayloadHashComponent b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> DumpPayloadHashComponent b a -> ShowS # show :: DumpPayloadHashComponent b a -> String # showList :: [DumpPayloadHashComponent b a] -> ShowS # | |
Eq a => Eq (DumpPayloadHashComponent b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (==) :: DumpPayloadHashComponent b a -> DumpPayloadHashComponent b a -> Bool # (/=) :: DumpPayloadHashComponent b a -> DumpPayloadHashComponent b a -> Bool # |
class GToHashComponent (b :: k) (f :: k1 -> Type) where #
Methods
gToHashComponent :: forall (a :: k1). f a -> HashComponent #
Instances
GToHashComponent (b :: k1) (U1 :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a :: k2). U1 a -> HashComponent # | |
GToHashComponent (b :: k1) (V1 :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a :: k2). V1 a -> HashComponent # | |
(GToHashComponent b x, GToHashComponent b y) => GToHashComponent (b :: k1) (x :*: y :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a :: k2). (x :*: y) a -> HashComponent # | |
(GToHashComponent b x, GToHashComponent b y) => GToHashComponent (b :: k1) (x :+: y :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a :: k2). (x :+: y) a -> HashComponent # | |
(Constructor m, GToHashComponent b a) => GToHashComponent (b :: k1) (C1 m a :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a0 :: k2). C1 m a a0 -> HashComponent # | |
GToHashComponent b a => GToHashComponent (b :: k1) (D1 m a :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a0 :: k2). D1 m a a0 -> HashComponent # | |
ToHashComponent b a => GToHashComponent (b :: k1) (K1 m a :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a0 :: k2). K1 m a a0 -> HashComponent # | |
(GToHashComponent b a, Selector m) => GToHashComponent (b :: k1) (S1 m a :: k2 -> Type) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods gToHashComponent :: forall (a0 :: k2). S1 m a a0 -> HashComponent # |
newtype FoldableHashComponent (f :: k -> Type) (b :: k1) (a :: k) #
Constructors
FoldableHashComponent (f a) |
Instances
(Foldable f, ToHashComponent b a) => ToHashComponent (b :: k) (FoldableHashComponent f b a) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toHashComponent :: FoldableHashComponent f b a -> HashComponent # |
data HashComponent' (b :: k) #
Constructors
(Eq x, Show x, ToHashComponent b x, Typeable x) => HashComponent x |
Instances
IsString (HashComponent' b) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods fromString :: String -> HashComponent' b # | |
Show (HashComponent' b) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> HashComponent' b -> ShowS # show :: HashComponent' b -> String # showList :: [HashComponent' b] -> ShowS # | |
Eq (HashComponent' b) # | |
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (==) :: HashComponent' b -> HashComponent' b -> Bool # (/=) :: HashComponent' b -> HashComponent' b -> Bool # |
newtype HashComponents (b :: k) #
Constructors
HashComponents [HashComponent' b] |
Instances
Monoid (HashComponents b) # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods mempty :: HashComponents b # mappend :: HashComponents b -> HashComponents b -> HashComponents b # mconcat :: [HashComponents b] -> HashComponents b # | |||||
Semigroup (HashComponents b) # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (<>) :: HashComponents b -> HashComponents b -> HashComponents b # sconcat :: NonEmpty (HashComponents b) -> HashComponents b # stimes :: Integral b0 => b0 -> HashComponents b -> HashComponents b # | |||||
Generic (HashComponents b) # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Associated Types
Methods from :: HashComponents b -> Rep (HashComponents b) x # to :: Rep (HashComponents b) x -> HashComponents b # | |||||
Show (HashComponents b) # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> HashComponents b -> ShowS # show :: HashComponents b -> String # showList :: [HashComponents b] -> ShowS # | |||||
Eq (HashComponents b) # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods (==) :: HashComponents b -> HashComponents b -> Bool # (/=) :: HashComponents b -> HashComponents b -> Bool # | |||||
type Rep (HashComponents b) # | |||||
nonHashableProgram :: forall {k} (b :: k). HashComponents b #
excludedHashProgram :: forall {k} (b :: k). HashComponents b #
data ProgramHash #
Constructors
EmptyHash | |
ProgramHash Text | |
UnhashableProgram |
Instances
FromJSON ProgramHash # | |||||
ToJSON ProgramHash # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods toJSON :: ProgramHash -> Value # toEncoding :: ProgramHash -> Encoding # toJSONList :: [ProgramHash] -> Value # toEncodingList :: [ProgramHash] -> Encoding # omitField :: ProgramHash -> Bool # | |||||
Buildable ProgramHash # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods build :: ProgramHash -> Builder # | |||||
Generic ProgramHash # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Associated Types
| |||||
Show ProgramHash # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types Methods showsPrec :: Int -> ProgramHash -> ShowS # show :: ProgramHash -> String # showList :: [ProgramHash] -> ShowS # | |||||
Eq ProgramHash # | |||||
type Rep ProgramHash # | |||||
Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types type Rep ProgramHash = D1 ('MetaData "ProgramHash" "Napkin.Run.Effects.Interceptors.LogProgram.Types" "napkin-spec-2.0.0-K8Z80aIHKAH2qnB4rTEZon" 'False) (C1 ('MetaCons "EmptyHash" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ProgramHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "UnhashableProgram" 'PrefixI 'False) (U1 :: Type -> Type))) |
getProgramHash :: forall {k} (b :: k). HashComponents b -> ProgramHash #