[commit: haddock] T6018-injective-type-families, adamse-D1033, ghc-head, master, metainfo, wip/10268, wip/10313, wip/D538, wip/D538-1, wip/D538-2, wip/D538-3, wip/D538-4, wip/D538-5, wip/D538-6, wip/D548-master, wip/D548-master-2, wip/T10483, wip/T9840, wip/api-annot-tweaks-7.10, wip/api-annots-ghc-7.10-3, wip/orf-reboot: newtype-wrap parser monad (b4b25f5)
git at git.haskell.org
git at git.haskell.org
Wed Jul 8 08:32:48 UTC 2015
- Previous message: [commit: haddock] T6018-injective-type-families, adamse-D1033, ghc-head, master, metainfo, wip/10268, wip/10313, wip/D538, wip/D538-1, wip/D538-2, wip/D538-3, wip/D538-4, wip/D538-5, wip/D538-6, wip/D548-master, wip/D548-master-2, wip/T10483, wip/T9840, wip/api-annot-tweaks-7.10, wip/api-annots-ghc-7.10-3, wip/orf-reboot: Minor code simplification (86ee241)
- Next message: [commit: haddock] wip/ast-prepare-annotations, wip/ast-prepare-annotations-final: con_name in ConDecl is now [Located Name] (1f234fa)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
Repository : ssh://git@git.haskell.org/haddock
On branches: T6018-injective-type-families,adamse-D1033,ghc-head,master,metainfo,wip/10268,wip/10313,wip/D538,wip/D538-1,wip/D538-2,wip/D538-3,wip/D538-4,wip/D538-5,wip/D538-6,wip/D548-master,wip/D548-master-2,wip/T10483,wip/T9840,wip/api-annot-tweaks-7.10,wip/api-annots-ghc-7.10-3,wip/orf-reboot
Link : http://git.haskell.org/haddock.git/commitdiff/b4b25f5b5777939584aa3c548a855490d5791f73
>---------------------------------------------------------------
commit b4b25f5b5777939584aa3c548a855490d5791f73
Author: Simon Hengel <sol at typeful.net>
Date: Sat Nov 8 17:28:33 2014 +0800
newtype-wrap parser monad
>---------------------------------------------------------------
b4b25f5b5777939584aa3c548a855490d5791f73
.../src/Documentation/Haddock/Parser.hs | 2 +-
.../src/Documentation/Haddock/Parser/Monad.hs | 128 +++++++++++++++++++++
.../src/Documentation/Haddock/Parser/Util.hs | 2 +-
.../test/Documentation/Haddock/Parser/UtilSpec.hs | 2 +-
4 files changed, 131 insertions(+), 3 deletions(-)
diff --git a/haddock-library/src/Documentation/Haddock/Parser.hs b/haddock-library/src/Documentation/Haddock/Parser.hs
index b3387f5..8b4ec78 100644
--- a/haddock-library/src/Documentation/Haddock/Parser.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser.hs
@@ -22,13 +22,13 @@ module Documentation.Haddock.Parser ( parseString, parseParas
import Control.Applicative
import Control.Arrow (first)
import Control.Monad
-import Data.Attoparsec.ByteString.Char8 hiding (parse, take, endOfLine)
import qualified Data.ByteString.Char8 as BS
import Data.Char (chr, isAsciiUpper)
import Data.List (stripPrefix, intercalate, unfoldr)
import Data.Maybe (fromMaybe)
import Data.Monoid
import Documentation.Haddock.Doc
+import Documentation.Haddock.Parser.Monad hiding (take, endOfLine)
import Documentation.Haddock.Parser.Util
import Documentation.Haddock.Types
import Documentation.Haddock.Utf8
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Monad.hs b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
new file mode 100644
index 0000000..19edce0
--- /dev/null
+++ b/haddock-library/src/Documentation/Haddock/Parser/Monad.hs
@@ -0,0 +1,128 @@
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+module Documentation.Haddock.Parser.Monad (
+ module Documentation.Haddock.Parser.Monad
+, Attoparsec.isDigit
+, Attoparsec.isDigit_w8
+, Attoparsec.isAlpha_iso8859_15
+, Attoparsec.isAlpha_ascii
+, Attoparsec.isSpace
+, Attoparsec.isSpace_w8
+, Attoparsec.inClass
+, Attoparsec.notInClass
+, Attoparsec.isEndOfLine
+, Attoparsec.isHorizontalSpace
+, Attoparsec.choice
+, Attoparsec.count
+, Attoparsec.option
+, Attoparsec.many'
+, Attoparsec.many1
+, Attoparsec.many1'
+, Attoparsec.manyTill
+, Attoparsec.manyTill'
+, Attoparsec.sepBy
+, Attoparsec.sepBy'
+, Attoparsec.sepBy1
+, Attoparsec.sepBy1'
+, Attoparsec.skipMany
+, Attoparsec.skipMany1
+, Attoparsec.eitherP
+) where
+
+import Control.Applicative
+import Control.Monad
+import Data.String
+import Data.ByteString (ByteString)
+import qualified Data.ByteString.Lazy as LB
+import qualified Data.Attoparsec.ByteString.Char8 as Attoparsec
+import Data.Word
+import Data.Bits
+
+newtype Parser a = Parser (Attoparsec.Parser a)
+ deriving (Functor, Applicative, Alternative, Monad, MonadPlus, IsString)
+
+parseOnly :: Parser a -> ByteString -> Either String a
+parseOnly (Parser p) = Attoparsec.parseOnly p
+
+lift :: Attoparsec.Parser a -> Parser a
+lift = Parser
+
+char :: Char -> Parser Char
+char = lift . Attoparsec.char
+
+char8 :: Char -> Parser Word8
+char8 = lift . Attoparsec.char8
+
+anyChar :: Parser Char
+anyChar = lift Attoparsec.anyChar
+
+notChar :: Char -> Parser Char
+notChar = lift . Attoparsec.notChar
+
+satisfy :: (Char -> Bool) -> Parser Char
+satisfy = lift . Attoparsec.satisfy
+
+peekChar :: Parser (Maybe Char)
+peekChar = lift Attoparsec.peekChar
+
+peekChar' :: Parser Char
+peekChar' = lift Attoparsec.peekChar'
+
+digit :: Parser Char
+digit = lift Attoparsec.digit
+
+letter_iso8859_15 :: Parser Char
+letter_iso8859_15 = lift Attoparsec.letter_iso8859_15
+
+letter_ascii :: Parser Char
+letter_ascii = lift Attoparsec.letter_ascii
+
+space :: Parser Char
+space = lift Attoparsec.space
+
+string :: ByteString -> Parser ByteString
+string = lift . Attoparsec.string
+
+stringCI :: ByteString -> Parser ByteString
+stringCI = lift . Attoparsec.stringCI
+
+skipSpace :: Parser ()
+skipSpace = lift Attoparsec.skipSpace
+
+skipWhile :: (Char -> Bool) -> Parser ()
+skipWhile = lift . Attoparsec.skipWhile
+
+take :: Int -> Parser ByteString
+take = lift . Attoparsec.take
+
+scan :: s -> (s -> Char -> Maybe s) -> Parser ByteString
+scan s = lift . Attoparsec.scan s
+
+takeWhile :: (Char -> Bool) -> Parser ByteString
+takeWhile = lift . Attoparsec.takeWhile
+
+takeWhile1 :: (Char -> Bool) -> Parser ByteString
+takeWhile1 = lift . Attoparsec.takeWhile1
+
+takeTill :: (Char -> Bool) -> Parser ByteString
+takeTill = lift . Attoparsec.takeTill
+
+takeByteString :: Parser ByteString
+takeByteString = lift Attoparsec.takeByteString
+
+takeLazyByteString :: Parser LB.ByteString
+takeLazyByteString = lift Attoparsec.takeLazyByteString
+
+endOfLine :: Parser ()
+endOfLine = lift Attoparsec.endOfLine
+
+decimal :: Integral a => Parser a
+decimal = lift Attoparsec.decimal
+
+hexadecimal :: (Integral a, Bits a) => Parser a
+hexadecimal = lift Attoparsec.hexadecimal
+
+endOfInput :: Parser ()
+endOfInput = lift Attoparsec.endOfInput
+
+atEnd :: Parser Bool
+atEnd = lift Attoparsec.atEnd
diff --git a/haddock-library/src/Documentation/Haddock/Parser/Util.hs b/haddock-library/src/Documentation/Haddock/Parser/Util.hs
index eff7dfc..d908ce1 100644
--- a/haddock-library/src/Documentation/Haddock/Parser/Util.hs
+++ b/haddock-library/src/Documentation/Haddock/Parser/Util.hs
@@ -22,7 +22,7 @@ module Documentation.Haddock.Parser.Util (
import Control.Applicative
import Control.Monad (mfilter)
-import Data.Attoparsec.ByteString.Char8 hiding (parse, take, endOfLine)
+import Documentation.Haddock.Parser.Monad
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as BS
import Prelude hiding (takeWhile)
diff --git a/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs b/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs
index a6ac49e..32dd11d 100644
--- a/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs
+++ b/haddock-library/test/Documentation/Haddock/Parser/UtilSpec.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
module Documentation.Haddock.Parser.UtilSpec (main, spec) where
-import Data.Attoparsec.ByteString.Char8
+import Documentation.Haddock.Parser.Monad
import Documentation.Haddock.Parser.Util
import Data.Either.Compat (isLeft)
import Test.Hspec
- Previous message: [commit: haddock] T6018-injective-type-families, adamse-D1033, ghc-head, master, metainfo, wip/10268, wip/10313, wip/D538, wip/D538-1, wip/D538-2, wip/D538-3, wip/D538-4, wip/D538-5, wip/D538-6, wip/D548-master, wip/D548-master-2, wip/T10483, wip/T9840, wip/api-annot-tweaks-7.10, wip/api-annots-ghc-7.10-3, wip/orf-reboot: Minor code simplification (86ee241)
- Next message: [commit: haddock] wip/ast-prepare-annotations, wip/ast-prepare-annotations-final: con_name in ConDecl is now [Located Name] (1f234fa)
- Messages sorted by:
[ date ]
[ thread ]
[ subject ]
[ author ]
More information about the ghc-commits
mailing list