| Copyright | (c) Eitan Chatav 2010 |
|---|---|
| Maintainer | eitan@morphism.tech |
| Stability | experimental |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Squeal.PostgreSQL.Type
Contents
Description
storage newtypes
Synopsis
- newtype Money = Money {}
- newtype Json hask = Json {
- getJson :: hask
- newtype Jsonb hask = Jsonb {
- getJsonb :: hask
- newtype Composite record = Composite {
- getComposite :: record
- newtype Enumerated enum = Enumerated {
- getEnumerated :: enum
- newtype VarArray arr = VarArray {
- getVarArray :: arr
- newtype FixArray arr = FixArray {
- getFixArray :: arr
- data VarChar (n :: Nat)
- varChar :: forall n. KnownNat n => Text -> Maybe (VarChar n)
- getVarChar :: VarChar n -> Text
- data FixChar (n :: Nat)
- fixChar :: forall n. KnownNat n => Text -> Maybe (FixChar n)
- getFixChar :: FixChar n -> Text
- newtype Only x = Only {
- fromOnly :: x
Storage newtypes
The Money newtype stores a monetary value in terms
of the number of cents, i.e. $2,000.20 would be expressed as
Money { cents = 200020 }.
>>>:kind! PG MoneyPG Money :: PGType = 'PGmoney
Instances
| Generic Money Source # | |
| Read Money Source # | |
| Show Money Source # | |
| Generic Money Source # | |
| HasDatatypeInfo Money Source # | |
Defined in Squeal.PostgreSQL.Type Associated Types type DatatypeInfoOf Money :: DatatypeInfo # Methods datatypeInfo :: proxy Money -> DatatypeInfo (Code Money) # | |
| Eq Money Source # | |
| Ord Money Source # | |
| Inline Money Source # | |
| FromPG Money Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
| IsPG Money Source # | |
| ToPG db Money Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
| type Rep Money Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type Code Money Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type DatatypeInfoOf Money Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type PG Money Source # | |
Defined in Squeal.PostgreSQL.Type.PG | |
The Json newtype is an indication that the Haskell
type it's applied to should be stored as a
PGjson.
>>>:kind! PG (Json [String])PG (Json [String]) :: PGType = 'PGjson
Instances
| ToJSON x => ToPG db (Json x) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
| Generic (Json hask) Source # | |
| Read hask => Read (Json hask) Source # | |
| Show hask => Show (Json hask) Source # | |
| Generic (Json hask) Source # | |
| HasDatatypeInfo (Json hask) Source # | |
Defined in Squeal.PostgreSQL.Type Associated Types type DatatypeInfoOf (Json hask) :: DatatypeInfo # Methods datatypeInfo :: proxy (Json hask) -> DatatypeInfo (Code (Json hask)) # | |
| Eq hask => Eq (Json hask) Source # | |
| Ord hask => Ord (Json hask) Source # | |
| ToJSON x => Inline (Json x) Source # | |
| FromJSON x => FromPG (Json x) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
| IsPG (Json hask) Source # | |
| type Rep (Json hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type Code (Json hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type DatatypeInfoOf (Json hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type PG (Json hask) Source # | |
Defined in Squeal.PostgreSQL.Type.PG | |
The Jsonb newtype is an indication that the Haskell
type it's applied to should be stored as a
PGjsonb.
>>>:kind! PG (Jsonb [String])PG (Jsonb [String]) :: PGType = 'PGjsonb
Instances
| ToJSON x => ToPG db (Jsonb x) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
| Generic (Jsonb hask) Source # | |
| Read hask => Read (Jsonb hask) Source # | |
| Show hask => Show (Jsonb hask) Source # | |
| Generic (Jsonb hask) Source # | |
| HasDatatypeInfo (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type Associated Types type DatatypeInfoOf (Jsonb hask) :: DatatypeInfo # Methods datatypeInfo :: proxy (Jsonb hask) -> DatatypeInfo (Code (Jsonb hask)) # | |
| Eq hask => Eq (Jsonb hask) Source # | |
| Ord hask => Ord (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| ToJSON x => Inline (Jsonb x) Source # | |
| FromJSON x => FromPG (Jsonb x) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
| IsPG (Jsonb hask) Source # | |
| type Rep (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type Code (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type DatatypeInfoOf (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type PG (Jsonb hask) Source # | |
Defined in Squeal.PostgreSQL.Type.PG | |
newtype Composite record Source #
The Composite newtype is an indication that the Haskell
type it's applied to should be stored as a
PGcomposite.
>>>:{data Complex = Complex { real :: Double , imaginary :: Double } deriving stock GHC.Generic deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo) :}
>>>:kind! PG (Composite Complex)PG (Composite Complex) :: PGType = 'PGcomposite '["real" ::: 'NotNull 'PGfloat8, "imaginary" ::: 'NotNull 'PGfloat8]
Constructors
| Composite | |
Fields
| |
Instances
newtype Enumerated enum Source #
The Enumerated newtype is an indication that the Haskell
type it's applied to should be stored as a
PGenum.
>>>:kind! PG (Enumerated Ordering)PG (Enumerated Ordering) :: PGType = 'PGenum '["LT", "EQ", "GT"]
Constructors
| Enumerated | |
Fields
| |
Instances
The VarArray newtype is an indication that the Haskell
type it's applied to should be stored as a
PGvararray.
>>>import Data.Vector>>>:kind! PG (VarArray (Vector Double))PG (VarArray (Vector Double)) :: PGType = 'PGvararray ('NotNull 'PGfloat8)
Constructors
| VarArray | |
Fields
| |
Instances
The FixArray newtype is an indication that the Haskell
type it's applied to should be stored as a
PGfixarray.
>>>:kind! PG (FixArray ((Double, Double), (Double, Double)))PG (FixArray ((Double, Double), (Double, Double))) :: PGType = 'PGfixarray '[2, 2] ('NotNull 'PGfloat8)
Constructors
| FixArray | |
Fields
| |
Instances
data VarChar (n :: Nat) Source #
Variable-length text type with limit
>>>:kind! PG (VarChar 4)PG (VarChar 4) :: PGType = 'PGvarchar 4
Instances
| ToPG db (VarChar n) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
| Read (VarChar n) Source # | |
| Show (VarChar n) Source # | |
| Eq (VarChar n) Source # | |
| Ord (VarChar n) Source # | |
| (KnownNat n, 1 <= n) => Inline (VarChar n) Source # | |
| KnownNat n => FromPG (VarChar n) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
| IsPG (VarChar n) Source # | |
| type PG (VarChar n) Source # | |
Defined in Squeal.PostgreSQL.Type.PG | |
data FixChar (n :: Nat) Source #
Fixed-length, blank padded
>>>:kind! PG (FixChar 4)PG (FixChar 4) :: PGType = 'PGchar 4
Instances
| ToPG db (FixChar n) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
| Read (FixChar n) Source # | |
| Show (FixChar n) Source # | |
| Eq (FixChar n) Source # | |
| Ord (FixChar n) Source # | |
| (KnownNat n, 1 <= n) => Inline (FixChar n) Source # | |
| KnownNat n => FromPG (FixChar n) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
| IsPG (FixChar n) Source # | |
| type PG (FixChar n) Source # | |
Defined in Squeal.PostgreSQL.Type.PG | |
Only is a 1-tuple type, useful for encoding or decoding a singleton
Instances
| Foldable Only Source # | |
Defined in Squeal.PostgreSQL.Type Methods fold :: Monoid m => Only m -> m # foldMap :: Monoid m => (a -> m) -> Only a -> m # foldMap' :: Monoid m => (a -> m) -> Only a -> m # foldr :: (a -> b -> b) -> b -> Only a -> b # foldr' :: (a -> b -> b) -> b -> Only a -> b # foldl :: (b -> a -> b) -> b -> Only a -> b # foldl' :: (b -> a -> b) -> b -> Only a -> b # foldr1 :: (a -> a -> a) -> Only a -> a # foldl1 :: (a -> a -> a) -> Only a -> a # elem :: Eq a => a -> Only a -> Bool # maximum :: Ord a => Only a -> a # | |
| Traversable Only Source # | |
| Functor Only Source # | |
| Generic (Only x) Source # | |
| Read x => Read (Only x) Source # | |
| Show x => Show (Only x) Source # | |
| Generic (Only x) Source # | |
| HasDatatypeInfo (Only x) Source # | |
Defined in Squeal.PostgreSQL.Type Associated Types type DatatypeInfoOf (Only x) :: DatatypeInfo # Methods datatypeInfo :: proxy (Only x) -> DatatypeInfo (Code (Only x)) # | |
| Eq x => Eq (Only x) Source # | |
| Ord x => Ord (Only x) Source # | |
| type Rep (Only x) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type Code (Only x) Source # | |
Defined in Squeal.PostgreSQL.Type | |
| type DatatypeInfoOf (Only x) Source # | |
Defined in Squeal.PostgreSQL.Type | |