Change head/tail to pattern guards.
This commit is contained in:
parent
a02ce74acf
commit
c15978ce5e
1 changed files with 8 additions and 7 deletions
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings, PatternGuards #-}
|
||||||
|
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2014 Jesse Rosenthal <jrosenthal@jhu.edu>
|
Copyright (C) 2014 Jesse Rosenthal <jrosenthal@jhu.edu>
|
||||||
|
@ -87,12 +87,13 @@ combineReducibles r s =
|
||||||
remaining' = conts' \\ shared
|
remaining' = conts' \\ shared
|
||||||
in
|
in
|
||||||
case null shared of
|
case null shared of
|
||||||
True -> case () of
|
True | (x : xs) <- reverse rs
|
||||||
_ | (not . null) rs && isSpace (last rs) ->
|
, isSpace x ->
|
||||||
rebuild conts (init rs) ++ [last rs, s]
|
rebuild conts (reverse xs) ++ [x, s]
|
||||||
_ | (not . null) ss && isSpace (head ss) ->
|
| (x : xs) <- ss
|
||||||
[r, head ss] ++ rebuild conts' (tail ss)
|
, isSpace x ->
|
||||||
_ -> [r,s]
|
[r, x] ++ rebuild conts' (xs)
|
||||||
|
True -> [r,s]
|
||||||
False -> rebuild
|
False -> rebuild
|
||||||
shared $
|
shared $
|
||||||
reduceList $
|
reduceList $
|
||||||
|
|
Loading…
Reference in a new issue