Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Database.DuckDB.Simple.FromField
Description
Synopsis
- data Field = Field {
- fieldName :: Text
- fieldIndex :: Int
- fieldValue :: FieldValue
- data FieldValue
- = FieldNull
- | FieldInt8 Int8
- | FieldInt16 Int16
- | FieldInt32 Int32
- | FieldInt64 Int64
- | FieldWord8 Word8
- | FieldWord16 Word16
- | FieldWord32 Word32
- | FieldWord64 Word64
- | FieldUUID UUID
- | FieldFloat Float
- | FieldDouble Double
- | FieldText Text
- | FieldBool Bool
- | FieldBlob ByteString
- | FieldDate Day
- | FieldTime TimeOfDay
- | FieldTimestamp LocalTime
- | FieldInterval IntervalValue
- | FieldHugeInt Integer
- | FieldUHugeInt Integer
- | FieldDecimal DecimalValue
- | FieldTimestampTZ UTCTime
- | FieldTimeTZ TimeWithZone
- | FieldBit BitString
- | FieldBigNum BigNum
- | FieldEnum Word32
- | FieldList [FieldValue]
- | FieldMap [(FieldValue, FieldValue)]
- data BitString = BitString {
- padding :: !Word8
- bits :: !ByteString
- bsFromBool :: [Bool] -> BitString
- newtype BigNum = BigNum Integer
- fromBigNumBytes :: [Word8] -> Integer
- toBigNumBytes :: Integer -> [Word8]
- data DecimalValue = DecimalValue {
- decimalWidth :: !Word8
- decimalScale :: !Word8
- decimalInteger :: !Integer
- data IntervalValue = IntervalValue {
- intervalMonths :: !Int32
- intervalDays :: !Int32
- intervalMicros :: !Int64
- data TimeWithZone = TimeWithZone {}
- data ResultError
- = Incompatible {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- | UnexpectedNull {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- | ConversionFailed {
- errSQLType :: Text
- errSQLField :: Text
- errHaskellType :: Text
- errMessage :: Text
- = Incompatible {
- type FieldParser a = Field -> Ok a
- class FromField a where
- fromField :: FieldParser a
- returnError :: forall b. Typeable b => (Text -> Text -> Text -> Text -> ResultError) -> Field -> Text -> Ok b
Documentation
Metadata for a single column in a row.
Constructors
Field | |
Fields
|
Instances
data FieldValue Source #
Internal representation of a column value.
Constructors
Instances
Show FieldValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> FieldValue -> ShowS # show :: FieldValue -> String # showList :: [FieldValue] -> ShowS # | |
FromField FieldValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
Eq FieldValue Source # | |
Defined in Database.DuckDB.Simple.FromField |
Constructors
BitString | |
Fields
|
Instances
Show BitString Source # | |
FromField BitString Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
DuckDBColumnType BitString Source # | |
Defined in Database.DuckDB.Simple.ToField | |
ToField BitString Source # | |
Defined in Database.DuckDB.Simple.ToField Methods toField :: BitString -> FieldBinding Source # | |
Eq BitString Source # | |
bsFromBool :: [Bool] -> BitString Source #
Instances
Num BigNum Source # | |
Show BigNum Source # | |
FromField BigNum Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
DuckDBColumnType BigNum Source # | |
Defined in Database.DuckDB.Simple.ToField | |
ToField BigNum Source # | |
Defined in Database.DuckDB.Simple.ToField Methods toField :: BigNum -> FieldBinding Source # | |
Eq BigNum Source # | |
fromBigNumBytes :: [Word8] -> Integer Source #
Decode DuckDB’s BIGNUM blob (3-byte header + big-endian payload where negative magnitudes are
bitwise complemented) back into a Haskell Integer
. We undo the complement when needed, then chunk
the remaining bytes into machine-word limbs (MSB chunk first) for integerFromWordList
.
toBigNumBytes :: Integer -> [Word8] Source #
Encode an Integer
into DuckDB’s BIGNUM blob layout: emit the 3-byte header
(sign bit plus payload length) followed by the magnitude bytes in the same
big-endian / complemented-on-negative form that DuckDB stores internally.
data DecimalValue Source #
Constructors
DecimalValue | |
Fields
|
Instances
Show DecimalValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> DecimalValue -> ShowS # show :: DecimalValue -> String # showList :: [DecimalValue] -> ShowS # | |
FromField DecimalValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
Eq DecimalValue Source # | |
Defined in Database.DuckDB.Simple.FromField |
data IntervalValue Source #
Constructors
IntervalValue | |
Fields
|
Instances
Show IntervalValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> IntervalValue -> ShowS # show :: IntervalValue -> String # showList :: [IntervalValue] -> ShowS # | |
FromField IntervalValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
Eq IntervalValue Source # | |
Defined in Database.DuckDB.Simple.FromField Methods (==) :: IntervalValue -> IntervalValue -> Bool # (/=) :: IntervalValue -> IntervalValue -> Bool # |
data TimeWithZone Source #
Constructors
TimeWithZone | |
Fields |
Instances
Show TimeWithZone Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> TimeWithZone -> ShowS # show :: TimeWithZone -> String # showList :: [TimeWithZone] -> ShowS # | |
FromField TimeWithZone Source # | |
Defined in Database.DuckDB.Simple.FromField Methods | |
Eq TimeWithZone Source # | |
Defined in Database.DuckDB.Simple.FromField |
data ResultError Source #
Exception thrown if conversion from a SQL value to a Haskell value fails.
Constructors
Incompatible | The SQL and Haskell types are not compatible. |
Fields
| |
UnexpectedNull | A SQL |
Fields
| |
ConversionFailed | The SQL value could not be parsed, or could not be represented as a valid Haskell value, or an unexpected low-level error occurred (e.g. mismatch between metadata and actual data in a row). |
Fields
|
Instances
Exception ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField Methods toException :: ResultError -> SomeException # fromException :: SomeException -> Maybe ResultError # displayException :: ResultError -> String # | |
Show ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField Methods showsPrec :: Int -> ResultError -> ShowS # show :: ResultError -> String # showList :: [ResultError] -> ShowS # | |
Eq ResultError Source # | |
Defined in Database.DuckDB.Simple.FromField |
type FieldParser a = Field -> Ok a Source #
Parser used by FromField
instances and utilities such as
fieldWith
. The supplied Field
contains
column metadata and an already-decoded FieldValue
; callers should return
Ok
on success or Errors
(typically wrapping a ResultError
) when the
conversion fails.
class FromField a where Source #
Types that can be constructed from a DuckDB column.
Methods
fromField :: FieldParser a Source #