99 , TypeOperators
1010#-}
1111
12+ {-# LANGUAGE AllowAmbiguousTypes #-}
13+ {-# LANGUAGE FlexibleInstances #-}
14+ {-# LANGUAGE MultiParamTypeClasses #-}
15+ {-# LANGUAGE ScopedTypeVariables #-}
16+ {-# LANGUAGE TypeFamilies #-}
17+
1218module Main (main , main2 , upsertUser ) where
1319
20+ import Control.Monad.Except (MonadError (throwError ))
1421import Control.Monad.IO.Class (MonadIO (.. ))
1522import Data.Int (Int16 , Int32 )
1623import Data.Text (Text )
@@ -46,6 +53,7 @@ type OrgSchema =
4653 '[ " pk_organizations" ::: 'PrimaryKey '[" id" ] ] :=>
4754 '[ " id" ::: 'Def :=> 'NotNull 'PGint4
4855 , " name" ::: 'NoDef :=> 'NotNull 'PGtext
56+ , " type" ::: 'NoDef :=> 'NotNull 'PGtext
4957 ])
5058 , " members" ::: 'Table (
5159 '[ " fk_member" ::: 'ForeignKey '[" member" ] " user" " users" '[" id" ]
@@ -54,7 +62,7 @@ type OrgSchema =
5462 , " organization" ::: 'NoDef :=> 'NotNull 'PGint4 ])
5563 ]
5664
57- type Schemas
65+ type Schemas
5866 = '[ " public" ::: PublicSchema , " user" ::: UserSchema , " org" ::: OrgSchema ]
5967
6068setup :: Definition (Public '[] ) Schemas
@@ -83,7 +91,8 @@ setup =
8391 >>>
8492 createTable (# org ! # organizations)
8593 ( serial `as` # id :*
86- (text & notNullable) `as` # name )
94+ (text & notNullable) `as` # name :*
95+ (text & notNullable) `as` # type )
8796 ( primaryKey # id `as` # pk_organizations )
8897 >>>
8998 createTable (# org ! # members)
@@ -93,7 +102,7 @@ setup =
93102 (OnDelete Cascade ) (OnUpdate Cascade ) `as` # fk_member :*
94103 foreignKey # organization (# org ! # organizations) # id
95104 (OnDelete Cascade ) (OnUpdate Cascade ) `as` # fk_organization )
96-
105+
97106teardown :: Definition Schemas (Public '[] )
98107teardown = dropType # positive >>> dropSchemaCascade # user >>> dropSchemaCascade # org
99108
@@ -106,13 +115,48 @@ insertEmail :: Manipulation_ Schemas (Int32, Maybe Text) ()
106115insertEmail = insertInto_ (# user ! # emails)
107116 (Values_ (Default `as` # id :* Set (param @ 1 ) `as` # user_id :* Set (param @ 2 ) `as` # email))
108117
118+ insertOrganization :: Manipulation_ Schemas (Text , OrganizationType ) (Only Int32 )
119+ insertOrganization = insertInto (# org ! # organizations)
120+ (Values_ (Default `as` # id :* Set (param @ 1 ) `as` # name :* Set (param @ 2 ) `as` # type ))
121+ (OnConflict (OnConstraint # pk_organizations) DoNothing ) (Returning_ (# id `as` # fromOnly))
122+
109123getUsers :: Query_ Schemas () User
110124getUsers = select_
111125 (# u ! # name `as` # userName :* # e ! # email `as` # userEmail :* # u ! # vec `as` # userVec)
112126 ( from (table ((# user ! # users) `as` # u)
113127 & innerJoin (table ((# user ! # emails) `as` # e))
114128 (# u ! # id .== # e ! # user_id)) )
115129
130+ getOrganizations :: Query_ Schemas () Organization
131+ getOrganizations = select_
132+ ( # o ! # id `as` # orgId :*
133+ # o ! # name `as` # orgName :*
134+ # o ! # type `as` # orgType
135+ )
136+ (from (table (# org ! # organizations `as` # o)))
137+
138+ getOrganizationsBy ::
139+ forall hsty .
140+ (ToPG Schemas hsty ) =>
141+ Condition
142+ 'Ungrouped
143+ '[]
144+ '[]
145+ Schemas
146+ '[NullPG hsty ]
147+ '[" o" ::: [" id" ::: NotNull PGint4 , " name" ::: NotNull PGtext , " type" ::: NotNull PGtext ]] ->
148+ Query_ Schemas (Only hsty ) Organization
149+ getOrganizationsBy condition =
150+ select_
151+ ( # o ! # id `as` # orgId :*
152+ # o ! # name `as` # orgName :*
153+ # o ! # type `as` # orgType
154+ )
155+ (
156+ from (table (# org ! # organizations `as` # o))
157+ & where_ condition
158+ )
159+
116160upsertUser :: Manipulation_ Schemas (Int32 , String , VarArray [Maybe Int16 ]) ()
117161upsertUser = insertInto (# user ! # users `as` # u)
118162 (Values_ (Set (param @ 1 ) `as` # id :* setUser))
@@ -137,28 +181,98 @@ users =
137181 ,
User " Carole" (
Just " [email protected] " ) (
VarArray [
Just 3 ,
Nothing ,
Just 4 ])
138182 ]
139183
184+ data Organization
185+ = Organization
186+ { orgId :: Int32
187+ , orgName :: Text
188+ , orgType :: OrganizationType
189+ } deriving (Show , GHC.Generic )
190+ instance SOP. Generic Organization
191+ instance SOP. HasDatatypeInfo Organization
192+
193+ data OrganizationType
194+ = ForProfit
195+ | NonProfit
196+ deriving (Show , GHC.Generic )
197+ instance SOP. Generic OrganizationType
198+ instance SOP. HasDatatypeInfo OrganizationType
199+
200+ instance IsPG OrganizationType where
201+ type PG OrganizationType = 'PGtext
202+ instance ToPG db OrganizationType where
203+ toPG = toPG . toText
204+ where
205+ toText ForProfit = " for-profit" :: Text
206+ toText NonProfit = " non-profit" :: Text
207+
208+ instance FromPG OrganizationType where
209+ fromPG = do
210+ value <- fromPG @ Text
211+ fromText value
212+ where
213+ fromText " for-profit" = pure ForProfit
214+ fromText " non-profit" = pure NonProfit
215+ fromText value = throwError $ " Invalid organization type: \" " <> value <> " \" "
216+
217+ organizations :: [Organization ]
218+ organizations =
219+ [ Organization { orgId = 1 , orgName = " ACME" , orgType = ForProfit }
220+ , Organization { orgId = 2 , orgName = " Haskell Foundation" , orgType = NonProfit }
221+ ]
222+
140223session :: (MonadIO pq , MonadPQ Schemas pq ) => pq ()
141224session = do
142- liftIO $ Char8. putStrLn " manipulating"
143- idResults <- traversePrepared insertUser ([(userName user, userVec user) | user <- users])
144- ids <- traverse (fmap fromOnly . getRow 0 ) (idResults :: [Result (Only Int32 )])
145- traversePrepared_ insertEmail (zip (ids :: [Int32 ]) (userEmail <$> users))
146- liftIO $ Char8. putStrLn " querying"
225+ liftIO $ Char8. putStrLn " ===> manipulating"
226+ userIdResults <- traversePrepared insertUser [(userName user, userVec user) | user <- users]
227+ userIds <- traverse (fmap fromOnly . getRow 0 ) (userIdResults :: [Result (Only Int32 )])
228+ traversePrepared_ insertEmail (zip (userIds :: [Int32 ]) (userEmail <$> users))
229+
230+ orgIdResults <- traversePrepared
231+ insertOrganization
232+ [(orgName organization, orgType organization) | organization <- organizations]
233+ _ <- traverse (fmap fromOnly . getRow 0 ) (orgIdResults :: [Result (Only Int32 )])
234+
235+ liftIO $ Char8. putStrLn " ===> querying: users"
147236 usersResult <- runQuery getUsers
148237 usersRows <- getRows usersResult
149238 liftIO $ print (usersRows :: [User ])
150239
240+ liftIO $ Char8. putStrLn " ===> querying: organizations: all"
241+ organizationsResult1 <- runQuery getOrganizations
242+ organizationRows1 <- getRows organizationsResult1
243+ liftIO $ print (organizationRows1 :: [Organization ])
244+
245+ liftIO $ Char8. putStrLn " ===> querying: organizations: by ID (2)"
246+ organizationsResult2 <- runQueryParams
247+ (getOrganizationsBy @ Int32 ((# o ! # id ) .== param @ 1 )) (Only (2 :: Int32 ))
248+ organizationRows2 <- getRows organizationsResult2
249+ liftIO $ print (organizationRows2 :: [Organization ])
250+
251+ liftIO $ Char8. putStrLn " ===> querying: organizations: by name (ACME)"
252+ organizationsResult3 <- runQueryParams
253+ (getOrganizationsBy @ Text ((# o ! # name) .== param @ 1 )) (Only (" ACME" :: Text ))
254+ organizationRows3 <- getRows organizationsResult3
255+ liftIO $ print (organizationRows3 :: [Organization ])
256+
257+ liftIO $ Char8. putStrLn " ===> querying: organizations: by type (non-profit)"
258+ organizationsResult4 <- runQueryParams
259+ (getOrganizationsBy @ Text ((# o ! # type ) .== param @ 1 )) (Only NonProfit )
260+ organizationRows4 <- getRows organizationsResult4
261+ liftIO $ print (organizationRows4 :: [Organization ])
262+
151263main :: IO ()
152264main = do
153- Char8. putStrLn " squeal"
265+ Char8. putStrLn " ===> squeal"
154266 connectionString <- pure
155267 " host=localhost port=5432 dbname=exampledb user=postgres password=postgres"
156268 Char8. putStrLn $ " connecting to " <> connectionString
157269 connection0 <- connectdb connectionString
158- Char8. putStrLn " setting up schema"
270+
271+ Char8. putStrLn " ===> setting up schema"
159272 connection1 <- execPQ (define setup) connection0
160273 connection2 <- execPQ session connection1
161- Char8. putStrLn " tearing down schema"
274+
275+ Char8. putStrLn " ===> tearing down schema"
162276 connection3 <- execPQ (define teardown) connection2
163277 finish connection3
164278
0 commit comments