微信公众号搜"智元新知"关注
微信扫一扫可直接关注哦!

从SQL数据库反序列化数据

如何解决从SQL数据库反序列化数据

HDBC库中似乎没有任何标准方法可用于此目的。如果您感觉特别敏锐,则可以用自己的机器来滚动GHC.Generics,尽管治愈方法可能比疾病还差!

我还添加了反向转换,但是如果需要,您可以省去/拆分类

{-# LANGUAGE DeriveAnyClass, DeriveGeneric, DefaultSignatures
           , TypeOperators, FlexibleContexts, FlexibleInstances
           , TypeSynonymInstances #-}

import Data.Convertible
import Database.HDBC


import Data.Coercible -- not strictly necessary
import GHC.Generics

-- serialization for Generic Rep-resentations
class GsqlConvert f where
    gFromsqlValuesImpl :: [sqlValue] -> (f a, [sqlValue])
    gTosqlValuesImpl :: f a -> [sqlValue] -> [sqlValue]

-- no data, no representation
instance GsqlConvert U1 where
    gFromsqlValuesImpl vs = (U1, vs)
    gTosqlValuesImpl U1 vs = vs

-- multiple things are stored in order
instance (GsqlConvert a, GsqlConvert b) => GsqlConvert (a :*: b) where
    gFromsqlValuesImpl vs =
        let (a, vs1) = gFromsqlValuesImpl vs
            (b, vs2) = gFromsqlValuesImpl vs1
         in (a :*: b, vs2)
    gTosqlValuesImpl (a :*: b) = gTosqlValuesImpl a . gTosqlValuesImpl b

-- note no instance for a :+: b, so no support for unions

-- ignore Metadata
instance GsqlConvert a => GsqlConvert (M1 i c a) where
    gFromsqlValuesImpl = coerce . gFromsqlValuesImpl
    gTosqlValuesImpl = gTosqlValuesImpl . unM1

-- delegate to the members' serializers
instance sqlConvert a => GsqlConvert (K1 i a) where
    gFromsqlValuesImpl = coerce . fromsqlValuesImpl
    gTosqlValuesImpl = tosqlValuesImpl . unK1

-- serialization for normal data types
-- some types are "primitive" and have their own serialization code
-- other types are serialized via the default implementations,
-- which are based on Generic
-- the defaults convert the data into a generic representation and let
-- the GsqlConvert class decide how to serialize the generic representation
class sqlConvert a where
    fromsqlValuesImpl :: [sqlValue] -> (a, [sqlValue])
    default fromsqlValuesImpl :: (Generic a, GsqlConvert (Rep a))
                              => [sqlValue] -> (a, [sqlValue])
    fromsqlValuesImpl vs =
        let (rep, vs1) = gFromsqlValuesImpl vs
         in (to rep, vs1)

    tosqlValuesImpl :: a -> [sqlValue] -> [sqlValue]
    default tosqlValuesImpl :: (Generic a, GsqlConvert (Rep a))
                            => a -> [sqlValue] -> [sqlValue]
    tosqlValuesImpl a vs = gTosqlValuesImpl (from a) vs

fromsqlValuesImplPrim :: Convertible sqlValue a
                      => [sqlValue] -> (a, [sqlValue])
-- no error checking
fromsqlValuesImplPrim (v:vs) = (fromsql v, vs)

tosqlValuesImplPrim :: Convertible a sqlValue
                    => a -> [sqlValue] -> [sqlValue]
tosqlValuesImplPrim a vs = tosql a:vs

instance sqlConvert Int where
    fromsqlValuesImpl = fromsqlValuesImplPrim
    tosqlValuesImpl = tosqlValuesImplPrim
instance sqlConvert String where
    fromsqlValuesImpl = fromsqlValuesImplPrim
    tosqlValuesImpl = tosqlValuesImplPrim

fromsqlValues :: sqlConvert t => [sqlValue] -> t
 -- no error checking for unused values
fromsqlValues = fst . fromsqlValuesImpl

tosqlValues :: sqlConvert t => t -> [sqlValue]
tosqlValues v = tosqlValuesImpl v []

-- and Now given all the above machinery, the conversion
-- for Whatever comes for free:
data Whatever = Whatever Int Int String String
    deriving (Show, Generic, sqlConvert)

{-
-- DeriveGeneric produces:
instance Generic Whatever where
  type Rep Whatever = D1 _ (C1 _ (
                            (S1 _ (Rec0 Int) :*: S1 _ (Rec0 Int))
                        :*: (S1 _ (Rec0 String) :*: S1 _ (Rec0 String))
                      ))
  to = _; from = _
-- There is an instance for GsqlConvert (Rep Whatever)
-- DeriveAnyClass produces
instance sqlConvert Whatever where
-- DefaultSignatures uses the default implementations from the class declaration
-- to implement the methods
   fromsqlValuesImpl = _; tosqlValuesImpl = _
-}

解决方法

我有一个由数据库支持的小应用程序(SQLite,但与问题无关)。我已经定义了一些类型,例如:

data Whatever = Whatever Int Int String String
data ImportantStuff = ImportantStuff { id :: Int,count :: Int,name :: String,description :: String }

这些类型映射到数据库中的表。当我读取数据时,我最终会写出这样的函数:

whateverFromDB :: [SqlValue] -> Whatever
whateverFromDB (a:b:c:d:_) = Whatever (fromSql a) (fromSql b) (fromSql c) (fromSql d)

(为了清楚起见,我省略了处理错误。)

编写这样的函数确实很烦人,感觉就像创建了很多样板。有没有更惯用的方法将一组SqlValues转换为Haskell数据?

版权声明:本文内容由互联网用户自发贡献,该文观点与技术仅代表作者本人。本站仅提供信息存储空间服务,不拥有所有权,不承担相关法律责任。如发现本站有涉嫌侵权/违法违规的内容, 请发送邮件至 dio@foxmail.com 举报,一经查实,本站将立刻删除。