Skip to content

Commit

Permalink
Build with stack nightly
Browse files Browse the repository at this point in the history
  • Loading branch information
tathougies committed Mar 18, 2019
1 parent d87120b commit 737b73c
Show file tree
Hide file tree
Showing 3 changed files with 10 additions and 5 deletions.
6 changes: 3 additions & 3 deletions beam-core/Database/Beam/Backend/SQL/Row.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE ConstraintKinds #-}
Expand All @@ -24,7 +25,9 @@ import Data.Typeable
import Data.Vector.Sized (Vector)
import qualified Data.Vector.Sized as Vector

#if !MIN_VERSION_base(4, 12, 0)
import Data.Proxy
#endif

import GHC.Generics
import GHC.TypeLits
Expand Down Expand Up @@ -80,9 +83,6 @@ parseOneField = do
peekField :: (Typeable a, BackendFromField be a) => FromBackendRowM be (Maybe a)
peekField = fmap Just (FromBackendRowM (liftF (ParseOneField id))) <|> pure Nothing

-- checkNextNNull :: Int -> FromBackendRowM be Bool
-- checkNextNNull n = FromBackendRowM (liftF (CheckNextNNull n id))

-- BeamBackend instead of BeamSqlBackend to prevent circular super class
class BeamBackend be => FromBackendRow be a where
-- | Parses a beam row. This should not fail, except in the case of
Expand Down
2 changes: 2 additions & 0 deletions beam-migrate/Database/Beam/Haskell/Syntax.hs
Original file line number Diff line number Diff line change
Expand Up @@ -970,7 +970,9 @@ instance Hashable (Hs.Name ())
instance Hashable (Hs.Type ())
instance Hashable (Hs.QOp ())
instance Hashable (Hs.TyVarBind ())
#if !MIN_VERSION_haskell_src_exts(1, 21, 0)
instance Hashable (Hs.Kind ())
#endif
instance Hashable (Hs.Context ())
instance Hashable (Hs.SpecialCon ())
instance Hashable (Hs.Pat ())
Expand Down
7 changes: 5 additions & 2 deletions beam-postgres/Database/Beam/Postgres/Connection.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-partial-type-signatures #-}

{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE LambdaCase #-}
Expand Down Expand Up @@ -64,7 +64,11 @@ import Data.Proxy
import Data.String
import qualified Data.Text as T
import Data.Text.Encoding (decodeUtf8)
#if MIN_VERSION_base(4,12,0)
import Data.Typeable (cast)
#else
import Data.Typeable (cast, typeOf)
#endif
#if !MIN_VERSION_base(4, 11, 0)
import Data.Semigroup
#endif
Expand Down Expand Up @@ -177,7 +181,6 @@ runPgRowReader conn rowIdx res fields (FromBackendRowM readRow) =
pure (Left err)

finish x _ _ _ = pure (Right x)
finishWithSt x curCol colCount cols = pure (Right (x, curCol, colCount, cols))

withPgDebug :: (String -> IO ()) -> Pg.Connection -> Pg a -> IO (Either BeamRowReadError a)
withPgDebug dbg conn (Pg action) =
Expand Down

0 comments on commit 737b73c

Please sign in to comment.