| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Database.Selda.SqlType
Description
Types representable as columns in Selda's subset of SQL.
Synopsis
- class Typeable a => SqlType a where
- mkLit :: a -> Lit a
- sqlType :: Proxy a -> SqlTypeRep
- fromSql :: SqlValue -> a
- defaultValue :: Lit a
- class (Typeable a, Bounded a, Enum a) => SqlEnum a where
- data Lit a where
- LText :: !Text -> Lit Text
- LInt32 :: !Int32 -> Lit Int32
- LInt64 :: !Int64 -> Lit Int64
- LDouble :: !Double -> Lit Double
- LBool :: !Bool -> Lit Bool
- LDateTime :: !UTCTime -> Lit UTCTime
- LDate :: !Day -> Lit Day
- LTime :: !TimeOfDay -> Lit TimeOfDay
- LJust :: SqlType a => !(Lit a) -> Lit (Maybe a)
- LBlob :: !ByteString -> Lit ByteString
- LNull :: SqlType a => Lit (Maybe a)
- LCustom :: SqlTypeRep -> Lit a -> Lit b
- LUUID :: !UUID -> Lit UUID
- data UUID
- data UUID' a
- data RowID
- data ID a
- data SqlValue where
- data SqlTypeRep
- invalidRowId :: RowID
- isInvalidRowId :: RowID -> Bool
- toRowId :: Int64 -> RowID
- fromRowId :: RowID -> Int64
- fromId :: ID a -> Int64
- toId :: Int64 -> ID a
- invalidId :: ID a
- isInvalidId :: ID a -> Bool
- untyped :: ID a -> RowID
- compLit :: Lit a -> Lit b -> Ordering
- litType :: Lit a -> SqlTypeRep
- sqlDateTimeFormat :: String
- sqlDateFormat :: String
- sqlTimeFormat :: String
- typedUuid :: UUID -> UUID' a
- untypedUuid :: UUID' a -> UUID
Documentation
class Typeable a => SqlType a where Source #
Any datatype representable in (Selda's subset of) SQL.
Minimal complete definition
Nothing
Methods
Create a literal of this type.
sqlType :: Proxy a -> SqlTypeRep Source #
The SQL representation for this type.
fromSql :: SqlValue -> a Source #
Convert an SqlValue into this type.
defaultValue :: Lit a Source #
Default value when using def at this type.
Instances
class (Typeable a, Bounded a, Enum a) => SqlEnum a where Source #
Any type that's bounded, enumerable and has a text representation, and thus representable as a Selda enumerable.
While it would be more efficient to store enumerables as integers, this makes hand-rolled SQL touching the values inscrutable, and will break if the user a) derives Enum and b) changes the order of their constructors. Long-term, this should be implemented in PostgreSQL as a proper enum anyway, which mostly renders the performance argument moot.
An SQL literal.
Constructors
| LText :: !Text -> Lit Text | |
| LInt32 :: !Int32 -> Lit Int32 | |
| LInt64 :: !Int64 -> Lit Int64 | |
| LDouble :: !Double -> Lit Double | |
| LBool :: !Bool -> Lit Bool | |
| LDateTime :: !UTCTime -> Lit UTCTime | |
| LDate :: !Day -> Lit Day | |
| LTime :: !TimeOfDay -> Lit TimeOfDay | |
| LJust :: SqlType a => !(Lit a) -> Lit (Maybe a) | |
| LBlob :: !ByteString -> Lit ByteString | |
| LNull :: SqlType a => Lit (Maybe a) | |
| LCustom :: SqlTypeRep -> Lit a -> Lit b | |
| LUUID :: !UUID -> Lit UUID |
Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.
Instances
| Data UUID | |
Defined in Data.UUID.Types.Internal Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID # dataTypeOf :: UUID -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UUID) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) # gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r # gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID # | |
| Storable UUID | This |
Defined in Data.UUID.Types.Internal | |
| Read UUID | |
| Show UUID | Pretty prints a
|
| Binary UUID | This |
| NFData UUID | |
Defined in Data.UUID.Types.Internal | |
| Eq UUID | |
| Ord UUID | |
| Hashable UUID | |
Defined in Data.UUID.Types.Internal | |
| Random UUID | This |
| Uniform UUID | |
Defined in Data.UUID.Types.Internal Methods uniformM :: StatefulGen g m => g -> m UUID # | |
| IsUUID UUID Source # | |
| SqlType UUID Source # |
|
| Lift UUID | |
An UUID identifying a database row.
Instances
| Generic (UUID' a) Source # | |
| Show (UUID' a) Source # | |
| Eq (UUID' a) Source # | |
| Ord (UUID' a) Source # | |
Defined in Database.Selda.SqlType | |
| IsUUID (UUID' a) Source # | |
| Typeable a => SqlType (UUID' a) Source # |
|
| type Rep (UUID' a) Source # | |
Defined in Database.Selda.SqlType | |
A row identifier for some table. This is the type of auto-incrementing primary keys.
A typed row identifier.
Generic tables should use this instead of RowID.
Use untyped to erase the type of a row identifier, and cast from the
Database.Selda.Unsafe module if you for some reason need to add a type
to a row identifier.
Some value that is representable in SQL.
Constructors
| SqlInt32 :: !Int32 -> SqlValue | |
| SqlInt64 :: !Int64 -> SqlValue | |
| SqlFloat :: !Double -> SqlValue | |
| SqlString :: !Text -> SqlValue | |
| SqlBool :: !Bool -> SqlValue | |
| SqlBlob :: !ByteString -> SqlValue | |
| SqlUTCTime :: !UTCTime -> SqlValue | |
| SqlTime :: !TimeOfDay -> SqlValue | |
| SqlDate :: !Day -> SqlValue | |
| SqlNull :: SqlValue |
data SqlTypeRep Source #
Representation of an SQL type.
Instances
| Show SqlTypeRep Source # | |
Defined in Database.Selda.SqlType Methods showsPrec :: Int -> SqlTypeRep -> ShowS # show :: SqlTypeRep -> String # showList :: [SqlTypeRep] -> ShowS # | |
| Eq SqlTypeRep Source # | |
Defined in Database.Selda.SqlType | |
| Ord SqlTypeRep Source # | |
Defined in Database.Selda.SqlType Methods compare :: SqlTypeRep -> SqlTypeRep -> Ordering # (<) :: SqlTypeRep -> SqlTypeRep -> Bool # (<=) :: SqlTypeRep -> SqlTypeRep -> Bool # (>) :: SqlTypeRep -> SqlTypeRep -> Bool # (>=) :: SqlTypeRep -> SqlTypeRep -> Bool # max :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # min :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # | |
invalidRowId :: RowID Source #
A row identifier which is guaranteed to not match any row in any table.
isInvalidRowId :: RowID -> Bool Source #
Is the given row identifier invalid? I.e. is it guaranteed to not match any row in any table?
toRowId :: Int64 -> RowID Source #
Create a row identifier from an integer. Use with caution, preferably only when reading user input.
fromId :: ID a -> Int64 Source #
Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.
toId :: Int64 -> ID a Source #
Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.
A typed row identifier which is guaranteed to not match any row in any table.
isInvalidId :: ID a -> Bool Source #
Is the given typed row identifier invalid? I.e. is it guaranteed to not match any row in any table?
litType :: Lit a -> SqlTypeRep Source #
The SQL type representation for the given literal.
sqlDateTimeFormat :: String Source #
Format string used to represent date and time when
representing timestamps as text.
If at all possible, use SqlUTCTime instead.
sqlDateFormat :: String Source #
Format string used to represent date when
representing dates as text.
If at all possible, use SqlDate instead.
sqlTimeFormat :: String Source #
Format string used to represent time of day when
representing time as text.
If at all possible, use SqlTime instead.
typedUuid :: UUID -> UUID' a Source #
Convert an untyped UUID to a typed one. Use sparingly, preferably only during deserialization.
untypedUuid :: UUID' a -> UUID Source #