Skip to content
This repository has been archived by the owner on Apr 30, 2021. It is now read-only.

Commit

Permalink
Keep position of citations with prefixes when sorting.
Browse files Browse the repository at this point in the history
Closes #292.

If citations with prefixes are moved around, gibberish can
result.  E.g.:

    A fascinating research tidbit [@Zanadu1999, p. 35; see for comparison
    @Aalto2005] ...

can become

   A fascinating research tidbit (see for comparison Aalto, 2005;
   Zanadu, 1999: 35)

with a sorting style like sage-harvard.csl.

This change causes sorting to be applied only to subgroups of citations
within the group that lack prefixes.
  • Loading branch information
jgm committed Jan 19, 2018
1 parent 480d343 commit 31b463a
Showing 1 changed file with 15 additions and 1 deletion.
16 changes: 15 additions & 1 deletion src/Text/CSL/Proc.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternGuards #-}
-----------------------------------------------------------------------------
-- |
Expand All @@ -19,6 +20,7 @@ module Text.CSL.Proc where

import Control.Applicative ((<|>))
import Control.Arrow (second, (&&&), (>>>))
import Control.Monad.State (execState, modify)
import Data.Aeson
import Data.Char (isDigit, isLetter, toLower)
import Data.List
Expand Down Expand Up @@ -304,7 +306,19 @@ procGroup Style {citation = ct, csMacros = ms , styleLocale = l,
format (c,r) = (c, evalLayout (citLayout ct) (EvalCite c) False l ms opts' as r)
sort_ (c,r) = evalSorting (EvalSorting c) l ms opts' (citSort ct) as r
process = map (second (flip Output emptyFormatting) . format &&& sort_)
result = sortItems $ process cr
result = concatMap sortItems $ toChunks $ process cr
-- toChunks splits the citations up into groups, such that
-- a citation with a non-null prefix is by itself in its
-- group, otherwise preserving the order (see #292 for
-- motivation; we don't want to move prefixed citations
-- around)
toChunks xs = reverse $ execState (toChunks' xs) []
toChunks' xs = do
case break hasPrefix xs of
([], []) -> return ()
([], y:ys) -> modify ([y]:) >> toChunks' ys
(zs, ys) -> modify (zs:) >> toChunks' ys
hasPrefix ((c,_),_) = citePrefix c /= mempty

formatBiblioLayout :: Formatting -> Delimiter -> [Output] -> [Output]
formatBiblioLayout f d = appendOutput f . addDelim d
Expand Down

0 comments on commit 31b463a

Please sign in to comment.