1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20 21 22 23 24 25 26 27 28 29 30 31 32 33 34 35 36 37 38 39 40 41 42 43 44 45 46 47 48 49 50 51 52 53 54 55 56 57 58 59 60 61 62 63 64 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 91 92 93 94 95 96 97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 123 124 125 126 127 128 129 130 131 132 133 134 135 136 137 138 139 140 141 142 143 144 145 146 147 148 149 150 151 152 153 154 155 156 157 158 159 160 161 162 163 164 165 166 167 168 169 170 171 172 173 174 175 176 177 178 179 180 181 182 183 184 185 186 187 188 189 190 191 192 193 194 195 196 197 198 199 200 201 202 203 204 205 206 207 208 209 210 211 212 213 214 215 216 217 218 219 220 221 222 223 224 225 226 227 228 229 230 231 232 233 234 235 236 237 238 239 240 241 242 243 244 245 246 247 248 249 250 251 252 253 254 255 256 257 258 259 260 261 262 263 264 265 266 267 268 269 270 271 272 273 274 275 276 277 278 279 280 281 282 283 284 285 286 287 288 289 290 291 292 293 294 295 296 297 298 299 300 301 302 303 304 305 306 307 308 309 310 311 312 313 314 315 316 317 318 319 320 321 322 323 324 325 326 327 328 329 330 331 332 333 334 335 336 337 338 339 340 341 342 343 344 345 346 347 348 349 350 351 352 353 354 355 356 357 358 359 360 361 362 363 364 365 366 367 368 369 370 371 372 373 374 375 376 377 378 379 380 381 382 383 384 385 386 387 388 389 390 391 392 393 394 395 396 397 398 399
|
{-# LANGUAGE CPP #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Database.Persist.Types.Base where
import qualified Data.Aeson as A
import Control.Exception (Exception)
import Web.PathPieces (PathPiece (..))
import Control.Monad.Trans.Error (Error (..))
import Data.Typeable (Typeable)
import Data.Text (Text, pack)
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import Data.Text.Encoding.Error (lenientDecode)
import qualified Data.ByteString.Base64 as B64
import qualified Data.Vector as V
import Control.Arrow (second)
import Data.Time (Day, TimeOfDay, UTCTime)
import Data.Int (Int64)
import qualified Data.Text.Read
import Data.ByteString (ByteString, foldl')
import Data.Bits (shiftL, shiftR)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as BS8
import Data.Time.LocalTime (ZonedTime, zonedTimeToUTC, zonedTimeToLocalTime, zonedTimeZone)
import Data.Map (Map)
import qualified Data.HashMap.Strict as HM
import Data.Word (Word32)
import Numeric (showHex, readHex)
#if MIN_VERSION_aeson(0, 7, 0)
import qualified Data.Scientific
#else
import qualified Data.Attoparsec.Number as AN
#endif
-- | A 'Checkmark' should be used as a field type whenever a
-- uniqueness constraint should guarantee that a certain kind of
-- record may appear at most once, but other kinds of records may
-- appear any number of times.
--
-- /NOTE:/ You need to mark any @Checkmark@ fields as @nullable@
-- (see the following example).
--
-- For example, suppose there's a @Location@ entity that
-- represents where a user has lived:
--
-- @
-- Location
-- user UserId
-- name Text
-- current Checkmark nullable
--
-- UniqueLocation user current
-- @
--
-- The @UniqueLocation@ constraint allows any number of
-- 'Inactive' @Location@s to be @current@. However, there may be
-- at most one @current@ @Location@ per user (i.e., either zero
-- or one per user).
--
-- This data type works because of the way that SQL treats
-- @NULL@able fields within uniqueness constraints. The SQL
-- standard says that @NULL@ values should be considered
-- different, so we represent 'Inactive' as SQL @NULL@, thus
-- allowing any number of 'Inactive' records. On the other hand,
-- we represent 'Active' as @TRUE@, so the uniqueness constraint
-- will disallow more than one 'Active' record.
--
-- /Note:/ There may be DBMSs that do not respect the SQL
-- standard's treatment of @NULL@ values on uniqueness
-- constraints, please check if this data type works before
-- relying on it.
--
-- The SQL @BOOLEAN@ type is used because it's the smallest data
-- type available. Note that we never use @FALSE@, just @TRUE@
-- and @NULL@. Provides the same behavior @Maybe ()@ would if
-- @()@ was a valid 'PersistField'.
data Checkmark = Active
-- ^ When used on a uniqueness constraint, there
-- may be at most one 'Active' record.
| Inactive
-- ^ When used on a uniqueness constraint, there
-- may be any number of 'Inactive' records.
deriving (Eq, Ord, Read, Show, Enum, Bounded)
instance PathPiece Checkmark where
toPathPiece = pack . show
fromPathPiece txt =
case reads (T.unpack txt) of
[(a, "")] -> Just a
_ -> Nothing
data IsNullable = Nullable !WhyNullable
| NotNullable
deriving (Eq, Show)
-- | The reason why a field is 'nullable' is very important. A
-- field that is nullable because of a @Maybe@ tag will have its
-- type changed from @A@ to @Maybe A@. OTOH, a field that is
-- nullable because of a @nullable@ tag will remain with the same
-- type.
data WhyNullable = ByMaybeAttr
| ByNullableAttr
deriving (Eq, Show)
data EntityDef sqlType = EntityDef
{ entityHaskell :: !HaskellName
, entityDB :: !DBName
, entityID :: !DBName
, entityAttrs :: ![Attr]
, entityFields :: ![FieldDef sqlType]
, entityPrimary :: Maybe PrimaryDef
, entityUniques :: ![UniqueDef]
, entityForeigns:: ![ForeignDef]
, entityDerives :: ![Text]
, entityExtra :: !(Map Text [ExtraLine])
, entitySum :: !Bool
}
deriving (Show, Eq, Read, Ord, Functor)
type ExtraLine = [Text]
newtype HaskellName = HaskellName { unHaskellName :: Text }
deriving (Show, Eq, Read, Ord)
newtype DBName = DBName { unDBName :: Text }
deriving (Show, Eq, Read, Ord)
type Attr = Text
data FieldType
= FTTypeCon (Maybe Text) Text
-- ^ Optional module and name.
| FTApp FieldType FieldType
| FTList FieldType
deriving (Show, Eq, Read, Ord)
data FieldDef sqlType = FieldDef
{ fieldHaskell :: !HaskellName -- ^ name of the field
, fieldDB :: !DBName
, fieldType :: !FieldType
, fieldSqlType :: !sqlType
, fieldAttrs :: ![Attr] -- ^ user annotations for a field
, fieldStrict :: !Bool -- ^ a strict field in the data type. Default: true
, fieldEmbedded :: Maybe (EntityDef ()) -- ^ indicates that the field uses an embedded entity
}
deriving (Show, Eq, Read, Ord, Functor)
data UniqueDef = UniqueDef
{ uniqueHaskell :: !HaskellName
, uniqueDBName :: !DBName
, uniqueFields :: ![(HaskellName, DBName)]
, uniqueAttrs :: ![Attr]
}
deriving (Show, Eq, Read, Ord)
data PrimaryDef = PrimaryDef
{ primaryFields :: ![(HaskellName, DBName)]
, primaryAttrs :: ![Attr]
}
deriving (Show, Eq, Read, Ord)
data ForeignDef = ForeignDef
{ foreignRefTableHaskell :: !HaskellName
, foreignRefTableDBName :: !DBName
, foreignConstraintNameHaskell :: !HaskellName
, foreignConstraintNameDBName :: !DBName
, foreignFields :: ![(HaskellName, DBName, HaskellName, DBName)] -- foreignkey name gb our field plus corresponding other primary field:make this a real adt
, foreignAttrs :: ![Attr]
}
deriving (Show, Eq, Read, Ord)
data PersistException
= PersistError Text -- ^ Generic Exception
| PersistMarshalError Text
| PersistInvalidField Text
| PersistForeignConstraintUnmet Text
| PersistMongoDBError Text
| PersistMongoDBUnsupported Text
deriving (Show, Typeable)
instance Exception PersistException
instance Error PersistException where
strMsg = PersistError . pack
-- | Avoid orphan instances.
newtype ZT = ZT ZonedTime deriving (Show, Read, Typeable)
instance Eq ZT where
ZT a /= ZT b = zonedTimeToLocalTime a /= zonedTimeToLocalTime b || zonedTimeZone a /= zonedTimeZone b
instance Ord ZT where
ZT a `compare` ZT b = zonedTimeToUTC a `compare` zonedTimeToUTC b
-- | A raw value which can be stored in any backend and can be marshalled to
-- and from a 'PersistField'.
data PersistValue = PersistText Text
| PersistByteString ByteString
| PersistInt64 Int64
| PersistDouble Double
| PersistRational Rational
| PersistBool Bool
| PersistDay Day
| PersistTimeOfDay TimeOfDay
| PersistUTCTime UTCTime
| PersistZonedTime ZT
| PersistNull
| PersistList [PersistValue]
| PersistMap [(Text, PersistValue)]
| PersistObjectId ByteString -- ^ Intended especially for MongoDB backend
| PersistDbSpecific ByteString -- ^ Using 'PersistDbSpecific' allows you to use types specific to a particular backend
-- For example, below is a simple example of the PostGIS geography type:
--
-- @
-- data Geo = Geo ByteString
--
-- instance PersistField Geo where
-- toPersistValue (Geo t) = PersistDbSpecific t
--
-- fromPersistValue (PersistDbSpecific t) = Right $ Geo $ Data.ByteString.concat ["'", t, "'"]
-- fromPersistValue _ = Left "Geo values must be converted from PersistDbSpecific"
--
-- instance PersistFieldSql Geo where
-- sqlType _ = SqlOther "GEOGRAPHY(POINT,4326)"
--
-- toPoint :: Double -> Double -> Geo
-- toPoint lat lon = Geo $ Data.ByteString.concat ["'POINT(", ps $ lon, " ", ps $ lat, ")'"]
-- where ps = Data.Text.pack . show
-- @
--
-- If Foo has a geography field, we can then perform insertions like the following:
--
-- @
-- insert $ Foo (toPoint 44 44)
-- @
--
deriving (Show, Read, Eq, Typeable, Ord)
instance PathPiece PersistValue where
fromPathPiece t =
case Data.Text.Read.signed Data.Text.Read.decimal t of
Right (i, t')
| T.null t' -> Just $ PersistInt64 i
_ -> case reads $ T.unpack t of
[(fks, "")] -> Just $ PersistList fks
_ -> Just $ PersistText t
toPathPiece x =
case fromPersistValueText x of
Left e -> error e
Right y -> y
fromPersistValueText :: PersistValue -> Either String Text
fromPersistValueText (PersistText s) = Right s
fromPersistValueText (PersistByteString bs) =
Right $ TE.decodeUtf8With lenientDecode bs
fromPersistValueText (PersistInt64 i) = Right $ T.pack $ show i
fromPersistValueText (PersistDouble d) = Right $ T.pack $ show d
fromPersistValueText (PersistRational r) = Right $ T.pack $ show r
fromPersistValueText (PersistDay d) = Right $ T.pack $ show d
fromPersistValueText (PersistTimeOfDay d) = Right $ T.pack $ show d
fromPersistValueText (PersistUTCTime d) = Right $ T.pack $ show d
fromPersistValueText (PersistZonedTime (ZT z)) = Right $ T.pack $ show z
fromPersistValueText PersistNull = Left "Unexpected null"
fromPersistValueText (PersistBool b) = Right $ T.pack $ show b
fromPersistValueText (PersistList _) = Left "Cannot convert PersistList to Text"
fromPersistValueText (PersistMap _) = Left "Cannot convert PersistMap to Text"
fromPersistValueText (PersistObjectId _) = Left "Cannot convert PersistObjectId to Text"
fromPersistValueText (PersistDbSpecific _) = Left "Cannot convert PersistDbSpecific to Text"
instance A.ToJSON PersistValue where
toJSON (PersistText t) = A.String $ T.cons 's' t
toJSON (PersistByteString b) = A.String $ T.cons 'b' $ TE.decodeUtf8 $ B64.encode b
toJSON (PersistInt64 i) = A.Number $ fromIntegral i
toJSON (PersistDouble d) = A.Number $
#if MIN_VERSION_aeson(0, 7, 0)
Data.Scientific.fromFloatDigits
#else
AN.D
#endif
d
toJSON (PersistRational r) = A.String $ T.pack $ 'r' : show r
toJSON (PersistBool b) = A.Bool b
toJSON (PersistTimeOfDay t) = A.String $ T.pack $ 't' : show t
toJSON (PersistUTCTime u) = A.String $ T.pack $ 'u' : show u
toJSON (PersistZonedTime z) = A.String $ T.pack $ 'z' : show z
toJSON (PersistDay d) = A.String $ T.pack $ 'd' : show d
toJSON PersistNull = A.Null
toJSON (PersistList l) = A.Array $ V.fromList $ map A.toJSON l
toJSON (PersistMap m) = A.object $ map (second A.toJSON) m
toJSON (PersistDbSpecific b) = A.String $ T.cons 'p' $ TE.decodeUtf8 $ B64.encode b
toJSON (PersistObjectId o) =
A.toJSON $ showChar 'o' $ showHexLen 8 (bs2i four) $ showHexLen 16 (bs2i eight) ""
where
(four, eight) = BS8.splitAt 4 o
-- taken from crypto-api
bs2i :: ByteString -> Integer
bs2i bs = foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0 bs
{-# INLINE bs2i #-}
-- showHex of n padded with leading zeros if necessary to fill d digits
-- taken from Data.BSON
showHexLen :: (Show n, Integral n) => Int -> n -> ShowS
showHexLen d n = showString (replicate (d - sigDigits n) '0') . showHex n where
sigDigits 0 = 1
sigDigits n' = truncate (logBase (16 :: Double) $ fromIntegral n') + 1
instance A.FromJSON PersistValue where
parseJSON (A.String t0) =
case T.uncons t0 of
Nothing -> fail "Null string"
Just ('p', t) -> either (fail "Invalid base64") (return . PersistDbSpecific)
$ B64.decode $ TE.encodeUtf8 t
Just ('s', t) -> return $ PersistText t
Just ('b', t) -> either (fail "Invalid base64") (return . PersistByteString)
$ B64.decode $ TE.encodeUtf8 t
Just ('t', t) -> fmap PersistTimeOfDay $ readMay t
Just ('u', t) -> fmap PersistUTCTime $ readMay t
Just ('z', t) -> fmap PersistZonedTime $ readMay t
Just ('d', t) -> fmap PersistDay $ readMay t
Just ('r', t) -> fmap PersistRational $ readMay t
Just ('o', t) -> maybe (fail "Invalid base64") (return . PersistObjectId) $
fmap (i2bs (8 * 12) . fst) $ headMay $ readHex $ T.unpack t
Just (c, _) -> fail $ "Unknown prefix: " ++ [c]
where
headMay [] = Nothing
headMay (x:_) = Just x
readMay :: (Read a, Monad m) => T.Text -> m a
readMay t =
case reads $ T.unpack t of
(x, _):_ -> return x
[] -> fail "Could not read"
-- taken from crypto-api
-- |@i2bs bitLen i@ converts @i@ to a 'ByteString' of @bitLen@ bits (must be a multiple of 8).
i2bs :: Int -> Integer -> BS.ByteString
i2bs l i = BS.unfoldr (\l' -> if l' < 0 then Nothing else Just (fromIntegral (i `shiftR` l'), l' - 8)) (l-8)
{-# INLINE i2bs #-}
#if MIN_VERSION_aeson(0, 7, 0)
parseJSON (A.Number n) = return $
if fromInteger (floor n) == n
then PersistInt64 $ floor n
else PersistDouble $ fromRational $ toRational n
#else
parseJSON (A.Number (AN.I i)) = return $ PersistInt64 $ fromInteger i
parseJSON (A.Number (AN.D d)) = return $ PersistDouble d
#endif
parseJSON (A.Bool b) = return $ PersistBool b
parseJSON A.Null = return $ PersistNull
parseJSON (A.Array a) = fmap PersistList (mapM A.parseJSON $ V.toList a)
parseJSON (A.Object o) =
fmap PersistMap $ mapM go $ HM.toList o
where
go (k, v) = fmap ((,) k) $ A.parseJSON v
-- | A SQL data type. Naming attempts to reflect the underlying Haskell
-- datatypes, eg SqlString instead of SqlVarchar. Different SQL databases may
-- have different translations for these types.
data SqlType = SqlString
| SqlInt32
| SqlInt64
| SqlReal
| SqlNumeric Word32 Word32
| SqlBool
| SqlDay
| SqlTime
| SqlDayTime
| SqlDayTimeZoned
| SqlBlob
| SqlOther T.Text -- ^ a backend-specific name
deriving (Show, Read, Eq, Typeable, Ord)
newtype KeyBackend backend entity = Key { unKey :: PersistValue }
deriving (Show, Read, Eq, Ord)
type family KeyEntity key
type instance KeyEntity (KeyBackend backend entity) = entity
instance A.ToJSON (KeyBackend backend entity) where
toJSON (Key val) = A.toJSON val
instance A.FromJSON (KeyBackend backend entity) where
parseJSON = fmap Key . A.parseJSON
data PersistFilter = Eq | Ne | Gt | Lt | Ge | Le | In | NotIn
| BackendSpecificFilter T.Text
deriving (Read, Show)
data UpdateGetException = KeyNotFound String
deriving Typeable
instance Show UpdateGetException where
show (KeyNotFound key) = "Key not found during updateGet: " ++ key
instance Exception UpdateGetException
data PersistUpdate = Assign | Add | Subtract | Multiply | Divide -- FIXME need something else here
deriving (Read, Show, Enum, Bounded)
|