summaryrefslogtreecommitdiffhomepage
path: root/src
diff options
context:
space:
mode:
authorJasper Van der Jeugt <m@jaspervdj.be>2012-05-30 17:51:53 +0200
committerJasper Van der Jeugt <m@jaspervdj.be>2012-05-30 17:51:53 +0200
commit153502289ab8884ea05626dfc65b8b55e6b09405 (patch)
tree071dc4b369c5d3b041ce6c8c32100e2d366392fc /src
parenta57d329a5e123013998624870e207acebfc86c52 (diff)
downloadstylish-haskell-153502289ab8884ea05626dfc65b8b55e6b09405.tar.gz
Add a test for UnicodeSyntax
Diffstat (limited to 'src')
-rw-r--r--src/StylishHaskell/Stylish/UnicodeSyntax.hs40
-rw-r--r--src/StylishHaskell/Util.hs8
2 files changed, 33 insertions, 15 deletions
diff --git a/src/StylishHaskell/Stylish/UnicodeSyntax.hs b/src/StylishHaskell/Stylish/UnicodeSyntax.hs
index e6e9c74..308c15b 100644
--- a/src/StylishHaskell/Stylish/UnicodeSyntax.hs
+++ b/src/StylishHaskell/Stylish/UnicodeSyntax.hs
@@ -1,4 +1,5 @@
--------------------------------------------------------------------------------
+{-# LANGUAGE UnicodeSyntax #-}
module StylishHaskell.Stylish.UnicodeSyntax
( stylish
) where
@@ -22,8 +23,9 @@ import StylishHaskell.Util
--------------------------------------------------------------------------------
unicodeReplacements :: Map String String
unicodeReplacements = M.fromList
- [ ("->", "→")
+ [ ("::", "∷")
, ("=>", "⇒")
+ , ("->", "→")
]
@@ -59,13 +61,12 @@ groupPerLine = M.toList . M.fromListWith (++) .
--------------------------------------------------------------------------------
-typeFuns :: H.Module H.SrcSpanInfo -> Lines -> [((Int, Int), String)]
-typeFuns module' ls =
- [ (pos, "->")
- | H.TyFun _ t1 t2 <- everything module'
- , let start = H.srcSpanEnd $ H.srcInfoSpan $ H.ann t1
- , let end = H.srcSpanStart $ H.srcInfoSpan $ H.ann t2
- , pos <- maybeToList $ between start end "->" ls
+typeSigs :: H.Module H.SrcSpanInfo -> Lines -> [((Int, Int), String)]
+typeSigs module' ls =
+ [ (pos, "::")
+ | H.TypeSig loc _ _ <- everything module' :: [H.Decl H.SrcSpanInfo]
+ , (start, end) <- infoPoints loc
+ , pos <- maybeToList $ between start end "::" ls
]
@@ -73,10 +74,20 @@ typeFuns module' ls =
contexts :: H.Module H.SrcSpanInfo -> Lines -> [((Int, Int), String)]
contexts module' ls =
[ (pos, "=>")
- | context <- everything module' :: [H.Context H.SrcSpanInfo]
- , point <- H.srcInfoPoints $ H.ann context
- , let (start, end) = (H.srcSpanStart point, H.srcSpanEnd point)
- , pos <- maybeToList $ between start end "=>" ls
+ | context <- everything module' :: [H.Context H.SrcSpanInfo]
+ , (start, end) <- infoPoints $ H.ann context
+ , pos <- maybeToList $ between start end "=>" ls
+ ]
+
+
+--------------------------------------------------------------------------------
+typeFuns :: H.Module H.SrcSpanInfo -> Lines -> [((Int, Int), String)]
+typeFuns module' ls =
+ [ (pos, "->")
+ | H.TyFun _ t1 t2 <- everything module'
+ , let start = H.srcSpanEnd $ H.srcInfoSpan $ H.ann t1
+ , let end = H.srcSpanStart $ H.srcInfoSpan $ H.ann t2
+ , pos <- maybeToList $ between start end "->" ls
]
@@ -112,5 +123,6 @@ stylish ls (module', _) = applyChanges changes ls
where
changes = replaceAll perLine ls
perLine = sort $ groupPerLine $
- typeFuns module' ls ++
- contexts module' ls
+ typeSigs module' ls ++
+ contexts module' ls ++
+ typeFuns module' ls
diff --git a/src/StylishHaskell/Util.hs b/src/StylishHaskell/Util.hs
index 2a78f56..5a4372f 100644
--- a/src/StylishHaskell/Util.hs
+++ b/src/StylishHaskell/Util.hs
@@ -3,10 +3,12 @@ module StylishHaskell.Util
( nameToString
, padRight
, everything
+ , infoPoints
) where
--------------------------------------------------------------------------------
+import Control.Arrow ((&&&), (>>>))
import Data.Data (Data)
import qualified Data.Generics as G
import Data.Maybe (maybeToList)
@@ -15,7 +17,6 @@ import qualified Language.Haskell.Exts.Annotated as H
--------------------------------------------------------------------------------
--- | TODO: put this in utilities?
nameToString :: H.Name l -> String
nameToString (H.Ident _ str) = str
nameToString (H.Symbol _ str) = str
@@ -29,3 +30,8 @@ padRight len str = str ++ replicate (len - length str) ' '
--------------------------------------------------------------------------------
everything :: (Data a, Data b) => a -> [b]
everything = G.everything (++) (maybeToList . cast)
+
+
+--------------------------------------------------------------------------------
+infoPoints :: H.SrcSpanInfo -> [((Int, Int), (Int, Int))]
+infoPoints = H.srcInfoPoints >>> map (H.srcSpanStart &&& H.srcSpanEnd)