esqueleto/test/PostgreSQL/MigrateJSON.hs
Matt Parsons 96331257e4
get persistent 2.12 going (#243)
* run mysql tests

* uhhh why are you like this

* stuff

* tests pass locally

* make the example work

* minor bump

* fix gha

* k

* no persistent-template dependency please

* it passed?

* ci nonsense

* uh

* i think that should do it

* ok no really

* i miss file-watch

* sigh

* come on pls

* stylish haskell

* i hate this
2021-03-29 14:47:20 -06:00

40 lines
1.1 KiB
Haskell

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE 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)
deriving Show
|]
cleanJSON
:: (forall m. RunDbMonad m
=> SqlPersistT (ResourceT m) ())
cleanJSON = delete $ from $ \(_ :: SqlExpr (Entity Json)) -> return ()