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

Safe HaskellNone
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.

Minimal complete definition

Nothing

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 UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

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.

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 :: !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 
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 #

data UUID #

The UUID type. A Random instance is provided which produces version 4 UUIDs as specified in RFC 4122. The Storable and Binary instances are compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instances
Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

Data UUID 
Instance details

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 #

toConstr :: UUID -> Constr #

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 :: (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 #

Ord UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

compare :: UUID -> UUID -> Ordering #

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

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

(>) :: UUID -> UUID -> Bool #

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Read UUID 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Storable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

peekElemOff :: Ptr UUID -> Int -> IO UUID #

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UUID #

pokeByteOff :: Ptr b -> Int -> UUID -> IO () #

peek :: Ptr UUID -> IO UUID #

poke :: Ptr UUID -> UUID -> IO () #

Binary UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

randomRIO :: (UUID, UUID) -> IO UUID #

randomIO :: IO UUID #

SqlType UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

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 #

Generic RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep RowID :: Type -> Type #

Methods

from :: RowID -> Rep RowID x #

to :: Rep RowID x -> RowID #

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

type Rep RowID Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep RowID = D1 (MetaData "RowID" "Database.Selda.SqlType" "selda-0.5.0.0-9689aUoAmdW4Xy6C3mKwDZ" True) (C1 (MetaCons "RowID" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))

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 #

Generic (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (ID a) :: Type -> Type #

Methods

from :: ID a -> Rep (ID a) x #

to :: Rep (ID a) x -> ID a #

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

type Rep (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (ID a) = D1 (MetaData "ID" "Database.Selda.SqlType" "selda-0.5.0.0-9689aUoAmdW4Xy6C3mKwDZ" True) (C1 (MetaCons "ID" PrefixI True) (S1 (MetaSel (Just "untyped") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RowID)))

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 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.