0

我有一个相当简单的查询,它执行两个外连接。(一顿饭有许多食谱,而食谱又包含许多食物)。

getMeals :: (MonadIO m) => Key DbUser -> SqlPersistT m [Meal]
getMeals user =
  fmap deserializeDb $ E.select $
        E.from $ \(m `E.InnerJoin` u `E.LeftOuterJoin` r `E.LeftOuterJoin` f) -> do
          E.on     (r ?. DbRecipeId E.==. f ?. DbFoodRecipeId)
          E.on     (E.just (m ^. DbMealId) E.==. r ?. DbRecipeMealId)
          E.on     (m ^. DbMealUserId      E.==. u ^. DbUserId)
          E.where_ (m ^. DbMealUserId      E.==. E.val user )
          return (m, r, f)

这个查询很棒,它说明了它需要什么,没有更多内容。但是,由于 SQL 的工作方式,它为我返回了一个包含大量重复膳食的表,对于每个匹配的外部连接。

例如,一顿饭有两个食谱,每个食谱有两种食物,变成 4 个元组。

(m1, r1, f1)
(m1, r1, f2)
(m1, r2, f3)
(m1, r2, f4)

我想将这些回滚为单一Meal数据类型。(此处简化以显示结构,其他字段当然存储在数据库中)。

data Meal   = Meal   { recipes :: [Recipe] }
data Recipe = Recipe { foods :: [Food]   }
data Food   = Food   { name :: String }

我似乎必须完全手动进行此合并,而对于这个单个查询,它最终变成了 2 页左右的代码。

忽略不应该像这样使用类型类的事实,它看起来像一个(愚蠢的)类型类的很多实例DeserializeDb

class DeserializeDb a r | a -> r where
  deserializeDb :: a -> r

instance DeserializeDb [(Entity DbMeal, Maybe (Entity DbRecipe))] [Meal] where
  deserializeDb items = let grouped = groupBy (\a b -> entityKey (fst a) == entityKey (fst b)) items
                            joined  = map (\list -> ( (fst . head) list
                                                    ,  mapMaybe snd list
                                                    )) grouped
                        in (map deserializeDb joined)

剪辑了许多复杂性的实例(代码: https ://gist.github.com/cschneid/2989057ec4bb9875e2ae )

instance DeserializeDb (Entity DbFood) Food where
  deserializeDb (Entity _ val) = Food (dbFoodName val)

问题:

我唯一要公开的是查询签名。其余的都是实施垃圾。有没有我没有注意到的使用 Persistent 的技巧?我是否必须手动将连接合并回haskell类型?

4

1 回答 1

1

多亏了@JPMoresmau 的暗示,我最终得到了一个更短且我认为更简单的方法。由于 ,它在大型数据集上可能会更慢nub,但在小型数据集上,它的返回速度比我需要的要快得多。

我仍然讨厌我有这么多的手动管道来根据从数据库返回的数据构建树结构。我想知道是否有一般的好方法可以做到这一点?

module Grocery.Database.Calendar where

import Grocery.DatabaseSchema
import Grocery.Types.Meal
import Grocery.Types.Recipe
import Grocery.Types.Food
import Database.Persist
import Database.Persist.Sqlite
import qualified Database.Esqueleto      as E
import           Database.Esqueleto      ((^.), (?.))
import Data.Time
import Control.Monad.Trans -- for MonadIO
import Data.List
import Data.Maybe
import Data.Tuple3

getMeals :: (MonadIO m) => Key DbUser -> SqlPersistT m [Meal]
getMeals user =
  fmap deserializeDb $ E.select $
        E.from $ \(m `E.InnerJoin` u `E.LeftOuterJoin` r `E.LeftOuterJoin` f) -> do
          E.on     (r ?. DbRecipeId E.==. f ?. DbFoodRecipeId)
          E.on     (E.just (m ^. DbMealId) E.==. r ?. DbRecipeMealId)
          E.on     (m ^. DbMealUserId      E.==. u ^. DbUserId)
          E.where_ (m ^. DbMealUserId      E.==. E.val user )
          return (m, r, f)

deserializeDb :: [(Entity DbMeal, Maybe (Entity DbRecipe), Maybe (Entity DbFood))] -> [Meal]
deserializeDb results = makeMeals results
  where
    makeMeals :: [(Entity DbMeal, Maybe (Entity DbRecipe), Maybe (Entity DbFood))] -> [Meal]
    makeMeals dupedMeals = map makeMeal (nub $ map fst3 dupedMeals)

    makeMeal :: Entity DbMeal -> Meal
    makeMeal (Entity k m) = let d = dbMealDay m
                                n = dbMealName m
                                r = makeRecipesForMeal k
                            in  Meal Nothing (utctDay d) n r

    makeRecipesForMeal :: Key DbMeal -> [Recipe]
    makeRecipesForMeal mealKey = map makeRecipe $ appropriateRecipes mealKey

    appropriateRecipes :: Key DbMeal -> [Entity DbRecipe]
    appropriateRecipes mealKey = nub $ filter (\(Entity _ v) -> dbRecipeMealId v == mealKey) $ mapMaybe snd3 results

    makeRecipe :: Entity DbRecipe -> Recipe
    makeRecipe (Entity k r) = let n = dbRecipeName r
                                  f = makeFoodForRecipe k
                              in  Recipe Nothing n f

    makeFoodForRecipe :: Key DbRecipe -> [Food]
    makeFoodForRecipe rKey = map makeFood $ appropriateFoods rKey

    appropriateFoods :: Key DbRecipe -> [Entity DbFood]
    appropriateFoods rKey = nub $ filter (\(Entity _ v) -> dbFoodRecipeId v == rKey) $ mapMaybe thd3 results

    makeFood :: Entity DbFood -> Food
    makeFood (Entity _ f) = Food (dbFoodName f)
于 2015-05-05T03:33:36.563 回答