Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- cancelPacketSize :: CSize
- maximumPayloadPacketSize :: CSize
- pktHdrSz :: CSize
- data Sender
- data ResponseInfo a
- data ResponseType a = ResponseType Bool a
- data StreamType
- data Unimplemented
- newtype SPID = SPID Word16
- data PacketType (sender :: Sender) (resp :: ResponseInfo *) (d :: *) where
- PreLogin :: PacketType Client (ExpectsResponse (ResponseType False PreLogin)) PreLogin
- Login7 :: PacketType Client (ExpectsResponse (ResponseType False Login7Ack)) Login7
- SQLBatch :: PacketType Client (ExpectsResponse (ResponseType True RowResults)) Text
- BulkLoad :: PacketType Client NoResponse Unimplemented
- RPC :: PacketType Client NoResponse Unimplemented
- Attention :: PacketType Client (ExpectsResponse (ResponseType False ())) ()
- TrMgrRequest :: PacketType Client NoResponse Unimplemented
- TabularResult :: PacketType Server NoResponse a
- packetType :: PacketType sender resp d -> Word8
- newtype PacketStatus (s :: Sender) = PacketStatus Word8
- hasStatus :: PacketStatus s -> PacketStatus s -> Bool
- pktStatusEndOfMessage :: PacketStatus s
- pktStatusIgnore :: PacketStatus Client
- pktStatusResetConn :: PacketStatus Client
- pktStatusResetConnSkipTran :: PacketStatus Client
- newtype PacketSequenceID = PacketSequenceID Word8
- type family Packed (packed :: Bool) (a :: *) (b :: *) where ...
- data PacketHeader (sender :: Sender) (resp :: ResponseInfo *) (d :: *) where
- PacketHeader :: {..} -> PacketHeader sender resp d
- mkPacketHeader :: PacketType sender resp d -> PacketStatus sender -> PacketHeader sender resp d
- writeHdr :: Ptr a -> PacketHeader Client resp d -> IO ()
- readHdr :: PacketType sender resp d -> Ptr a -> IO (Maybe (PacketHeader sender resp d))
- data Packet (sender :: Sender) (resp :: ResponseInfo *) (d :: *) (f :: * -> *) where
- mkPacket :: PacketHeader sender resp d -> d -> Packet sender resp d Identity
- packetEncoding :: Payload d => Packet sender resp d Identity -> Packet sender resp d PacketEncoding
- displayRequest :: Show d => Packet sender resp d Identity -> String
- data PayloadEncoder (streaming :: StreamType) where
- newtype PacketEncoding pld = PacketEncoding (PayloadEncoder (PayloadStreaming pld))
- class Show pld => Payload pld where
- type PayloadStreaming pld :: StreamType
- encodePayload :: pld -> PayloadEncoder (PayloadStreaming pld)
- runBatchEncoder :: Monoid fixup => Tardis fixup (Builder, Word) () -> PayloadEncoder TokenlessStream
- getFixups :: Tardis fixup (Builder, Word) fixup
- getPosition :: Tardis fixup (Builder, Word) Word
- fixup :: Monoid fixup => fixup -> Tardis fixup (Builder, Word) ()
- emit :: Word -> Builder -> Tardis fixup (Builder, Word) ()
- newtype MajorVersion = MajorVersion Word8
- newtype MinorVersion = MinorVersion Word8
- newtype BuildNumber = BuildNumber Word16
- newtype SubBuildNumber = SubBuildNumber Word16
- data Encryption
- data Nonce = Nonce !Word64 !Word64 !Word64 !Word64
- data PreLoginOption
- type PreLoginOptions = [PreLoginOption]
- versionOption :: MajorVersion -> MinorVersion -> BuildNumber -> SubBuildNumber -> PreLoginOptions
- encryptionOff :: PreLoginOptions
- newtype PreLogin = PreLoginP {}
- newtype TDSVersion = TDSVersion {}
- newtype ClientProgVersion = ClientProgVersion {}
- newtype ClientPID = ClientPID {}
- newtype ConnectionID = ConnectionID {}
- newtype Login7Options = Login7Options {}
- defaultLoginOptions :: Login7Options
- data Login7Feature = Login7Feature
- newtype LCID = LCID Word16
- newtype CollationFlags = CollationFlags Word8
- newtype CollationVersion = CollationVersion Word8
- data Collation = Collation {}
- data ClientID = ClientID !Word16 !Word32
- tdsVersion71 :: TDSVersion
- data Login7 = Login7P {
- login7_tdsVersion :: !TDSVersion
- login7_packetSize :: !Word32
- login7_clientProgVer :: !ClientProgVersion
- login7_clientPID :: !ClientPID
- login7_connectionID :: !ConnectionID
- login7_flags :: !Login7Options
- login7_clientTmZone :: !Word32
- login7_collation :: !Collation
- login7_hostName :: !Text
- login7_userName :: !Text
- login7_password :: !Text
- login7_appName :: !Text
- login7_serverName :: !Text
- login7_extension :: !Text
- login7_cltIntName :: !Text
- login7_language :: !Text
- login7_database :: !Text
- login7_clientID :: !ClientID
- login7_SSPI :: !Text
- login7_atchDbFile :: !Text
- login7_changePasswd :: !Text
- login7_SSPILong :: !Word32
- login7_extraFeatures :: [Login7Feature]
- data Login7Fixups = Login7Fixups {
- login7_totalLen :: !(Sum Word32)
- login7_hostNameOfs :: !Word16
- login7_userNameOfs :: !Word16
- login7_passwordOfs :: !Word16
- login7_appNameOfs :: !Word16
- login7_serverNameOfs :: !Word16
- login7_extensionOfs :: !Word16
- login7_cltIntNameOfs :: !Word16
- login7_languageOfs :: !Word16
- login7_databaseOfs :: !Word16
- login7_SSPIOfs :: !Word16
- login7_atchDbFileOfs :: !Word16
- login7_changePasswdOfs :: !Word16
- data ResponseDecoder (streaming :: StreamType) (res :: *) where
- DecodeBatchResponse :: (Ptr Word8 -> Word16 -> IO (Maybe res)) -> ResponseDecoder TokenlessStream res
- DecodeTokenStream :: (forall r. IO () -> Stream TokenStream IO r -> IO res) -> ResponseDecoder TokenStream res
- class Show res => Response res where
- type ResponseStreaming res :: StreamType
- responseDecoder :: ResponseDecoder (ResponseStreaming res) res
- type BatchDecoder = StateT (Ptr Word8, Word16) (ReaderT Word16 (MaybeT IO))
- decodeBatch :: BatchDecoder a -> ResponseDecoder TokenlessStream a
- read8 :: BatchDecoder Word8
- read16BE :: BatchDecoder Word16
- read32BE :: BatchDecoder Word32
- read64BE :: BatchDecoder Word64
- read16LE :: BatchDecoder Word16
- read32LE :: BatchDecoder Word32
- read64LE :: BatchDecoder Word64
- ztText :: Word16 -> BatchDecoder Text
- tell :: BatchDecoder Word16
- seek :: Word16 -> BatchDecoder ()
- data Login7Ack = Login7Ack !Word8 !TDSVersion !Text !ProgVersion
- newtype DoneSts = DoneSts Word16
- newtype ProgVersion = ProgVersion Word32
- data Message = Message {
- messageCode :: !SQLError
- messageSt :: !Word8
- messageClass :: !ErrorClass
- messageText :: !Text
- messageServerName :: !Text
- messageProcName :: !Text
- messageLineNum :: Word16
- data EnvChange
- data Token' f
- = TvpRow
- | Offset
- | ReturnStatus
- | ColMetadata !ColumnMetadata
- | AltMetadata
- | TableName
- | ColumnInfo
- | Order (Vector Word8)
- | Error !Message
- | Info !Message
- | ReturnValue
- | LoginAck !Word8 !TDSVersion !Text !ProgVersion
- | FeatureExtAck
- | Row !f
- | NbcRow
- | AltRow
- | EnvChange !EnvChange
- | SessionState
- | SSPI
- | FedAuthInfo
- | Done !DoneSts !Word16 !Word64
- | DoneProc
- | DoneInProc
- type Token = Token' (ByteString IO ())
- data TokenStream f
- doneHasMore :: DoneSts -> Bool
- doneHasError :: DoneSts -> Bool
- parseTokenStream :: ByteString IO () -> Stream TokenStream IO ()
- usVarChar :: Parser (Int, Text)
- bVarChar :: Parser (Int, Text)
- bVarByte :: Parser (Int, ByteString)
- parseToken :: Parser (Either (ByteString IO () -> Token) Token)
- data EncryptionAlgorithm = EncryptionAlgorithm
- data EncryptionAlgorithmType = EncryptionAlgorithmType
- data CharKind
- data PrecScale = PrecScale !Word8 !Word8
- data TypeLen
- data TypeInfo
- = NullType
- | IntNType !Bool !Word8
- | GuidType !Word8
- | DecimalType !Bool !Word8 !PrecScale
- | NumericType !Bool !Word8 !PrecScale
- | BitNType !Bool !Word8
- | DecimalNType !Bool !Word8 !PrecScale
- | NumericNType !Bool !Word8 !PrecScale
- | FloatNType !Bool !Word8
- | MoneyNType !Bool !Word8
- | DtTmNType !Bool !Word8
- | DateNType !Bool !Word8
- | TimeNType !Bool !Word8
- | DtTm2NType !Word8
- | DtTmOfsType !Word8
- | CharType !TypeLen !CharKind !Word16 !(Maybe Collation)
- | VarcharType !TypeLen !CharKind !Word16 !(Maybe Collation)
- | BinaryType !Word16
- | VarBinType !Word16
- | ImageType !Word32
- | NTextType !Word32 !Collation
- | SSVarType !Word32
- | TextType !Word32 !Collation
- | XMLType !Word32
- data CryptoMetadata = CryptoMetadata {}
- data ColumnData = ColumnData {
- cdUserType :: !Word32
- cdFlags :: !Word16
- cdBaseTypeInfo :: !TypeInfo
- cdTableName :: !(Maybe Text)
- cdCrypto :: !(Maybe CryptoMetadata)
- cdColName :: !Text
- data ColumnMetadata = ColumnMetadata {
- cmCekTbl :: ByteString
- cmColData :: [ColumnData]
- data RawColumn f where
- RawColumn :: ColumnData -> ByteString IO () -> (ByteString IO () -> f) -> RawColumn f
- typeInfoParser :: Parser TypeInfo
- colDataParser :: Parser ColumnData
- colMetadataP :: Parser ColumnMetadata
- newtype RowResults = RowResults {}
- data SplitEncoding sender resp pld
- = LastPacket (Ptr () -> IO CSize)
- | OnePacket (Ptr () -> IO (Packet sender resp pld (SplitEncoding sender resp)))
- type SplitPacket sender resp pld = Packet sender resp pld (SplitEncoding sender resp)
- splitPacket :: CSize -> Packet Client resp d PacketEncoding -> (Maybe CSize, SplitPacket Client resp d)
- class KnownBool (b :: Bool) where
Documentation
data ResponseInfo a Source #
Instances
Show a => Show (ResponseInfo a) Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ResponseInfo a -> ShowS # show :: ResponseInfo a -> String # showList :: [ResponseInfo a] -> ShowS # |
data ResponseType a Source #
ResponseType | |
|
Instances
Show a => Show (ResponseType a) Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ResponseType a -> ShowS # show :: ResponseType a -> String # showList :: [ResponseType a] -> ShowS # |
data StreamType Source #
Instances
Show StreamType Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> StreamType -> ShowS # show :: StreamType -> String # showList :: [StreamType] -> ShowS # |
data Unimplemented Source #
Instances
Show Unimplemented Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> Unimplemented -> ShowS # show :: Unimplemented -> String # showList :: [Unimplemented] -> ShowS # | |
Response Unimplemented Source # | |
type ResponseStreaming Unimplemented Source # | |
Defined in Database.TDS.Proto |
Misc data types
Packets
Packet header
data PacketType (sender :: Sender) (resp :: ResponseInfo *) (d :: *) where Source #
Data type representing valid packet types
Instances
Show (PacketType sender resp d) Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> PacketType sender resp d -> ShowS # show :: PacketType sender resp d -> String # showList :: [PacketType sender resp d] -> ShowS # |
packetType :: PacketType sender resp d -> Word8 Source #
newtype PacketStatus (s :: Sender) Source #
Instances
Show (PacketStatus s) Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> PacketStatus s -> ShowS # show :: PacketStatus s -> String # showList :: [PacketStatus s] -> ShowS # | |
Semigroup (PacketStatus s) Source # | |
Defined in Database.TDS.Proto (<>) :: PacketStatus s -> PacketStatus s -> PacketStatus s # sconcat :: NonEmpty (PacketStatus s) -> PacketStatus s # stimes :: Integral b => b -> PacketStatus s -> PacketStatus s # | |
Monoid (PacketStatus s) Source # | |
Defined in Database.TDS.Proto mempty :: PacketStatus s # mappend :: PacketStatus s -> PacketStatus s -> PacketStatus s # mconcat :: [PacketStatus s] -> PacketStatus s # |
hasStatus :: PacketStatus s -> PacketStatus s -> Bool Source #
newtype PacketSequenceID Source #
Instances
Eq PacketSequenceID Source # | |
Defined in Database.TDS.Proto (==) :: PacketSequenceID -> PacketSequenceID -> Bool # (/=) :: PacketSequenceID -> PacketSequenceID -> Bool # | |
Show PacketSequenceID Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> PacketSequenceID -> ShowS # show :: PacketSequenceID -> String # showList :: [PacketSequenceID] -> ShowS # |
data PacketHeader (sender :: Sender) (resp :: ResponseInfo *) (d :: *) where Source #
PacketHeader | |
|
Instances
Show (PacketHeader sender resp d) Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> PacketHeader sender resp d -> ShowS # show :: PacketHeader sender resp d -> String # showList :: [PacketHeader sender resp d] -> ShowS # |
mkPacketHeader :: PacketType sender resp d -> PacketStatus sender -> PacketHeader sender resp d Source #
readHdr :: PacketType sender resp d -> Ptr a -> IO (Maybe (PacketHeader sender resp d)) Source #
data Packet (sender :: Sender) (resp :: ResponseInfo *) (d :: *) (f :: * -> *) where Source #
Packet | |
|
packetEncoding :: Payload d => Packet sender resp d Identity -> Packet sender resp d PacketEncoding Source #
Packet payloads
data PayloadEncoder (streaming :: StreamType) where Source #
newtype PacketEncoding pld Source #
class Show pld => Payload pld where Source #
type PayloadStreaming pld :: StreamType Source #
encodePayload :: pld -> PayloadEncoder (PayloadStreaming pld) Source #
Instances
Payload () Source # | |
Defined in Database.TDS.Proto type PayloadStreaming () :: StreamType Source # encodePayload :: () -> PayloadEncoder (PayloadStreaming ()) Source # | |
Payload Text Source # | |
Defined in Database.TDS.Proto type PayloadStreaming Text :: StreamType Source # | |
Payload Login7 Source # | |
Defined in Database.TDS.Proto type PayloadStreaming Login7 :: StreamType Source # | |
Payload PreLogin Source # | |
Defined in Database.TDS.Proto type PayloadStreaming PreLogin :: StreamType Source # |
runBatchEncoder :: Monoid fixup => Tardis fixup (Builder, Word) () -> PayloadEncoder TokenlessStream Source #
PRELOGIN Payload
newtype MajorVersion Source #
Instances
Num MajorVersion Source # | |
Defined in Database.TDS.Proto (+) :: MajorVersion -> MajorVersion -> MajorVersion # (-) :: MajorVersion -> MajorVersion -> MajorVersion # (*) :: MajorVersion -> MajorVersion -> MajorVersion # negate :: MajorVersion -> MajorVersion # abs :: MajorVersion -> MajorVersion # signum :: MajorVersion -> MajorVersion # fromInteger :: Integer -> MajorVersion # | |
Show MajorVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> MajorVersion -> ShowS # show :: MajorVersion -> String # showList :: [MajorVersion] -> ShowS # |
newtype MinorVersion Source #
Instances
Num MinorVersion Source # | |
Defined in Database.TDS.Proto (+) :: MinorVersion -> MinorVersion -> MinorVersion # (-) :: MinorVersion -> MinorVersion -> MinorVersion # (*) :: MinorVersion -> MinorVersion -> MinorVersion # negate :: MinorVersion -> MinorVersion # abs :: MinorVersion -> MinorVersion # signum :: MinorVersion -> MinorVersion # fromInteger :: Integer -> MinorVersion # | |
Show MinorVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> MinorVersion -> ShowS # show :: MinorVersion -> String # showList :: [MinorVersion] -> ShowS # |
newtype BuildNumber Source #
Instances
Num BuildNumber Source # | |
Defined in Database.TDS.Proto (+) :: BuildNumber -> BuildNumber -> BuildNumber # (-) :: BuildNumber -> BuildNumber -> BuildNumber # (*) :: BuildNumber -> BuildNumber -> BuildNumber # negate :: BuildNumber -> BuildNumber # abs :: BuildNumber -> BuildNumber # signum :: BuildNumber -> BuildNumber # fromInteger :: Integer -> BuildNumber # | |
Show BuildNumber Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> BuildNumber -> ShowS # show :: BuildNumber -> String # showList :: [BuildNumber] -> ShowS # |
newtype SubBuildNumber Source #
Instances
Num SubBuildNumber Source # | |
Defined in Database.TDS.Proto (+) :: SubBuildNumber -> SubBuildNumber -> SubBuildNumber # (-) :: SubBuildNumber -> SubBuildNumber -> SubBuildNumber # (*) :: SubBuildNumber -> SubBuildNumber -> SubBuildNumber # negate :: SubBuildNumber -> SubBuildNumber # abs :: SubBuildNumber -> SubBuildNumber # signum :: SubBuildNumber -> SubBuildNumber # fromInteger :: Integer -> SubBuildNumber # | |
Show SubBuildNumber Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> SubBuildNumber -> ShowS # show :: SubBuildNumber -> String # showList :: [SubBuildNumber] -> ShowS # |
data Encryption Source #
Instances
Show Encryption Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> Encryption -> ShowS # show :: Encryption -> String # showList :: [Encryption] -> ShowS # |
data PreLoginOption Source #
Instances
Show PreLoginOption Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> PreLoginOption -> ShowS # show :: PreLoginOption -> String # showList :: [PreLoginOption] -> ShowS # |
type PreLoginOptions = [PreLoginOption] Source #
versionOption :: MajorVersion -> MinorVersion -> BuildNumber -> SubBuildNumber -> PreLoginOptions Source #
Instances
Show PreLogin Source # | |
Response PreLogin Source # | |
Defined in Database.TDS.Proto type ResponseStreaming PreLogin :: StreamType Source # | |
Payload PreLogin Source # | |
Defined in Database.TDS.Proto type PayloadStreaming PreLogin :: StreamType Source # | |
type ResponseStreaming PreLogin Source # | |
Defined in Database.TDS.Proto | |
type PayloadStreaming PreLogin Source # | |
Defined in Database.TDS.Proto |
LOGIN7 Payload
newtype TDSVersion Source #
Instances
Show TDSVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> TDSVersion -> ShowS # show :: TDSVersion -> String # showList :: [TDSVersion] -> ShowS # |
newtype ClientProgVersion Source #
Instances
Show ClientProgVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ClientProgVersion -> ShowS # show :: ClientProgVersion -> String # showList :: [ClientProgVersion] -> ShowS # |
newtype ConnectionID Source #
Instances
Show ConnectionID Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ConnectionID -> ShowS # show :: ConnectionID -> String # showList :: [ConnectionID] -> ShowS # |
newtype Login7Options Source #
Instances
Show Login7Options Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> Login7Options -> ShowS # show :: Login7Options -> String # showList :: [Login7Options] -> ShowS # | |
Semigroup Login7Options Source # | |
Defined in Database.TDS.Proto (<>) :: Login7Options -> Login7Options -> Login7Options # sconcat :: NonEmpty Login7Options -> Login7Options # stimes :: Integral b => b -> Login7Options -> Login7Options # | |
Monoid Login7Options Source # | |
Defined in Database.TDS.Proto mempty :: Login7Options # mappend :: Login7Options -> Login7Options -> Login7Options # mconcat :: [Login7Options] -> Login7Options # |
data Login7Feature Source #
Instances
Show Login7Feature Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> Login7Feature -> ShowS # show :: Login7Feature -> String # showList :: [Login7Feature] -> ShowS # |
12-bit Windows language code identifier
newtype CollationFlags Source #
Instances
Show CollationFlags Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> CollationFlags -> ShowS # show :: CollationFlags -> String # showList :: [CollationFlags] -> ShowS # |
newtype CollationVersion Source #
4-bit collation version
Instances
Show CollationVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> CollationVersion -> ShowS # show :: CollationVersion -> String # showList :: [CollationVersion] -> ShowS # |
Login7P | |
|
Instances
Show Login7 Source # | |
Payload Login7 Source # | |
Defined in Database.TDS.Proto type PayloadStreaming Login7 :: StreamType Source # | |
type PayloadStreaming Login7 Source # | |
Defined in Database.TDS.Proto |
data Login7Fixups Source #
Instances
Show Login7Fixups Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> Login7Fixups -> ShowS # show :: Login7Fixups -> String # showList :: [Login7Fixups] -> ShowS # | |
Semigroup Login7Fixups Source # | |
Defined in Database.TDS.Proto (<>) :: Login7Fixups -> Login7Fixups -> Login7Fixups # sconcat :: NonEmpty Login7Fixups -> Login7Fixups # stimes :: Integral b => b -> Login7Fixups -> Login7Fixups # | |
Monoid Login7Fixups Source # | |
Defined in Database.TDS.Proto mempty :: Login7Fixups # mappend :: Login7Fixups -> Login7Fixups -> Login7Fixups # mconcat :: [Login7Fixups] -> Login7Fixups # |
Packet decoders
data ResponseDecoder (streaming :: StreamType) (res :: *) where Source #
DecodeBatchResponse :: (Ptr Word8 -> Word16 -> IO (Maybe res)) -> ResponseDecoder TokenlessStream res | |
DecodeTokenStream :: (forall r. IO () -> Stream TokenStream IO r -> IO res) -> ResponseDecoder TokenStream res |
class Show res => Response res where Source #
type ResponseStreaming res :: StreamType Source #
responseDecoder :: ResponseDecoder (ResponseStreaming res) res Source #
Instances
Response RowResults Source # | |
Defined in Database.TDS.Proto type ResponseStreaming RowResults :: StreamType Source # | |
Response Login7Ack Source # | |
Defined in Database.TDS.Proto type ResponseStreaming Login7Ack :: StreamType Source # | |
Response PreLogin Source # | |
Defined in Database.TDS.Proto type ResponseStreaming PreLogin :: StreamType Source # | |
Response Unimplemented Source # | |
decodeBatch :: BatchDecoder a -> ResponseDecoder TokenlessStream a Source #
seek :: Word16 -> BatchDecoder () Source #
PRELOGIN response
Instances
Show Login7Ack Source # | |
Response Login7Ack Source # | |
Defined in Database.TDS.Proto type ResponseStreaming Login7Ack :: StreamType Source # | |
type ResponseStreaming Login7Ack Source # | |
Defined in Database.TDS.Proto |
Tokens
newtype ProgVersion Source #
Instances
Show ProgVersion Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ProgVersion -> ShowS # show :: ProgVersion -> String # showList :: [ProgVersion] -> ShowS # |
Message | |
|
Instances
Show Message Source # | |
Exception Message Source # | |
Defined in Database.TDS.Proto toException :: Message -> SomeException # fromException :: SomeException -> Maybe Message # displayException :: Message -> String # |
data TokenStream f Source #
Instances
Functor TokenStream Source # | |
Defined in Database.TDS.Proto fmap :: (a -> b) -> TokenStream a -> TokenStream b # (<$) :: a -> TokenStream b -> TokenStream a # |
doneHasMore :: DoneSts -> Bool Source #
doneHasError :: DoneSts -> Bool Source #
parseTokenStream :: ByteString IO () -> Stream TokenStream IO () Source #
parseToken :: Parser (Either (ByteString IO () -> Token) Token) Source #
Tabular results
data EncryptionAlgorithm Source #
Instances
Show EncryptionAlgorithm Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> EncryptionAlgorithm -> ShowS # show :: EncryptionAlgorithm -> String # showList :: [EncryptionAlgorithm] -> ShowS # |
data EncryptionAlgorithmType Source #
Instances
Show EncryptionAlgorithmType Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> EncryptionAlgorithmType -> ShowS # show :: EncryptionAlgorithmType -> String # showList :: [EncryptionAlgorithmType] -> ShowS # |
data CryptoMetadata Source #
Instances
Show CryptoMetadata Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> CryptoMetadata -> ShowS # show :: CryptoMetadata -> String # showList :: [CryptoMetadata] -> ShowS # |
data ColumnData Source #
ColumnData | |
|
Instances
Show ColumnData Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ColumnData -> ShowS # show :: ColumnData -> String # showList :: [ColumnData] -> ShowS # |
data ColumnMetadata Source #
Instances
Show ColumnMetadata Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> ColumnMetadata -> ShowS # show :: ColumnMetadata -> String # showList :: [ColumnMetadata] -> ShowS # |
data RawColumn f where Source #
RawColumn :: ColumnData -> ByteString IO () -> (ByteString IO () -> f) -> RawColumn f |
newtype RowResults Source #
Instances
Show RowResults Source # | |
Defined in Database.TDS.Proto showsPrec :: Int -> RowResults -> ShowS # show :: RowResults -> String # showList :: [RowResults] -> ShowS # | |
Response RowResults Source # | |
Defined in Database.TDS.Proto type ResponseStreaming RowResults :: StreamType Source # | |
type ResponseStreaming RowResults Source # | |
Defined in Database.TDS.Proto |
Splitting packets
data SplitEncoding sender resp pld Source #
LastPacket (Ptr () -> IO CSize) | |
OnePacket (Ptr () -> IO (Packet sender resp pld (SplitEncoding sender resp))) |
type SplitPacket sender resp pld = Packet sender resp pld (SplitEncoding sender resp) Source #
splitPacket :: CSize -> Packet Client resp d PacketEncoding -> (Maybe CSize, SplitPacket Client resp d) Source #