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.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
data Checkmark = Active
                 
                 
               | Inactive
                 
                 
    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)
data WhyNullable = ByMaybeAttr
                 | ByNullableAttr
                  deriving (Eq, Show)
data EntityDef = EntityDef
    { entityHaskell :: !HaskellName
    , entityDB      :: !DBName
    , entityID      :: !DBName
    , entityAttrs   :: ![Attr]
    , entityFields  :: ![FieldDef]
    , entityPrimary :: Maybe PrimaryDef
    , entityUniques :: ![UniqueDef]
    , entityForeigns:: ![ForeignDef]
    , entityDerives :: ![Text]
    , entityExtra   :: !(Map Text [ExtraLine])
    , entitySum     :: !Bool
    }
    deriving (Show, Eq, Read, Ord)
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
      
    | FTApp FieldType FieldType
    | FTList FieldType
  deriving (Show, Eq, Read, Ord)
data FieldDef = FieldDef
    { fieldHaskell   :: !HaskellName 
    , fieldDB        :: !DBName
    , fieldType      :: !FieldType
    , fieldSqlType   :: !SqlType
    , fieldAttrs     :: ![Attr]   
    , fieldStrict    :: !Bool      
    , fieldReference :: !ReferenceDef
    }
    deriving (Show, Eq, Read, Ord)
data ReferenceDef = ForeignRef !HaskellName
                  | EmbedRef EmbedEntityDef
                  | NoReference
                  deriving (Show, Eq, Read, Ord)
data EmbedEntityDef = EmbedEntityDef
    { embeddedHaskell :: !HaskellName
    , embeddedFields  :: ![EmbedFieldDef]
    } deriving (Show, Eq, Read, Ord)
data EmbedFieldDef = EmbedFieldDef
    { emFieldDB       :: !DBName
    , emFieldEmbed :: Maybe EmbedEntityDef
    }
    deriving (Show, Eq, Read, Ord)
toEmbedEntityDef :: EntityDef -> EmbedEntityDef
toEmbedEntityDef ent = EmbedEntityDef
  { embeddedHaskell = entityHaskell ent
  , embeddedFields = map toEmbedFieldDef $ entityFields ent
  }
toEmbedFieldDef :: FieldDef -> EmbedFieldDef
toEmbedFieldDef field =
  EmbedFieldDef { emFieldDB       = fieldDB field
                   , emFieldEmbed = case fieldReference field of
                       EmbedRef em -> Just em
                       _ -> Nothing
                   }
data UniqueDef = UniqueDef
    { uniqueHaskell :: !HaskellName
    , uniqueDBName  :: !DBName
    , uniqueFields  :: ![(HaskellName, DBName)]
    , uniqueAttrs   :: ![Attr]
    }
    deriving (Show, Eq, Read, Ord)
data PrimaryDef = PrimaryDef
    { primaryFields  :: ![FieldDef]
    , primaryAttrs   :: ![Attr]
    }
    deriving (Show, Eq, Read, Ord)
type ForeignFieldDef = (HaskellName, DBName)
data ForeignDef = ForeignDef
    { foreignRefTableHaskell       :: !HaskellName
    , foreignRefTableDBName        :: !DBName
    , foreignConstraintNameHaskell :: !HaskellName
    , foreignConstraintNameDBName  :: !DBName
    , foreignFields                :: ![(ForeignFieldDef, ForeignFieldDef)] 
    , foreignAttrs                 :: ![Attr]
    , foreignNullable              :: Bool
    }
    deriving (Show, Eq, Read, Ord)
data PersistException
  = PersistError Text 
  | PersistMarshalError Text
  | PersistInvalidField Text
  | PersistForeignConstraintUnmet Text
  | PersistMongoDBError Text
  | PersistMongoDBUnsupported Text
    deriving (Show, Typeable)
instance Exception PersistException
instance Error PersistException where
    strMsg = PersistError . pack
data PersistValue = PersistText Text
                  | PersistByteString ByteString
                  | PersistInt64 Int64
                  | PersistDouble Double
                  | PersistRational Rational
                  | PersistBool Bool
                  | PersistDay Day
                  | PersistTimeOfDay TimeOfDay
                  | PersistUTCTime UTCTime
                  | PersistNull
                  | PersistList [PersistValue]
                  | PersistMap [(Text, PersistValue)]
                  | PersistObjectId ByteString 
                  | PersistDbSpecific ByteString 
    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 $ T.unpack e
            Right y -> y
fromPersistValueText :: PersistValue -> Either Text 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 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 (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
         
         bs2i :: ByteString -> Integer
         bs2i bs = foldl' (\i b -> (i `shiftL` 8) + fromIntegral b) 0 bs
         
         
         
         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 ('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"
        
        
        i2bs :: Int -> Integer -> BS.ByteString
        i2bs l i = BS.unfoldr (\l' -> if l' < 0 then Nothing else Just (fromIntegral (i `shiftR` l'), l'  8)) (l8)
        
#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
data SqlType = SqlString
             | SqlInt32
             | SqlInt64
             | SqlReal
             | SqlNumeric Word32 Word32
             | SqlBool
             | SqlDay
             | SqlTime
             | SqlDayTime 
             | SqlBlob
             | SqlOther T.Text 
    deriving (Show, Read, Eq, Typeable, Ord)
data PersistFilter = Eq | Ne | Gt | Lt | Ge | Le | In | NotIn
                   | BackendSpecificFilter T.Text
    deriving (Read, Show)
data UpdateException = KeyNotFound String
                     | UpsertError String
    deriving Typeable
instance Show UpdateException where
    show (KeyNotFound key) = "Key not found during updateGet: " ++ key
    show (UpsertError msg) = "Error during upsert: " ++ msg
instance Exception UpdateException
data OnlyUniqueException = OnlyUniqueException String deriving Typeable
instance Show OnlyUniqueException where
    show (OnlyUniqueException uniqueMsg) =
      "Expected only one unique key, got " ++ uniqueMsg
instance Exception OnlyUniqueException
data PersistUpdate = Assign | Add | Subtract | Multiply | Divide 
    deriving (Read, Show, Enum, Bounded)