Skip to content

Commit

Permalink
Guard OverloadedRecordDot with CPP pragma
Browse files Browse the repository at this point in the history
  • Loading branch information
halogenandtoast committed Oct 5, 2023
1 parent e88a28e commit 587a6d4
Showing 1 changed file with 23 additions and 12 deletions.
35 changes: 23 additions & 12 deletions test/Common/Record.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
Expand All @@ -8,7 +9,6 @@
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE StandaloneDeriving #-}
Expand All @@ -18,25 +18,31 @@
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}

#if __GLASGOW_HASKELL__ >= 902
{-# LANGUAGE OverloadedRecordDot #-}
#endif

-- Tests for `Database.Esqueleto.Record`.
module Common.Record (testDeriveEsqueletoRecord) where

import Common.Test.Import hiding (from, on)
import Control.Monad.Trans.State.Strict (StateT(..), evalStateT)
import Control.Monad.Trans.State.Strict (StateT (..), evalStateT)
import Data.Bifunctor (first)
import Data.List (sortOn)
import Data.Maybe (catMaybes)
import Data.Proxy (Proxy(..))
import Data.Proxy (Proxy (..))
import Database.Esqueleto.Experimental
import Database.Esqueleto.Internal.Internal (SqlSelect(..))
import Database.Esqueleto.Record
( DeriveEsqueletoRecordSettings(..)
, defaultDeriveEsqueletoRecordSettings
, deriveEsqueletoRecord
, deriveEsqueletoRecordWith
, takeColumns
, takeMaybeColumns
)
import Database.Esqueleto.Internal.Internal (SqlSelect (..))
import Database.Esqueleto.Record (
DeriveEsqueletoRecordSettings (..),
defaultDeriveEsqueletoRecordSettings,
deriveEsqueletoRecord,
deriveEsqueletoRecordWith,
takeColumns,
takeMaybeColumns,
)

#if __GLASGOW_HASKELL__ >= 902

data MyRecord =
MyRecord
Expand Down Expand Up @@ -313,3 +319,8 @@ testDeriveEsqueletoRecord = describe "deriveEsqueletoRecord" $ do
}
})) -> True
_ -> True)

#else
it "is only supported in GHC 9.2 or above" $ \_ -> do
pending
#endif

0 comments on commit 587a6d4

Please sign in to comment.