napkin-spec-2.0.0
Safe HaskellNone
LanguageGHC2024

Napkin.Run.Effects.Interceptors.LogProgram.Types

Documentation

class DumpPayload a (b :: k) where #

Methods

renderDumpPayload_ :: a -> Doc #

Instances

Instances details
DumpPayload LText (b :: k) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

DumpPayload Text (b :: k) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

RenderSql a b => DumpPayload a (b :: k) # 
Instance details

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

Instances details
Show (Renderable b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Eq (Renderable b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

(==) :: Renderable b -> Renderable b -> Bool #

(/=) :: Renderable b -> Renderable b -> Bool #

renderDumpPayload :: forall {k} (b :: k). Renderable b -> Doc #

data DumpItem (b :: k) #

Instances

Instances details
Generic (DumpItem b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Associated Types

type Rep (DumpItem b) 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

type Rep (DumpItem b) = D1 ('MetaData "DumpItem" "Napkin.Run.Effects.Interceptors.LogProgram.Types" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "DumpItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Renderable b))) :*: S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc RenderInfoFormatting))))

Methods

from :: DumpItem b -> Rep (DumpItem b) x #

to :: Rep (DumpItem b) x -> DumpItem b #

Show (DumpItem b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

showsPrec :: Int -> DumpItem b -> ShowS #

show :: DumpItem b -> String #

showList :: [DumpItem b] -> ShowS #

Eq (DumpItem b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

(==) :: DumpItem b -> DumpItem b -> Bool #

(/=) :: DumpItem b -> DumpItem b -> Bool #

type Rep (DumpItem b) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

type Rep (DumpItem b) = D1 ('MetaData "DumpItem" "Napkin.Run.Effects.Interceptors.LogProgram.Types" "napkin-spec-2.0.0-7NH5JHRFo7V8BQP5NCfMo1" 'False) (C1 ('MetaCons "DumpItem" 'PrefixI 'True) (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Renderable b))) :*: S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc RenderInfoFormatting))))

class ToDumpItem (b :: k) (a :: (Type -> Type) -> k1 -> Type) where #

Methods

toDumpItem :: forall (r :: EffectRow) (x :: k1). a (Sem r) x -> DumpItem b #

Instances

Instances details
ToDumpItem (b :: k) (Assertion :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. Assertion (Sem r) x -> DumpItem b #

ToDumpItem (b :: k) (External :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. External (Sem r) x -> DumpItem b #

ToDumpItem (b :: k) (Log :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. Log (Sem r) x -> DumpItem b #

ToDumpItem (b :: k) (Reader TableMemos) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. Reader TableMemos (Sem r) x -> DumpItem b #

(Show (BackendTableMeta b), Show (BackendViewMeta b), Show (BackendMaterializedViewMeta b), IsRenderable Query b, IsRenderable Statement b, IsRenderable SExp b, IsRenderable UpdateQuery b, IsRenderable Text b, Default (BackendTableMeta b), Default (BackendViewMeta b), MaybeDefault (YamlBackendMaterializedViewMeta b), Eq (BackendTableMeta b), Eq (BackendViewMeta b), Eq (YamlBackendMaterializedViewMeta b)) => ToDumpItem (b :: Type) (SqlWrite b :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. SqlWrite b (Sem r) x -> DumpItem b #

ToDumpItem (b :: k) (Output TableMemo :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. Output TableMemo (Sem r) x -> DumpItem b #

ToDumpItem (b :: k) (AnnotateRead b :: (Type -> Type) -> Type -> Type) # 
Instance details

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) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. AnnotateWrite b (Sem r) x -> DumpItem b #

(IsRenderable SExp b, IsRenderable Query b, IsRenderable Text b) => ToDumpItem (b :: k) (SqlRead b :: (Type -> Type) -> Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Interceptors.LogProgram.Types

Methods

toDumpItem :: forall (r :: EffectRow) x. SqlRead b (Sem r) x -> DumpItem b #

formatRef :: forall {k} (t :: k). Ref t -> Doc RenderInfoFormatting #