mysql-haskell-0.8.3.0: pure haskell MySQL driver

Copyright(c) Winterland 2016
LicenseBSD
Maintainerdrkoster@qq.com
Stabilityexperimental
PortabilityPORTABLE
Safe HaskellNone
LanguageHaskell2010

Database.MySQL.Protocol.MySQLValue

Contents

Description

Core text and binary row decoder/encoder machinery.

Synopsis

MySQLValue decoder and encoder

data MySQLValue Source #

Data type mapping between MySQL values and haskell values.

There're some subtle differences between MySQL values and haskell values:

MySQL's DATETIME and TIMESTAMP are different on timezone handling:

  • DATETIME and DATE is just a represent of a calendar date, it has no timezone information involved, you always get the same value as you put no matter what timezone you're using with MySQL.
  • MySQL converts TIMESTAMP values from the current time zone to UTC for storage, and back from UTC to the current time zone for retrieval. If you put a TIMESTAMP with timezone A, then read it with timezone B, you may get different result because of this conversion, so always be careful about setting up the right timezone with MySQL, you can do it with a simple SET time_zone = timezone; for more info on timezone support, please read http://dev.mysql.com/doc/refman/5.7/en/time-zone-support.html

So we use LocalTime to present both DATETIME and TIMESTAMP, but the local here is different.

MySQL's TIME type can present time of day, but also elapsed time or a time interval between two events. TIME values may range from -838:59:59 to 838:59:59, so MySQLTime values consist of a sign and a TimeOfDay whose hour part may exceeded 24. you can use timeOfDayToTime to get the absolute time interval.

Under MySQL >= 5.7, DATETIME, TIMESTAMP and TIME may contain fractional part, which matches haskell's precision.

Constructors

MySQLDecimal !Scientific

DECIMAL, NEWDECIMAL

MySQLInt8U !Word8

Unsigned TINY

MySQLInt8 !Int8

TINY

MySQLInt16U !Word16

Unsigned SHORT

MySQLInt16 !Int16

SHORT

MySQLInt32U !Word32

Unsigned LONG, INT24

MySQLInt32 !Int32

LONG, INT24

MySQLInt64U !Word64

Unsigned LONGLONG

MySQLInt64 !Int64

LONGLONG

MySQLFloat !Float

IEEE 754 single precision format

MySQLDouble !Double

IEEE 754 double precision format

MySQLYear !Word16

YEAR

MySQLDateTime !LocalTime

DATETIME

MySQLTimeStamp !LocalTime

TIMESTAMP

MySQLDate !Day

DATE

MySQLTime !Word8 !TimeOfDay

sign(0 = non-negative, 1 = negative) hh mm ss microsecond The sign is OPPOSITE to binlog one !!!

MySQLGeometry !ByteString

todo: parsing to something meanful

MySQLBytes !ByteString 
MySQLBit !Word64 
MySQLText !Text 
MySQLNull 

Instances

Eq MySQLValue Source # 
Show MySQLValue Source # 
Generic MySQLValue Source # 

Associated Types

type Rep MySQLValue :: * -> * #

QueryParam MySQLValue Source # 
type Rep MySQLValue Source # 
type Rep MySQLValue = D1 (MetaData "MySQLValue" "Database.MySQL.Protocol.MySQLValue" "mysql-haskell-0.8.3.0-JbYWjFKnjUp1c6jpYEZp3B" False) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MySQLDecimal" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Scientific))) (C1 (MetaCons "MySQLInt8U" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)))) ((:+:) (C1 (MetaCons "MySQLInt8" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int8))) ((:+:) (C1 (MetaCons "MySQLInt16U" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16))) (C1 (MetaCons "MySQLInt16" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int16)))))) ((:+:) ((:+:) (C1 (MetaCons "MySQLInt32U" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word32))) (C1 (MetaCons "MySQLInt32" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int32)))) ((:+:) (C1 (MetaCons "MySQLInt64U" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64))) ((:+:) (C1 (MetaCons "MySQLInt64" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64))) (C1 (MetaCons "MySQLFloat" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Float))))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "MySQLDouble" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double))) (C1 (MetaCons "MySQLYear" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word16)))) ((:+:) (C1 (MetaCons "MySQLDateTime" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LocalTime))) ((:+:) (C1 (MetaCons "MySQLTimeStamp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LocalTime))) (C1 (MetaCons "MySQLDate" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Day)))))) ((:+:) ((:+:) (C1 (MetaCons "MySQLTime" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TimeOfDay)))) ((:+:) (C1 (MetaCons "MySQLGeometry" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))) (C1 (MetaCons "MySQLBytes" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))))) ((:+:) (C1 (MetaCons "MySQLBit" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word64))) ((:+:) (C1 (MetaCons "MySQLText" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) (C1 (MetaCons "MySQLNull" PrefixI False) U1))))))

putParamMySQLType :: MySQLValue -> Put Source #

Put FieldType and usigned bit(0x80/0x00) for MySQLValues.

getTextField :: ColumnDef -> Get MySQLValue Source #

Text protocol decoder

putTextField :: MySQLValue -> Put Source #

Text protocol encoder

getTextRow :: [ColumnDef] -> Get [MySQLValue] Source #

Text row decoder

getBinaryField :: ColumnDef -> Get MySQLValue Source #

Binary protocol decoder

putBinaryField :: MySQLValue -> Put Source #

Binary protocol encoder

getBinaryRow :: [ColumnDef] -> Int -> Get [MySQLValue] Source #

Binary row decoder

MySQL use a special null bitmap without offset = 2 here.

Internal utilities

getBits :: Int -> Get Word64 Source #

Get a bit sequence as a Word64

Since Word64 has a Bits instance, it's easier to deal with in haskell.

newtype BitMap Source #

Use ByteString to present a bitmap.

When used for represent bits values, the underlining ByteString follows:

  • byteString: head -> tail
  • bit: high bit -> low bit

When used as a null-map/present-map, every bit inside a byte is mapped to a column, the mapping order is following:

  • byteString: head -> tail
  • column: left -> right

We don't use Int64 here because there maybe more than 64 columns.

Constructors

BitMap 

Instances

isColumnSet :: BitMap -> Int -> Bool Source #

Test if a column is set(binlog protocol).

The number counts from left to right.

isColumnNull :: BitMap -> Int -> Bool Source #

Test if a column is null(binary protocol).

The number counts from left to right.

makeNullMap :: [MySQLValue] -> BitMap Source #

Make a nullmap for params(binary protocol) without offset.