* added PostgreSQL.JSON module * finished adding all JSON operators * cleanup * half way through writing tests * final tweaks to comments * finished with JSON tests * upped persistent dependency to 2.10.0 because of PersistArray data constructor addition needed for JSON operators * noticed the minus operator with text[] as right operand was only added in PSQL v10, added function and adjusted types/tests * adjusted yaml configs for updated dependencies and PSQL v10 in Travis * try to get PostgreSQL 10 running * use @since notation * removed postgresql from 'services' field * and one more time, with FEELING! (and postgresql-10) * foo * PSQL 10 runs on 5433, it seems? reverting .travis.yml changes and setting test conn to port 5433 * of course I forget to add the PORT env > .< * doop-dee-doo * herp-a-derp * last commit (hopefully) * also have more recent dependencies in the 'compiler should error' tests * why does it feel like this'll go on for a while still? * copied some extra-deps from the persistent ymls * aaaaand we're done... right? * added persistent-postgresql to the dependencies and used its instances for Aeson.Value * small comment fix * moved the instances to their own module, this way they're optional to use if you don't use persistent-postgresql * use port 5432, like a normal PostgreSQL! * added JSONB newtype with instances, instead of orphaning Aeson.Value * reworked everything to use the JSONB newtype. And adjusted most comments to reflect the change * fixed all the tests (just making it compile again) * that's right, Travis' PSQL v10 NEEEEDS it to be port 5433... for some reason * update on the haddockumentation * added JSONAccessor data type for easier usage of certain operators * Also add to changelog.md * JSONExpr -> JSONBExpr * this damn PGPORT is really irritating
35 lines
957 B
Haskell
35 lines
957 B
Haskell
{-# LANGUAGE FlexibleContexts
|
|
, GADTs
|
|
, GeneralizedNewtypeDeriving
|
|
, MultiParamTypeClasses
|
|
, OverloadedStrings
|
|
, QuasiQuotes
|
|
, RankNTypes
|
|
, ScopedTypeVariables
|
|
, TemplateHaskell
|
|
, TypeFamilies
|
|
, UndecidableInstances
|
|
#-}
|
|
module PostgreSQL.MigrateJSON where
|
|
|
|
import Control.Monad.Trans.Resource (ResourceT)
|
|
import Data.Aeson (Value)
|
|
import Database.Esqueleto (SqlExpr, delete, from)
|
|
import Database.Esqueleto.PostgreSQL.JSON (JSONB)
|
|
import Database.Persist (Entity)
|
|
import Database.Persist.Sql (SqlPersistT)
|
|
import Database.Persist.TH
|
|
|
|
import Common.Test (RunDbMonad)
|
|
|
|
-- JSON Table for PostgreSQL
|
|
share [mkPersist sqlSettings, mkMigrate "migrateJSON"] [persistUpperCase|
|
|
Json
|
|
value (JSONB Value)
|
|
|]
|
|
|
|
cleanJSON
|
|
:: (forall m. RunDbMonad m
|
|
=> SqlPersistT (ResourceT m) ())
|
|
cleanJSON = delete $ from $ \(_ :: SqlExpr (Entity Json)) -> return ()
|