napkin-spec-2.0.0
Safe HaskellNone
LanguageGHC2024

Napkin.Run.Effects.Languages.SqlRead

Synopsis

Documentation

class (Eq (BackendSchemaField bk), Show (BackendSchemaField bk)) => HasBackendSchemaField (bk :: k) where #

Associated Types

data BackendSchemaField (bk :: k) #

data SqlRead (b :: k) (m :: k1) a where #

Constructors

RunQuery :: forall {k} {k1} (b :: k) (m :: k1). Query -> SqlRead b m [Map Text Value] 
CheckTableExists :: forall {k} {k1} (b :: k) (m :: k1). Ref Table -> SqlRead b m Bool 
GetTableKind :: forall {k} {k1} (b :: k) (m :: k1). Ref Table -> SqlRead b m TableKind 
GetRelationSchema' :: forall {k} {k1} (b :: k) (m :: k1). Ref Table -> Relation -> SqlRead b m [BackendSchemaField b] 

Instances

Instances details
(IsRenderable Query b, IsRenderable SExp 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 #

GShow (SqlRead b m :: Type -> Type) # 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

gshowsPrec :: Int -> SqlRead b m a -> ShowS #

Show (SqlRead b m a) # 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

showsPrec :: Int -> SqlRead b m a -> ShowS #

show :: SqlRead b m a -> String #

showList :: [SqlRead b m a] -> ShowS #

Eq (SqlRead b m a) # 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Methods

(==) :: SqlRead b m a -> SqlRead b m a -> Bool #

(/=) :: SqlRead b m a -> SqlRead b m a -> Bool #

runQuery :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Query -> Sem r [Map Text Value] #

checkTableExists :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r Bool #

getTableKind :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Sem r TableKind #

getRelationSchema' :: forall {k} (b :: k) (r :: EffectRow). Member (SqlRead b :: (Type -> Type) -> Type -> Type) r => Ref Table -> Relation -> Sem r [BackendSchemaField b] #

runQuerySingleAnswer :: forall {k} (b :: k) a (r :: EffectRow). (Member (SqlRead b :: (Type -> Type) -> Type -> Type) r, Val a) => Query -> Sem r (Maybe a) #

Run a query and pull out the first column from its first row. Meant for queries that return a single result.

getRelationSchema :: forall {k} (b :: k) (r :: EffectRow). Members '[SqlRead b :: (Type -> Type) -> Type -> Type, Input TemporaryTableName :: (Type -> Type) -> Type -> Type] r => Relation -> Sem r [BackendSchemaField b] #

data SchemaDiff (bk :: k) #

Instances

Instances details
Generic (SchemaDiff bk) # 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

Associated Types

type Rep (SchemaDiff bk) 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

type Rep (SchemaDiff bk) = D1 ('MetaData "SchemaDiff" "Napkin.Run.Effects.Languages.SqlRead" "napkin-spec-2.0.0-5xXYUWOFBl6BG2xbztGZJm" 'False) (C1 ('MetaCons "SchemaDiff" 'PrefixI 'True) (S1 ('MetaSel ('Just "droppedColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BackendSchemaField bk]) :*: S1 ('MetaSel ('Just "addedColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BackendSchemaField bk])))

Methods

from :: SchemaDiff bk -> Rep (SchemaDiff bk) x #

to :: Rep (SchemaDiff bk) x -> SchemaDiff bk #

type Rep (SchemaDiff bk) # 
Instance details

Defined in Napkin.Run.Effects.Languages.SqlRead

type Rep (SchemaDiff bk) = D1 ('MetaData "SchemaDiff" "Napkin.Run.Effects.Languages.SqlRead" "napkin-spec-2.0.0-5xXYUWOFBl6BG2xbztGZJm" 'False) (C1 ('MetaCons "SchemaDiff" 'PrefixI 'True) (S1 ('MetaSel ('Just "droppedColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BackendSchemaField bk]) :*: S1 ('MetaSel ('Just "addedColumns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [BackendSchemaField bk])))

newtype SchemaDiffError (bk :: k) #