1 {-# LANGUAGE TemplateHaskell, QuasiQuotes, RecordWildCards, OverloadedStrings, DataKinds #-}
    2 module Databrary.Model.Comment
    3   ( module Databrary.Model.Comment.Types
    4   , blankComment
    5   , lookupComment
    6   , lookupSlotComments
    7   , lookupVolumeCommentRows
    8   , addComment
    9   , commentJSON
   10   ) where
   11 
   12 import Control.Applicative (empty, pure)
   13 import Data.Int (Int64)
   14 import Data.Maybe (listToMaybe)
   15 import Data.Monoid ((<>))
   16 import Database.PostgreSQL.Typed.Query
   17 import Database.PostgreSQL.Typed.Types
   18 import qualified Data.ByteString
   19 import Data.ByteString (ByteString)
   20 import qualified Data.String
   21 import qualified Data.Text as T
   22 
   23 import Databrary.Has (peek, view)
   24 import qualified Databrary.JSON as JSON
   25 import Databrary.Service.DB
   26 -- import Databrary.Model.SQL
   27 import Databrary.Model.Id.Types
   28 import Databrary.Model.Party
   29 import Databrary.Model.Party.SQL
   30 import Databrary.Model.Identity
   31 import Databrary.Model.Time
   32 import Databrary.Model.Volume.Types
   33 import Databrary.Model.Volume.SQL
   34 import Databrary.Model.Container
   35 import Databrary.Model.Segment
   36 import Databrary.Model.Slot
   37 import Databrary.Model.Comment.Types
   38 -- import Databrary.Model.Comment.SQL
   39 
   40 blankComment :: Account -> Slot -> Comment
   41 blankComment who slot = Comment
   42   { commentId = error "blankComment"
   43   , commentWho = who
   44   , commentSlot = slot
   45   , commentTime = error "blankComment"
   46   , commentText = ""
   47   , commentParents = []
   48   }
   49 
   50 lookupComment :: (MonadDB c m, MonadHasIdentity c m) => Id Comment -> m (Maybe Comment)
   51 lookupComment i = do
   52   let _tenv_acxwT = unknownPGTypeEnv
   53   ident <- peek
   54   -- dbQuery1 $(selectQuery (selectComment 'ident) "$!WHERE comment.id = ${i}")
   55   mRow <- mapRunPrepQuery1
   56       ((\ _p_acxwU _p_acxwV _p_acxwW _p_acxwX _p_acxwY ->
   57                        (Data.String.fromString
   58                           "SELECT comment.id,comment.segment,comment.time,comment.text,comment.thread,party.id,party.name,party.prename,party.orcid,party.affiliation,party.url,account.email,container.id,container.top,container.name,container.date,slot_release.release,volume.id,volume.name,volume.body,volume.alias,volume.doi,volume_creation(volume.id),volume_owners.owners,volume_permission.permission,volume_permission.share_full FROM comment_thread AS comment JOIN party JOIN account USING (id) ON comment.who = account.id JOIN container LEFT JOIN slot_release ON container.id = slot_release.container AND slot_release.segment = '(,)' JOIN volume LEFT JOIN volume_owners ON volume.id = volume_owners.volume JOIN LATERAL   (VALUES      ( CASE WHEN $1              THEN enum_last(NULL::permission)              ELSE volume_access_check(volume.id, $2) END      , CASE WHEN $3              THEN null              ELSE (select share_full                    from volume_access_view                    where volume = volume.id and party = $4                    limit 1) END )   ) AS volume_permission (permission, share_full) ON volume_permission.permission >= 'PUBLIC'::permission ON container.volume = volume.id ON comment.container = container.id WHERE comment.id = $5",
   59                        [pgEncodeParameter
   60                           _tenv_acxwT (PGTypeProxy :: PGTypeName "boolean") _p_acxwU,
   61                         pgEncodeParameter
   62                           _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _p_acxwV,
   63                         pgEncodeParameter
   64                           _tenv_acxwT (PGTypeProxy :: PGTypeName "boolean") _p_acxwW,
   65                         pgEncodeParameter
   66                           _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _p_acxwX,
   67                         pgEncodeParameter
   68                           _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _p_acxwY],
   69                        [pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "integer"),
   70                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "segment"),
   71                         pgBinaryColumn
   72                           _tenv_acxwT (PGTypeProxy :: PGTypeName "timestamp with time zone"),
   73                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   74                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "integer[]"),
   75                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "integer"),
   76                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   77                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   78                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "bpchar"),
   79                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   80                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   81                         pgBinaryColumn
   82                           _tenv_acxwT (PGTypeProxy :: PGTypeName "character varying"),
   83                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "integer"),
   84                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "boolean"),
   85                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   86                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "date"),
   87                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "release"),
   88                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "integer"),
   89                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   90                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text"),
   91                         pgBinaryColumn
   92                           _tenv_acxwT (PGTypeProxy :: PGTypeName "character varying"),
   93                         pgBinaryColumn
   94                           _tenv_acxwT (PGTypeProxy :: PGTypeName "character varying"),
   95                         pgBinaryColumn
   96                           _tenv_acxwT (PGTypeProxy :: PGTypeName "timestamp with time zone"),
   97                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "text[]"),
   98                         pgBinaryColumn
   99                           _tenv_acxwT (PGTypeProxy :: PGTypeName "permission"),
  100                         pgBinaryColumn _tenv_acxwT (PGTypeProxy :: PGTypeName "boolean")]))
  101          (identitySuperuser ident)
  102          (view ident :: Id Party)
  103          (identitySuperuser ident)
  104          (view ident :: Id Party)
  105          i)
  106                (\
  107                   [_cid_acxwZ,
  108                    _csegment_acxx0,
  109                    _ctime_acxx1,
  110                    _ctext_acxx2,
  111                    _cthread_acxx3,
  112                    _cid_acxx4,
  113                    _cname_acxx5,
  114                    _cprename_acxx6,
  115                    _corcid_acxx7,
  116                    _caffiliation_acxx8,
  117                    _curl_acxx9,
  118                    _cemail_acxxa,
  119                    _cid_acxxb,
  120                    _ctop_acxxc,
  121                    _cname_acxxd,
  122                    _cdate_acxxe,
  123                    _crelease_acxxf,
  124                    _cid_acxxg,
  125                    _cname_acxxh,
  126                    _cbody_acxxi,
  127                    _calias_acxxj,
  128                    _cdoi_acxxk,
  129                    _cvolume_creation_acxxl,
  130                    _cowners_acxxm,
  131                    _cpermission_acxxn,
  132                    _cshare_full_acxxo]
  133                   -> (pgDecodeColumnNotNull
  134                         _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _cid_acxwZ, 
  135                       pgDecodeColumnNotNull
  136                         _tenv_acxwT (PGTypeProxy :: PGTypeName "segment") _csegment_acxx0, 
  137                       pgDecodeColumnNotNull
  138                         _tenv_acxwT
  139                         (PGTypeProxy :: PGTypeName "timestamp with time zone")
  140                         _ctime_acxx1, 
  141                       pgDecodeColumnNotNull
  142                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _ctext_acxx2, 
  143                       pgDecodeColumnNotNull
  144                         _tenv_acxwT
  145                         (PGTypeProxy :: PGTypeName "integer[]")
  146                         _cthread_acxx3, 
  147                       pgDecodeColumnNotNull
  148                         _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _cid_acxx4, 
  149                       pgDecodeColumnNotNull
  150                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _cname_acxx5, 
  151                       pgDecodeColumnNotNull
  152                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _cprename_acxx6, 
  153                       pgDecodeColumnNotNull
  154                         _tenv_acxwT (PGTypeProxy :: PGTypeName "bpchar") _corcid_acxx7, 
  155                       pgDecodeColumnNotNull
  156                         _tenv_acxwT
  157                         (PGTypeProxy :: PGTypeName "text")
  158                         _caffiliation_acxx8, 
  159                       pgDecodeColumnNotNull
  160                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _curl_acxx9, 
  161                       pgDecodeColumnNotNull
  162                         _tenv_acxwT
  163                         (PGTypeProxy :: PGTypeName "character varying")
  164                         _cemail_acxxa, 
  165                       pgDecodeColumnNotNull
  166                         _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _cid_acxxb, 
  167                       pgDecodeColumnNotNull
  168                         _tenv_acxwT (PGTypeProxy :: PGTypeName "boolean") _ctop_acxxc, 
  169                       pgDecodeColumnNotNull
  170                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _cname_acxxd, 
  171                       pgDecodeColumnNotNull
  172                         _tenv_acxwT (PGTypeProxy :: PGTypeName "date") _cdate_acxxe, 
  173                       pgDecodeColumnNotNull
  174                         _tenv_acxwT (PGTypeProxy :: PGTypeName "release") _crelease_acxxf, 
  175                       pgDecodeColumnNotNull
  176                         _tenv_acxwT (PGTypeProxy :: PGTypeName "integer") _cid_acxxg, 
  177                       pgDecodeColumnNotNull
  178                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _cname_acxxh, 
  179                       pgDecodeColumnNotNull
  180                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text") _cbody_acxxi, 
  181                       pgDecodeColumnNotNull
  182                         _tenv_acxwT
  183                         (PGTypeProxy :: PGTypeName "character varying")
  184                         _calias_acxxj, 
  185                       pgDecodeColumnNotNull
  186                         _tenv_acxwT
  187                         (PGTypeProxy :: PGTypeName "character varying")
  188                         _cdoi_acxxk, 
  189                       pgDecodeColumnNotNull
  190                         _tenv_acxwT
  191                         (PGTypeProxy :: PGTypeName "timestamp with time zone")
  192                         _cvolume_creation_acxxl, 
  193                       pgDecodeColumnNotNull
  194                         _tenv_acxwT (PGTypeProxy :: PGTypeName "text[]") _cowners_acxxm, 
  195                       pgDecodeColumnNotNull
  196                         _tenv_acxwT
  197                         (PGTypeProxy :: PGTypeName "permission")
  198                         _cpermission_acxxn, 
  199                       pgDecodeColumnNotNull
  200                         _tenv_acxwT
  201                         (PGTypeProxy :: PGTypeName "boolean")
  202                         _cshare_full_acxxo))
  203   pure
  204     (fmap
  205       (\ (vid_acxwt, vsegment_acxwu, vtime_acxwv, vtext_acxww,
  206           vthread_acxwx, vid_acxwy, vname_acxwz, vprename_acxwA,
  207           vorcid_acxwB, vaffiliation_acxwC, vurl_acxwD, vemail_acxwE,
  208           vid_acxwF, vtop_acxwG, vname_acxwH, vdate_acxwI, vrelease_acxwJ,
  209           vid_acxwK, vname_acxwL, vbody_acxwM, valias_acxwN, vdoi_acxwO,
  210           vc_acxwP, vowners_acxwQ, vpermission_acxwR, vfull_acxwS)
  211          -> ($)
  212               (($)
  213                  (makeComment
  214                     vid_acxwt vsegment_acxwu vtime_acxwv vtext_acxww vthread_acxwx)
  215                  (Databrary.Model.Party.SQL.permissionParty
  216                     (Databrary.Model.Party.SQL.makeAccount
  217                        (PartyRow
  218                           vid_acxwy
  219                           vname_acxwz
  220                           vprename_acxwA
  221                           vorcid_acxwB
  222                           vaffiliation_acxwC
  223                           vurl_acxwD)
  224                        (Account vemail_acxwE))
  225                     Nothing
  226                     ident))
  227               (($)
  228                  (Container
  229                     (ContainerRow vid_acxwF vtop_acxwG vname_acxwH vdate_acxwI)
  230                     vrelease_acxwJ)
  231                  (Databrary.Model.Volume.SQL.makeVolume
  232                     (Databrary.Model.Volume.SQL.setCreation
  233                        (VolumeRow
  234                           vid_acxwK vname_acxwL vbody_acxwM valias_acxwN vdoi_acxwO)
  235                        vc_acxwP)
  236                     vowners_acxwQ
  237                     (Databrary.Model.Volume.SQL.makePermInfo
  238                        vpermission_acxwR vfull_acxwS))))
  239     mRow)
  240 
  241 lookupSlotComments :: (MonadDB c m, MonadHasIdentity c m) => Slot -> Int -> m [Comment]
  242 lookupSlotComments (Slot c s) n = do
  243   let _tenv_acBuC = unknownPGTypeEnv
  244   ident <- peek
  245   -- dbQuery $ ($ c) <$> $(selectQuery (selectContainerComment 'ident) "$!WHERE comment.container = ${containerId $ containerRow c} AND comment.segment && ${s} ORDER BY comment.thread LIMIT ${fromIntegral n :: Int64}")
  246   rows <- mapRunPrepQuery
  247       ((\ _p_acBuD _p_acBuE _p_acBuF ->
  248                        (Data.String.fromString
  249                           "SELECT comment.id,comment.segment,comment.time,comment.text,comment.thread,party.id,party.name,party.prename,party.orcid,party.affiliation,party.url,account.email FROM comment_thread AS comment JOIN party JOIN account USING (id) ON comment.who = account.id WHERE comment.container = $1 AND comment.segment && $2 ORDER BY comment.thread LIMIT $3",
  250                        [pgEncodeParameter
  251                           _tenv_acBuC (PGTypeProxy :: PGTypeName "integer") _p_acBuD,
  252                         pgEncodeParameter
  253                           _tenv_acBuC (PGTypeProxy :: PGTypeName "segment") _p_acBuE,
  254                         pgEncodeParameter
  255                           _tenv_acBuC (PGTypeProxy :: PGTypeName "bigint") _p_acBuF],
  256                        [pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "integer"),
  257                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "segment"),
  258                         pgBinaryColumn
  259                           _tenv_acBuC (PGTypeProxy :: PGTypeName "timestamp with time zone"),
  260                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "text"),
  261                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "integer[]"),
  262                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "integer"),
  263                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "text"),
  264                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "text"),
  265                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "bpchar"),
  266                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "text"),
  267                         pgBinaryColumn _tenv_acBuC (PGTypeProxy :: PGTypeName "text"),
  268                         pgBinaryColumn
  269                           _tenv_acBuC (PGTypeProxy :: PGTypeName "character varying")]))
  270          (containerId $ containerRow c) s (fromIntegral n :: Int64))
  271                (\
  272                   [_cid_acBuG,
  273                    _csegment_acBuH,
  274                    _ctime_acBuI,
  275                    _ctext_acBuJ,
  276                    _cthread_acBuK,
  277                    _cid_acBuL,
  278                    _cname_acBuM,
  279                    _cprename_acBuN,
  280                    _corcid_acBuO,
  281                    _caffiliation_acBuP,
  282                    _curl_acBuQ,
  283                    _cemail_acBuR]
  284                   -> (pgDecodeColumnNotNull
  285                         _tenv_acBuC (PGTypeProxy :: PGTypeName "integer") _cid_acBuG, 
  286                       pgDecodeColumnNotNull
  287                         _tenv_acBuC (PGTypeProxy :: PGTypeName "segment") _csegment_acBuH, 
  288                       pgDecodeColumnNotNull
  289                         _tenv_acBuC
  290                         (PGTypeProxy :: PGTypeName "timestamp with time zone")
  291                         _ctime_acBuI, 
  292                       pgDecodeColumnNotNull
  293                         _tenv_acBuC (PGTypeProxy :: PGTypeName "text") _ctext_acBuJ, 
  294                       pgDecodeColumnNotNull
  295                         _tenv_acBuC
  296                         (PGTypeProxy :: PGTypeName "integer[]")
  297                         _cthread_acBuK, 
  298                       pgDecodeColumnNotNull
  299                         _tenv_acBuC (PGTypeProxy :: PGTypeName "integer") _cid_acBuL, 
  300                       pgDecodeColumnNotNull
  301                         _tenv_acBuC (PGTypeProxy :: PGTypeName "text") _cname_acBuM, 
  302                       pgDecodeColumnNotNull
  303                         _tenv_acBuC (PGTypeProxy :: PGTypeName "text") _cprename_acBuN, 
  304                       pgDecodeColumnNotNull
  305                         _tenv_acBuC (PGTypeProxy :: PGTypeName "bpchar") _corcid_acBuO, 
  306                       pgDecodeColumnNotNull
  307                         _tenv_acBuC
  308                         (PGTypeProxy :: PGTypeName "text")
  309                         _caffiliation_acBuP, 
  310                       pgDecodeColumnNotNull
  311                         _tenv_acBuC (PGTypeProxy :: PGTypeName "text") _curl_acBuQ, 
  312                       pgDecodeColumnNotNull
  313                         _tenv_acBuC
  314                         (PGTypeProxy :: PGTypeName "character varying")
  315                         _cemail_acBuR))
  316   pure
  317     (fmap
  318       (\ (vid_acBu6, vsegment_acBu7, vtime_acBu8, vtext_acBu9,
  319           vthread_acBua, vid_acBub, vname_acBuc, vprename_acBud,
  320           vorcid_acBue, vaffiliation_acBuf, vurl_acBug, vemail_acBuh)
  321          -> (makeComment
  322                  vid_acBu6 vsegment_acBu7 vtime_acBu8 vtext_acBu9 vthread_acBua)
  323               (Databrary.Model.Party.SQL.permissionParty
  324                  (Databrary.Model.Party.SQL.makeAccount
  325                     (PartyRow
  326                        vid_acBub
  327                        vname_acBuc
  328                        vprename_acBud
  329                        vorcid_acBue
  330                        vaffiliation_acBuf
  331                        vurl_acBug)
  332                     (Account vemail_acBuh))
  333                  Nothing
  334                  ident)
  335               c)
  336       rows)
  337 
  338 mapQuery :: ByteString -> ([PGValue] -> a) -> PGSimpleQuery a
  339 mapQuery qry mkResult =
  340   fmap mkResult (rawPGSimpleQuery qry)
  341 
  342 makeCommentRow :: Id Comment -> Id Container -> Segment -> Id Party -> Timestamp -> T.Text -> CommentRow
  343 makeCommentRow i c s w t x = CommentRow i w (SlotId c s) t x
  344 
  345 lookupVolumeCommentRows :: MonadDB c m => Volume -> m [CommentRow]
  346 lookupVolumeCommentRows v = do
  347   let _tenv_a8I48 = unknownPGTypeEnv
  348   dbQuery -- .(selectQuery selectCommentRow "JOIN container ON comment.container = container.id WHERE container.volume = ${volumeId $ volumeRow v} ORDER BY container")
  349    (fmap
  350       (\ (vid_a8I38, vcontainer_a8I39, vsegment_a8I3a, vwho_a8I3b,
  351           vtime_a8I3c, vtext_a8I3d)
  352          -> makeCommentRow
  353               vid_a8I38
  354               vcontainer_a8I39
  355               vsegment_a8I3a
  356               vwho_a8I3b
  357               vtime_a8I3c
  358               vtext_a8I3d)
  359       (mapQuery
  360         ((\ _p_a8I49 ->
  361                        (Data.ByteString.concat
  362                           [Data.String.fromString
  363                              "SELECT comment.id,comment.container,comment.segment,comment.who,comment.time,comment.text FROM comment JOIN container ON comment.container = container.id WHERE container.volume = ",
  364                            Database.PostgreSQL.Typed.Types.pgEscapeParameter
  365                              _tenv_a8I48
  366                              (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  367                                 Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  368                              _p_a8I49,
  369                            Data.String.fromString " ORDER BY container"]))
  370          (volumeId $ volumeRow v))
  371                (\ [_cid_a8I4a,
  372                    _ccontainer_a8I4b,
  373                    _csegment_a8I4c,
  374                    _cwho_a8I4d,
  375                    _ctime_a8I4e,
  376                    _ctext_a8I4f]
  377                   -> (Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  378                         _tenv_a8I48
  379                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  380                            Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  381                         _cid_a8I4a, 
  382                       Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  383                         _tenv_a8I48
  384                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  385                            Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  386                         _ccontainer_a8I4b, 
  387                       Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  388                         _tenv_a8I48
  389                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  390                            Database.PostgreSQL.Typed.Types.PGTypeName "segment")
  391                         _csegment_a8I4c, 
  392                       Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  393                         _tenv_a8I48
  394                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  395                            Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  396                         _cwho_a8I4d, 
  397                       Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  398                         _tenv_a8I48
  399                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  400                            Database.PostgreSQL.Typed.Types.PGTypeName "timestamp with time zone")
  401                         _ctime_a8I4e, 
  402                       Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  403                         _tenv_a8I48
  404                         (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  405                            Database.PostgreSQL.Typed.Types.PGTypeName "text")
  406                         _ctext_a8I4f))))
  407 
  408 addComment :: MonadDB c m => Comment -> m Comment
  409 addComment c@Comment{..} = do
  410   let _tenv_a8Iah = unknownPGTypeEnv
  411   (i, t) <- dbQuery1' -- [pgSQL|INSERT INTO comment (who, container, segment, text, parent) VALUES (${partyId $ partyRow $ accountParty commentWho}, ${containerId $ containerRow $ slotContainer commentSlot}, ${slotSegment commentSlot}, ${commentText}, ${listToMaybe commentParents}) RETURNING id, time|]
  412     (mapQuery
  413       ((\ _p_a8Iai _p_a8Iak _p_a8Ial _p_a8Iam _p_a8Ian ->
  414                     (Data.ByteString.concat
  415                        [Data.String.fromString
  416                           "INSERT INTO comment (who, container, segment, text, parent) VALUES (",
  417                         Database.PostgreSQL.Typed.Types.pgEscapeParameter
  418                           _tenv_a8Iah
  419                           (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  420                              Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  421                           _p_a8Iai,
  422                         Data.String.fromString ", ",
  423                         Database.PostgreSQL.Typed.Types.pgEscapeParameter
  424                           _tenv_a8Iah
  425                           (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  426                              Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  427                           _p_a8Iak,
  428                         Data.String.fromString ", ",
  429                         Database.PostgreSQL.Typed.Types.pgEscapeParameter
  430                           _tenv_a8Iah
  431                           (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  432                              Database.PostgreSQL.Typed.Types.PGTypeName "segment")
  433                           _p_a8Ial,
  434                         Data.String.fromString ", ",
  435                         Database.PostgreSQL.Typed.Types.pgEscapeParameter
  436                           _tenv_a8Iah
  437                           (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  438                              Database.PostgreSQL.Typed.Types.PGTypeName "text")
  439                           _p_a8Iam,
  440                         Data.String.fromString ", ",
  441                         Database.PostgreSQL.Typed.Types.pgEscapeParameter
  442                           _tenv_a8Iah
  443                           (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  444                              Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  445                           _p_a8Ian,
  446                         Data.String.fromString ") RETURNING id, time"]))
  447        (partyId $ partyRow $ accountParty commentWho)
  448        (containerId $ containerRow $ slotContainer commentSlot)
  449        (slotSegment commentSlot)
  450        commentText
  451        (listToMaybe commentParents))
  452           (\ [_cid_a8Iap, _ctime_a8Iaq]
  453                -> (Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  454                      _tenv_a8Iah
  455                      (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  456                         Database.PostgreSQL.Typed.Types.PGTypeName "integer")
  457                      _cid_a8Iap, 
  458                    Database.PostgreSQL.Typed.Types.pgDecodeColumnNotNull
  459                      _tenv_a8Iah
  460                      (Database.PostgreSQL.Typed.Types.PGTypeProxy ::
  461                         Database.PostgreSQL.Typed.Types.PGTypeName "timestamp with time zone")
  462                      _ctime_a8Iaq)))
  463   return c
  464     { commentId = i
  465     , commentTime = t
  466     }
  467 
  468 commentJSON :: JSON.ToNestedObject o u => Comment -> JSON.Record (Id Comment) o
  469 commentJSON Comment{ commentSlot = Slot{..}, ..} = JSON.Record commentId $
  470      "container" JSON..=: containerJSON False slotContainer -- should compute based on volume
  471   <> segmentJSON slotSegment
  472   <> "who" JSON..=: partyJSON (accountParty commentWho)
  473   <> "time" JSON..= commentTime
  474   <> "text" JSON..= commentText
  475   <> "parents" `JSON.kvObjectOrEmpty` (if null commentParents then empty else pure commentParents)
  476