mirror of
https://github.com/khibino/haskell-relational-record.git
synced 2024-12-12 12:09:08 +03:00
FIx to block record update.
This commit is contained in:
parent
01867542ac
commit
780af9d7d2
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
|
||||
module Database.Relational.Query.Expr (
|
||||
Expr(showExpr),
|
||||
Expr, showExpr,
|
||||
|
||||
ShowConstantSQL (showConstantSQL),
|
||||
|
||||
@ -17,7 +17,7 @@ import qualified Data.ByteString.Char8 as BS
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Database.Relational.Query.Expr.Unsafe (Expr(Expr, showExpr))
|
||||
import Database.Relational.Query.Expr.Unsafe (Expr(Expr), showExpr)
|
||||
|
||||
|
||||
intExprSQL :: (Show a, Integral a) => a -> String
|
||||
|
@ -1,9 +1,12 @@
|
||||
|
||||
module Database.Relational.Query.Expr.Unsafe (
|
||||
Expr(Expr, showExpr),
|
||||
Expr(Expr), showExpr
|
||||
) where
|
||||
|
||||
newtype Expr a = Expr { showExpr :: String }
|
||||
newtype Expr a = Expr (String)
|
||||
|
||||
showExpr :: Expr t -> String
|
||||
showExpr (Expr s) = s
|
||||
|
||||
instance Show (Expr a) where
|
||||
show = showExpr
|
||||
|
@ -1,19 +1,22 @@
|
||||
{-# LANGUAGE ExistentialQuantification #-}
|
||||
|
||||
module Database.Relational.Query.Pi.Unsafe (
|
||||
PiUnit (offset), definePiUnit,
|
||||
PiUnit, offset, definePiUnit,
|
||||
|
||||
Pi ((:*), Leaf),
|
||||
|
||||
defineColumn
|
||||
) where
|
||||
|
||||
newtype PiUnit r ft = PiUnit { offset :: Int }
|
||||
newtype PiUnit r ft = PiUnit Int
|
||||
-- data PiUnit r ft = PiUnit
|
||||
-- { offset :: Int
|
||||
-- , column :: Column r ft
|
||||
-- }
|
||||
|
||||
offset :: PiUnit r ft -> Int
|
||||
offset (PiUnit off) = off
|
||||
|
||||
data Pi r ft = forall r' . PiUnit r r' :* Pi r' ft
|
||||
| Leaf (PiUnit r ft)
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user