{-# LANGUAGE PatternGuards #-} ----------------------------------------------------------------------------- -- | -- Module : Text.CSL.Eval.Output -- Copyright : (c) Andrea Rossato -- License : BSD-style (see LICENSE) -- -- Maintainer : Andrea Rossato -- Stability : unstable -- Portability : unportable -- -- The CSL implementation -- ----------------------------------------------------------------------------- module Text.CSL.Eval.Output where import Text.CSL.Style output :: Formatting -> String -> [Output] output fm s | ' ':xs <- s = OSpace : output fm xs | [] <- s = [] | otherwise = [OStr s fm] appendOutput :: Formatting -> [Output] -> [Output] appendOutput fm xs = if xs /= [] then [Output xs fm] else [] outputList :: Formatting -> Delimiter -> [Output] -> [Output] outputList fm d = appendOutput fm . addDelim d cleanOutput :: [Output] -> [Output] cleanOutput = flatten where flatten [] = [] flatten (o:os) | ONull <- o = flatten os | Output [] _ <- o = flatten os | OStr [] _ <- o = flatten os | Output xs f <- o , f == emptyFormatting = flatten xs ++ flatten os | otherwise = o : flatten os addDelim :: String -> [Output] -> [Output] addDelim d = foldr (\x xs -> if length xs < 1 then x : xs else check x xs) [] where check x xs | ONull <- x = xs | otherwise = x : ODel d : xs noOutputError :: Output noOutputError = OStr "[CSL STYLE ERROR: reference with no printed form.]" emptyFormatting noBibDataError :: Cite -> Output noBibDataError c = OStr ("[CSL BIBLIOGRAPHIC DATA ERROR: reference " ++ show (citeId c) ++ " not found.]") emptyFormatting (<++>) :: [Output] -> [Output] -> [Output] [] <++> o = o o <++> [] = o o1 <++> o2 = o1 ++ [OSpace] ++ o2