Commit ac3de094 authored by Alexandre Delanoë's avatar Alexandre Delanoë

[CLEAN] Debug trace function.

parent 96920cfd
Pipeline #27 failed with stage
...@@ -23,8 +23,6 @@ Ngrams connection to the Database. ...@@ -23,8 +23,6 @@ Ngrams connection to the Database.
module Gargantext.Database.Ngrams where module Gargantext.Database.Ngrams where
-- import Opaleye
import Debug.Trace (trace)
import Prelude (Enum, Bounded, minBound, maxBound) import Prelude (Enum, Bounded, minBound, maxBound)
import Control.Lens (makeLenses, view) import Control.Lens (makeLenses, view)
import Data.ByteString.Internal (ByteString) import Data.ByteString.Internal (ByteString)
...@@ -224,10 +222,8 @@ getNgramsTableData :: DPS.Connection ...@@ -224,10 +222,8 @@ getNgramsTableData :: DPS.Connection
-> NodeType -> NgramsType -> NodeType -> NgramsType
-> NgramsTableParamUser -> NgramsTableParamMaster -> NgramsTableParamUser -> NgramsTableParamMaster
-> IO [NgramsTableData] -> IO [NgramsTableData]
getNgramsTableData conn nodeT ngrmT (NgramsTableParam ul uc) (NgramsTableParam ml mc) = do getNgramsTableData conn nodeT ngrmT (NgramsTableParam ul uc) (NgramsTableParam ml mc) =
_ <- trace $ show (ul,uc,nodeTId,ngrmTId,ml,mc,nodeTId,ngrmTId,uc)
map (\(t,n,nt,w) -> NgramsTableData t n (fromListTypeId nt) w) map (\(t,n,nt,w) -> NgramsTableData t n (fromListTypeId nt) w)
-- <$> DPS.query conn querySelectTableNgrams (ul,uc,nodeTId,ngrmTId,ml,mc,nodeTId,ngrmTId)
<$> DPS.query conn querySelectTableNgrams (ul,uc,nodeTId,ngrmTId,ml,mc,nodeTId,ngrmTId,uc) <$> DPS.query conn querySelectTableNgrams (ul,uc,nodeTId,ngrmTId,ml,mc,nodeTId,ngrmTId,uc)
where where
nodeTId = nodeTypeId nodeT nodeTId = nodeTypeId nodeT
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment