Skip to content

Instantly share code, notes, and snippets.

@Nnwww
Last active May 29, 2017 03:22
Show Gist options
  • Save Nnwww/83c592f938b9a427aad0bf1535e0bd22 to your computer and use it in GitHub Desktop.
Save Nnwww/83c592f938b9a427aad0bf1535e0bd22 to your computer and use it in GitHub Desktop.
nDCG in Haskell. Additionally, I draw graphs and serialize to csv (using Chart and Cassava).
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
module Lib
( writeNDCGs
, serializeNDCG
) where
import Data.List
import Graphics.Rendering.Chart.Easy
import Graphics.Rendering.Chart.Backend.Diagrams
import Control.Lens
import GHC.Generics
import qualified Data.Csv as DC
cg :: [Double] -> [Double]
cg gx = unfoldr consCG (0.0, gx)
where
consCG (_, []) = Nothing
consCG (m, h:t) = Just (m + h, (m + h, t))
dcg :: [Double] -> [Double]
dcg (h : tgx) = h : unfoldr consDCG (2, h, tgx)
where
l2 x = logBase 2 x
consDCG (_, _, []) = Nothing
consDCG (i, m, h:t) =
let term = m + h / l2 i in
Just (term, (succ i, term, t))
icg :: [Double] -> [Double]
icg gx = sortBy (flip $ compare) gx
ndcg :: [Double] -> [Double]
ndcg gx = map (\(a,b) -> a/b) $ zip (dcg gx) (dcg . icg $ gx)
writeNDCGs :: Foldable t => t [Double] -> IO ()
writeNDCGs gxs = toFile def{_fo_format=SVG} "example.svg" $ do
layout_title .= "Comparison between Google and Bing"
layout_x_axis . laxis_title .= "Rank (Top20)"
layout_y_axis . laxis_title .= "nDCG"
mapM_ (plot . line "Google" . (: []) . zip [0.0 :: Double ..] . ndcg) gxs
-- plot (line "Bing" [zip [0.0 :: Double ..] (ndcg gB)])
data CsvNDCG = CsvNDCG
{ _rank :: !Int
, _symbolRel :: !String
, _cg :: !Int
, _dcg :: !Double
} deriving Generic
-- instance DC.FromNamedRecord CsvNDCG
instance DC.ToNamedRecord CsvNDCG
instance DC.DefaultOrdered CsvNDCG
relToSymbol 0 = "×"
relToSymbol 1 = "△"
relToSymbol 2 = "○"
relToSymbol 3 = "◎"
serializeNDCG gx = DC.encodeDefaultOrderedByName $ zipWith4 CsvNDCG [1..] syms lcg lndcg
where
syms = map relToSymbol gx
lcg = map round $ cg gx
lndcg = dcg gx
module Main where
import Lib
import qualified Data.ByteString.Lazy as BL
-- There are results of searching by some kind of query and evaluating it in four levels.
gGoogle = [3,1,3,3,3,3,0,2,2,1,1,0,0,1,1,1,3,0,1,1]
gBing = [3,3,1,0,0,3,3,0,2,0,0,1,0,3,2,0,3,0,0,0]
main :: IO ()
main = do
writeNDCGs [gGoogle, gBing]
BL.writeFile "./ndcg.csv" (BL.concat $ map serializeNDCG [gGoogle, gBing])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment