| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.Tds.Message
Synopsis
- data ClientMessage
- getClientMessage :: Get ClientMessage
- putClientMessage :: Word32 -> ClientMessage -> Put
- data Login7
- tdsVersion :: Word32
- defaultLogin7 :: Login7
- l7PacketSize :: Login7 -> Word32
- l7ClientProgVer :: Login7 -> Word32
- l7ConnectionID :: Login7 -> Word32
- l7OptionFlags1 :: Login7 -> Word8
- l7OptionFlags2 :: Login7 -> Word8
- l7OptionFlags3 :: Login7 -> Word8
- l7TypeFlags :: Login7 -> Word8
- l7TimeZone :: Login7 -> Int32
- l7Collation :: Login7 -> Collation32
- l7CltIntName :: Login7 -> Text
- l7Language :: Login7 -> Text
- l7ClientPID :: Login7 -> Word32
- l7ClientMacAddr :: Login7 -> ByteString
- l7ClientHostName :: Login7 -> Text
- l7AppName :: Login7 -> Text
- l7ServerName :: Login7 -> Text
- l7UserName :: Login7 -> Text
- l7Password :: Login7 -> Text
- l7Database :: Login7 -> Text
- newtype SqlBatch = SqlBatch Text
- newtype RpcRequest = RpcRequest [RpcReqBatch]
- data RpcReqBatch
- type ProcID = Word16
- type ProcName = Text
- type OptionFlags = Word16
- data RpcReqBatchParam = RpcReqBatchParam !ParamName !StatusFlag !TypeInfo !RawBytes
- type ParamName = Text
- type StatusFlag = Word8
- class Binary a => ServerMessage a
- getServerMessage :: ServerMessage a => Get a
- putServerMessage :: ServerMessage a => Word32 -> a -> Put
- newtype TokenStreams = TokenStreams [TokenStream]
- data TokenStream- = TSAltMetaData !AltMetaData
- | TSAltRow !AltRowData
- | TSColInfo ![ColProperty]
- | TSColMetaData !(Maybe ColMetaData)
- | TSDone !Done
- | TSDoneInProc !Done
- | TSDoneProc !Done
- | TSEnvChange !ECType !ECNewValue !ECOldValue
- | TSError !Info
- | TSInfo !Info
- | TSLoginAck !LAInterface !LATdsVersion !LAProgName !LAProgVersion
- | TSOffset !Offset
- | TSOrder ![Word16]
- | TSReturnStatus !Int32
- | TSReturnValue !ReturnValue
- | TSRow ![RowColumnData]
- | TSSSPI !ByteString
- | TSTabName ![[Text]]
 
- data AltMetaData = AltMetaData
- data AltRowData = AltRowData
- data ColProperty = ColProperty !CPColNum !CPTableNum !CPStatus !(Maybe CPColName)
- type CPColNum = Word8
- type CPTableNum = Word8
- type CPStatus = Word8
- type CPColName = Text
- data ColMetaData = ColMetaData ![MetaColumnData]
- data MetaColumnData = MetaColumnData !MCDUserType !MCDFlags !TypeInfo !(Maybe MCDTableName) !MCDColName
- type MCDUserType = Word16
- type MCDFlags = Word16
- type MCDTableName = Text
- type MCDColName = Text
- data Done = Done !DoneStatus !DoneCurCmd !DoneRowCount
- type DoneStatus = Word16
- type DoneCurCmd = Word16
- type DoneRowCount = Int32
- type ECType = Word8
- type ECNewValue = ByteString
- type ECOldValue = ByteString
- data Info = Info !InfoNumber !InfoState !InfoClass !InfoMsgText !InfoServerName !InfoProcName !InfoLineNumber
- type InfoNumber = Int32
- type InfoState = Word8
- type InfoClass = Word8
- type InfoMsgText = Text
- type InfoServerName = Text
- type InfoProcName = Text
- type InfoLineNumber = Word16
- type LAInterface = Word8
- type LATdsVersion = Word32
- type LAProgName = Text
- type LAProgVersion = Word32
- type OffsetIdentifier = Word16
- type OffsetLength = Word16
- data Offset = Offset !OffsetIdentifier !OffsetLength
- data ReturnValue = ReturnValue !RVParamOrdinal !RVParamName !RVStatus !RVUserType !RVFlags !TypeInfo !RawBytes
- type RVParamOrdinal = Word16
- type RVParamName = Text
- type RVStatus = Word8
- type RVUserType = Word16
- type RVFlags = Word16
- data RowColumnData- = RCDOrdinal !RawBytes
- | RCDLarge !(Maybe TextPointer) !(Maybe TimeStamp) !RawBytes
 
- type TextPointer = ByteString
- type TimeStamp = Word64
- data TypeInfo- = TINull
- | TIBit
- | TIInt1
- | TIInt2
- | TIInt4
- | TIInt8
- | TIMoney4
- | TIMoney8
- | TIDateTime4
- | TIDateTime8
- | TIFlt4
- | TIFlt8
- | TIBitN
- | TIIntN1
- | TIIntN2
- | TIIntN4
- | TIIntN8
- | TIMoneyN4
- | TIMoneyN8
- | TIDateTimeN4
- | TIDateTimeN8
- | TIFltN4
- | TIFltN8
- | TIGUID
- | TIDecimalN !Precision !Scale
- | TINumericN !Precision !Scale
- | TIChar !Word8
- | TIVarChar !Word8
- | TIBigChar !Word16 !Collation
- | TIBigVarChar !Word16 !Collation
- | TIText !Word32 !Collation
- | TINChar !Word16 !Collation
- | TINVarChar !Word16 !Collation
- | TINText !Word32 !Collation
- | TIBinary !Word8
- | TIVarBinary !Word8
- | TIBigBinary !Word16
- | TIBigVarBinary !Word16
- | TIImage !Word32
 
- type RawBytes = Maybe ByteString
- class Data a where- fromRawBytes :: TypeInfo -> RawBytes -> a
- toRawBytes :: TypeInfo -> a -> RawBytes
 
- data Null = Null
- type Precision = Word8
- type Scale = Word8
- newtype Money = Money Fixed4
- data Collation = Collation !Collation32 !SortId
- type Collation32 = Word32
- type SortId = Word8
- newtype Prelogin = Prelogin [PreloginOption]
- data PreloginOption
- type MajorVer = Word8
- type MinorVer = Word8
- type BuildVer = Word16
- type SubBuildVer = Word16
- type Threadid = Word32
- type Connid = ByteString
- type Activity = ByteString
- type Sequence = Word32
- type Nonce = ByteString
Client Message
data ClientMessage Source #
Constructors
| CMPrelogin !Prelogin | |
| CMLogin7 !Login7 | |
| CMSqlBatch !SqlBatch | |
| CMRpcRequest !RpcRequest | 
Instances
| Show ClientMessage Source # | |
| Defined in Database.Tds.Message Methods showsPrec :: Int -> ClientMessage -> ShowS # show :: ClientMessage -> String # showList :: [ClientMessage] -> ShowS # | |
putClientMessage :: Word32 -> ClientMessage -> Put Source #
Login
tdsVersion :: Word32 Source #
l7PacketSize :: Login7 -> Word32 Source #
l7ClientProgVer :: Login7 -> Word32 Source #
l7ConnectionID :: Login7 -> Word32 Source #
l7OptionFlags1 :: Login7 -> Word8 Source #
l7OptionFlags2 :: Login7 -> Word8 Source #
l7OptionFlags3 :: Login7 -> Word8 Source #
l7TypeFlags :: Login7 -> Word8 Source #
l7TimeZone :: Login7 -> Int32 Source #
l7Collation :: Login7 -> Collation32 Source #
l7CltIntName :: Login7 -> Text Source #
l7Language :: Login7 -> Text Source #
l7ClientPID :: Login7 -> Word32 Source #
l7ClientMacAddr :: Login7 -> ByteString Source #
l7ClientHostName :: Login7 -> Text Source #
l7ServerName :: Login7 -> Text Source #
l7UserName :: Login7 -> Text Source #
l7Password :: Login7 -> Text Source #
l7Database :: Login7 -> Text Source #
SQL Batch
RPC Request
newtype RpcRequest Source #
Constructors
| RpcRequest [RpcReqBatch] | 
Instances
| Show RpcRequest Source # | |
| Defined in Database.Tds.Message.Client Methods showsPrec :: Int -> RpcRequest -> ShowS # show :: RpcRequest -> String # showList :: [RpcRequest] -> ShowS # | |
| Binary RpcRequest Source # | |
| Defined in Database.Tds.Message.Client | |
data RpcReqBatch Source #
Constructors
| RpcReqBatchProcId !ProcID !OptionFlags ![RpcReqBatchParam] | |
| RpcReqBatchProcName !ProcName !OptionFlags ![RpcReqBatchParam] | 
Instances
| Show RpcReqBatch Source # | |
| Defined in Database.Tds.Message.Client Methods showsPrec :: Int -> RpcReqBatch -> ShowS # show :: RpcReqBatch -> String # showList :: [RpcReqBatch] -> ShowS # | |
type OptionFlags = Word16 Source #
data RpcReqBatchParam Source #
Constructors
| RpcReqBatchParam !ParamName !StatusFlag !TypeInfo !RawBytes | 
Instances
| Show RpcReqBatchParam Source # | |
| Defined in Database.Tds.Message.Client Methods showsPrec :: Int -> RpcReqBatchParam -> ShowS # show :: RpcReqBatchParam -> String # showList :: [RpcReqBatchParam] -> ShowS # | |
type StatusFlag = Word8 Source #
Server Message
class Binary a => ServerMessage a Source #
Instances
| ServerMessage Prelogin Source # | |
| Defined in Database.Tds.Message | |
| ServerMessage TokenStreams Source # | |
| Defined in Database.Tds.Message | |
getServerMessage :: ServerMessage a => Get a Source #
putServerMessage :: ServerMessage a => Word32 -> a -> Put Source #
newtype TokenStreams Source #
Constructors
| TokenStreams [TokenStream] | 
Instances
| Show TokenStreams Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> TokenStreams -> ShowS # show :: TokenStreams -> String # showList :: [TokenStreams] -> ShowS # | |
| Binary TokenStreams Source # | |
| Defined in Database.Tds.Message.Server | |
| ServerMessage TokenStreams Source # | |
| Defined in Database.Tds.Message | |
data TokenStream Source #
Constructors
Instances
| Show TokenStream Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> TokenStream -> ShowS # show :: TokenStream -> String # showList :: [TokenStream] -> ShowS # | |
AltMetaData
data AltMetaData Source #
Constructors
| AltMetaData | 
Instances
| Show AltMetaData Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> AltMetaData -> ShowS # show :: AltMetaData -> String # showList :: [AltMetaData] -> ShowS # | |
AltRowData
data AltRowData Source #
Constructors
| AltRowData | 
Instances
| Show AltRowData Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> AltRowData -> ShowS # show :: AltRowData -> String # showList :: [AltRowData] -> ShowS # | |
ColProperty
data ColProperty Source #
Constructors
| ColProperty !CPColNum !CPTableNum !CPStatus !(Maybe CPColName) | 
Instances
| Show ColProperty Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> ColProperty -> ShowS # show :: ColProperty -> String # showList :: [ColProperty] -> ShowS # | |
type CPTableNum = Word8 Source #
ColMetaData
data ColMetaData Source #
Constructors
| ColMetaData ![MetaColumnData] | 
Instances
| Show ColMetaData Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> ColMetaData -> ShowS # show :: ColMetaData -> String # showList :: [ColMetaData] -> ShowS # | |
data MetaColumnData Source #
Constructors
| MetaColumnData !MCDUserType !MCDFlags !TypeInfo !(Maybe MCDTableName) !MCDColName | 
Instances
| Show MetaColumnData Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> MetaColumnData -> ShowS # show :: MetaColumnData -> String # showList :: [MetaColumnData] -> ShowS # | |
type MCDUserType = Word16 Source #
type MCDTableName = Text Source #
type MCDColName = Text Source #
Done, DoneInProc, DoneProc
Constructors
| Done !DoneStatus !DoneCurCmd !DoneRowCount | 
type DoneStatus = Word16 Source #
type DoneCurCmd = Word16 Source #
type DoneRowCount = Int32 Source #
EnvChange
type ECNewValue = ByteString Source #
type ECOldValue = ByteString Source #
Error, Info
Constructors
| Info !InfoNumber !InfoState !InfoClass !InfoMsgText !InfoServerName !InfoProcName !InfoLineNumber | 
type InfoNumber = Int32 Source #
type InfoMsgText = Text Source #
type InfoServerName = Text Source #
type InfoProcName = Text Source #
type InfoLineNumber = Word16 Source #
LoginAck
type LAInterface = Word8 Source #
type LATdsVersion = Word32 Source #
type LAProgName = Text Source #
type LAProgVersion = Word32 Source #
Offset
type OffsetIdentifier = Word16 Source #
type OffsetLength = Word16 Source #
Constructors
| Offset !OffsetIdentifier !OffsetLength | 
ReturnValue
data ReturnValue Source #
Constructors
| ReturnValue !RVParamOrdinal !RVParamName !RVStatus !RVUserType !RVFlags !TypeInfo !RawBytes | 
Instances
| Show ReturnValue Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> ReturnValue -> ShowS # show :: ReturnValue -> String # showList :: [ReturnValue] -> ShowS # | |
type RVParamOrdinal = Word16 Source #
type RVParamName = Text Source #
type RVUserType = Word16 Source #
Row
data RowColumnData Source #
Constructors
| RCDOrdinal !RawBytes | |
| RCDLarge !(Maybe TextPointer) !(Maybe TimeStamp) !RawBytes | 
Instances
| Show RowColumnData Source # | |
| Defined in Database.Tds.Message.Server Methods showsPrec :: Int -> RowColumnData -> ShowS # show :: RowColumnData -> String # showList :: [RowColumnData] -> ShowS # | |
type TextPointer = ByteString Source #
Primitives
Constructors
type RawBytes = Maybe ByteString Source #
Methods
fromRawBytes :: TypeInfo -> RawBytes -> a Source #
toRawBytes :: TypeInfo -> a -> RawBytes Source #
Instances
Constructors
| Null | 
Constructors
| Collation !Collation32 !SortId | 
type Collation32 = Word32 Source #
Prelogin
Constructors
| Prelogin [PreloginOption] | 
data PreloginOption Source #
Constructors
Instances
| Show PreloginOption Source # | |
| Defined in Database.Tds.Message.Prelogin Methods showsPrec :: Int -> PreloginOption -> ShowS # show :: PreloginOption -> String # showList :: [PreloginOption] -> ShowS # | |
type SubBuildVer = Word16 Source #
type Connid = ByteString Source #
type Activity = ByteString Source #
type Nonce = ByteString Source #