selda-0.3.4.0: Multi-backend, high-level EDSL for interacting with SQL databases.

Safe HaskellSafe
LanguageHaskell2010

Database.Selda.SqlType

Description

Types representable as columns in Selda's subset of SQL.

Synopsis

Documentation

class Typeable a => SqlType a where Source #

Any datatype representable in (Selda's subset of) SQL.

Methods

mkLit :: a -> Lit a Source #

Create a literal of this type.

mkLit :: (Typeable a, SqlEnum a) => a -> Lit a Source #

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.

fromSql :: (Typeable a, SqlEnum a) => SqlValue -> a Source #

Convert an SqlValue into this type.

defaultValue :: Lit a Source #

Default value when using def at this type.

defaultValue :: (Typeable a, SqlEnum a) => Lit a Source #

Default value when using def at this type.

Instances
SqlType Bool Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Double Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Int Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Ordering Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType a => SqlType (Maybe a) Source # 
Instance details

Defined in Database.Selda.SqlType

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

((TypeError (((Text "'Only " :<>: ShowType a) :<>: Text "' is not a proper SQL type.") :$$: Text "Use 'the' to access the value of the column.") :: Constraint), Typeable a) => SqlType (Only a) Source # 
Instance details

Defined in Database.Selda

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.

Minimal complete definition

toText, fromText

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances
(Typeable a, Bounded a, Enum a, Show a, Read a) => SqlEnum a Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

data Lit a where Source #

An SQL literal.

Constructors

LText :: !Text -> Lit Text 
LInt :: !Int -> Lit Int 
LDouble :: !Double -> Lit Double 
LBool :: !Bool -> Lit Bool 
LDateTime :: !Text -> Lit UTCTime 
LDate :: !Text -> Lit Day 
LTime :: !Text -> Lit TimeOfDay 
LJust :: SqlType a => !(Lit a) -> Lit (Maybe a) 
LBlob :: !ByteString -> Lit ByteString 
LNull :: SqlType a => Lit (Maybe a) 
LCustom :: Lit a -> Lit b 
Instances
Eq (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: Lit a -> Lit a -> Bool #

(/=) :: Lit a -> Lit a -> Bool #

Ord (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: Lit a -> Lit a -> Ordering #

(<) :: Lit a -> Lit a -> Bool #

(<=) :: Lit a -> Lit a -> Bool #

(>) :: Lit a -> Lit a -> Bool #

(>=) :: Lit a -> Lit a -> Bool #

max :: Lit a -> Lit a -> Lit a #

min :: Lit a -> Lit a -> Lit a #

Show (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> Lit a -> ShowS #

show :: Lit a -> String #

showList :: [Lit a] -> ShowS #

Hashable (Lit a) # 
Instance details

Defined in Database.Selda.Caching

Methods

hashWithSalt :: Int -> Lit a -> Int #

hash :: Lit a -> Int #

data RowID Source #

A row identifier for some table. This is the type of auto-incrementing primary keys.

Instances
Eq RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: RowID -> RowID -> Bool #

(/=) :: RowID -> RowID -> Bool #

Ord RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: RowID -> RowID -> Ordering #

(<) :: RowID -> RowID -> Bool #

(<=) :: RowID -> RowID -> Bool #

(>) :: RowID -> RowID -> Bool #

(>=) :: RowID -> RowID -> Bool #

max :: RowID -> RowID -> RowID #

min :: RowID -> RowID -> RowID #

Show RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> RowID -> ShowS #

show :: RowID -> String #

showList :: [RowID] -> ShowS #

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

data ID a Source #

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.

Instances
Eq (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: ID a -> ID a -> Bool #

(/=) :: ID a -> ID a -> Bool #

Ord (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: ID a -> ID a -> Ordering #

(<) :: ID a -> ID a -> Bool #

(<=) :: ID a -> ID a -> Bool #

(>) :: ID a -> ID a -> Bool #

(>=) :: ID a -> ID a -> Bool #

max :: ID a -> ID a -> ID a #

min :: ID a -> ID a -> ID a #

Show (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> ID a -> ShowS #

show :: ID a -> String #

showList :: [ID a] -> ShowS #

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Typeable a => SqlOrd (ID a) Source # 
Instance details

Defined in Database.Selda

data SqlValue where Source #

Some value that is representable in SQL.

Instances
Show SqlValue Source # 
Instance details

Defined in Database.Selda.SqlType

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 :: Int -> RowID Source #

Create a row identifier from an integer. Use with caution, preferably only when reading user input.

fromRowId :: RowID -> Int Source #

Inspect a row identifier.

fromId :: ID a -> Int Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

toId :: Int -> ID a Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

invalidId :: ID a Source #

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?

compLit :: Lit a -> Lit b -> Ordering Source #

Compare two literals of different type for equality.

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 talking to the database backend.

sqlDateFormat :: String Source #

Format string used to represent date when talking to the database backend.

sqlTimeFormat :: String Source #

Format string used to represent time of day when talking to the database backend.