Hello community,

here is the log from the commit of package ghc-heterocephalus for 
openSUSE:Factory checked in at 2017-06-21 13:55:29
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
Comparing /work/SRC/openSUSE:Factory/ghc-heterocephalus (Old)
 and      /work/SRC/openSUSE:Factory/.ghc-heterocephalus.new (New)
++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Package is "ghc-heterocephalus"

Wed Jun 21 13:55:29 2017 rev:2 rq:504669 version:1.0.5.0

Changes:
--------
--- /work/SRC/openSUSE:Factory/ghc-heterocephalus/ghc-heterocephalus.changes    
2017-04-12 18:06:50.881437595 +0200
+++ 
/work/SRC/openSUSE:Factory/.ghc-heterocephalus.new/ghc-heterocephalus.changes   
    2017-06-21 13:55:32.205376319 +0200
@@ -1,0 +2,5 @@
+Mon Jun 12 09:41:44 UTC 2017 - [email protected]
+
+- Update to version 1.0.5.0.
+
+-------------------------------------------------------------------

Old:
----
  heterocephalus-1.0.4.0.tar.gz

New:
----
  heterocephalus-1.0.5.0.tar.gz

++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

Other differences:
------------------
++++++ ghc-heterocephalus.spec ++++++
--- /var/tmp/diff_new_pack.xBkXPg/_old  2017-06-21 13:55:33.065255025 +0200
+++ /var/tmp/diff_new_pack.xBkXPg/_new  2017-06-21 13:55:33.069254461 +0200
@@ -19,7 +19,7 @@
 %global pkg_name heterocephalus
 %bcond_with tests
 Name:           ghc-%{pkg_name}
-Version:        1.0.4.0
+Version:        1.0.5.0
 Release:        0
 Summary:        A type-safe template engine for working with popular front end 
development tools
 License:        MIT
@@ -31,11 +31,13 @@
 BuildRequires:  ghc-blaze-markup-devel
 BuildRequires:  ghc-containers-devel
 BuildRequires:  ghc-dlist-devel
+BuildRequires:  ghc-mtl-devel
 BuildRequires:  ghc-parsec-devel
 BuildRequires:  ghc-rpm-macros
 BuildRequires:  ghc-shakespeare-devel
 BuildRequires:  ghc-template-haskell-devel
 BuildRequires:  ghc-text-devel
+BuildRequires:  ghc-transformers-devel
 BuildRoot:      %{_tmppath}/%{name}-%{version}-build
 %if %{with tests}
 BuildRequires:  ghc-Glob-devel

++++++ heterocephalus-1.0.4.0.tar.gz -> heterocephalus-1.0.5.0.tar.gz ++++++
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/heterocephalus-1.0.4.0/CHANGELOG.md 
new/heterocephalus-1.0.5.0/CHANGELOG.md
--- old/heterocephalus-1.0.4.0/CHANGELOG.md     2017-02-07 14:23:03.000000000 
+0100
+++ new/heterocephalus-1.0.5.0/CHANGELOG.md     2017-06-05 10:38:19.000000000 
+0200
@@ -1,6 +1,17 @@
 Change Log
 ==========
 
+Version 1.0.5.0 (2017-06-05)
+----------------
+
+### New features
+
+* Add settings to be able to change the character used to deliminate control 
statements #18
+
+### Document updates
+
+* Fixed small spelling/grammars on readme #19
+
 Version 1.0.4.0 (2017-02-07)
 ----------------
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/heterocephalus-1.0.4.0/README.md 
new/heterocephalus-1.0.5.0/README.md
--- old/heterocephalus-1.0.4.0/README.md        2017-01-23 17:27:54.000000000 
+0100
+++ new/heterocephalus-1.0.5.0/README.md        2017-06-05 10:32:26.000000000 
+0200
@@ -26,7 +26,7 @@
 There are many Haskell template engines today.
 [Shakespeare](http://hackage.haskell.org/package/shakespeare) is great because
 it checks template variables at compile time.  Using Shakespeare, it's not
-possible to for the template file to cause a runtime-error.
+possible for the template file to cause a runtime-error.
 
 Shakespeare provides its own original ways of writing HTML
 
([Hamlet](https://hackage.haskell.org/package/shakespeare/docs/Text-Hamlet.html)),
@@ -53,7 +53,7 @@
 [long time to compile](https://github.com/blueimpact/kucipong/pull/7) with
 GHC >= 7.10.
 
-Hetercephalus fills this missing niche. It gives you variable interpolation
+Heterocephalus fills this missing niche. It gives you variable interpolation
 along with control statements that can be used with any markup language.  Its
 compile times are reasonable.
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/heterocephalus-1.0.4.0/heterocephalus.cabal 
new/heterocephalus-1.0.5.0/heterocephalus.cabal
--- old/heterocephalus-1.0.4.0/heterocephalus.cabal     2017-02-07 
14:20:31.000000000 +0100
+++ new/heterocephalus-1.0.5.0/heterocephalus.cabal     2017-06-05 
10:34:40.000000000 +0200
@@ -1,5 +1,5 @@
 name:                heterocephalus
-version:             1.0.4.0
+version:             1.0.5.0
 synopsis:            A type-safe template engine for working with popular 
front end development tools
 description:
     Recent front end development tools and languages are growing fast and have
@@ -33,15 +33,18 @@
                      , Text.Heterocephalus.Parse
                      , Text.Heterocephalus.Parse.Control
                      , Text.Heterocephalus.Parse.Doc
+                     , Text.Heterocephalus.Parse.Option
   build-depends:       base >= 4.7 && < 5
                      , blaze-html >= 0.8 && < 0.10
                      , blaze-markup >= 0.7 && < 0.9
                      , containers >= 0.5 && < 0.6
                      , dlist >= 0.7.1.1
+                     , mtl
                      , parsec >= 3.1 && < 3.2
                      , shakespeare >= 2.0 && < 2.1
                      , template-haskell >= 2.7 && < 3
                      , text >= 1.2 && < 1.3
+                     , transformers
   ghc-options:         -Wall
   default-language:    Haskell2010
 
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse/Control.hs 
new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse/Control.hs
--- old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse/Control.hs 
2017-01-23 17:16:41.000000000 +0100
+++ new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse/Control.hs 
2017-06-05 10:32:26.000000000 +0200
@@ -12,18 +12,23 @@
 import Control.Applicative ((<$>), (*>), (<*), pure)
 #endif
 import Control.Monad (guard, void)
+import Control.Monad.Reader (Reader, runReaderT)
 import Data.Char (isUpper)
 import Data.Data (Data)
 import Data.Functor (($>))
+import Data.Functor.Identity (runIdentity)
 import Data.Typeable (Typeable)
 import Text.Parsec
-       (Parsec, (<?>), (<|>), alphaNum, between, char, choice, eof, many,
-        many1, manyTill, noneOf, oneOf, option, optional, parse, sepBy,
-        skipMany, spaces, string, try)
+       (Parsec, ParsecT, (<?>), (<|>), alphaNum, between, char, choice,
+        eof, many, many1, manyTill, mkPT, noneOf, oneOf, option, optional,
+        runParsecT, runParserT, sepBy, skipMany, spaces, string,
+        try)
 import Text.Shakespeare.Base
-       (Ident(Ident), Deref, parseDeref, parseHash)
+       (Ident(Ident), Deref, parseDeref, parseVar)
 
 import Text.Hamlet.Parse
+import Text.Heterocephalus.Parse.Option
+       (ParseOptions, getControlPrefix, getVariablePrefix)
 
 data Control
   = ControlForall Deref Binding
@@ -42,52 +47,62 @@
              | ContentVar Deref
     deriving (Data, Eq, Read, Show, Typeable)
 
-type UserParser = Parsec String ()
+type UserParser = ParsecT String () (Reader ParseOptions)
 
-parseLineControl :: String -> Either String [Control]
-parseLineControl s =
-  case parse lineControl s s of
-    Left e -> Left $ show e
-    Right x -> Right x
+parseLineControl :: ParseOptions -> String -> Either String [Control]
+parseLineControl opts s =
+  let readerT = runParserT lineControl () "" s
+      res = runIdentity $ runReaderT readerT opts
+  in case res of
+       Left e -> Left $ show e
+       Right x -> Right x
 
 lineControl :: UserParser [Control]
 lineControl = manyTill control $ try eof >> return ()
 
 control :: UserParser Control
-control = controlHash <|> controlPercent <|> controlReg
+control = noControlVariable <|> controlStatement <|> noControlRaw
   where
-    controlPercent :: UserParser Control
-    controlPercent = do
-      x <- parsePercent
+    controlStatement :: UserParser Control
+    controlStatement = do
+      x <- parseControlStatement
       case x of
         Left str -> return (NoControl $ ContentRaw str)
         Right ctrl -> return ctrl
 
-    controlHash :: UserParser Control
-    controlHash = do
-      x <- parseHash
+    noControlVariable :: UserParser Control
+    noControlVariable = do
+      variablePrefix <- getVariablePrefix
+      x <- identityToReader $ parseVar variablePrefix
       return . NoControl $
         case x of
           Left str -> ContentRaw str
           Right deref -> ContentVar deref
 
-    controlReg :: UserParser Control
-    controlReg = (NoControl . ContentRaw) <$> many (noneOf "#%")
-
-parsePercent :: UserParser (Either String Control)
-parsePercent = do
-  a <- parseControl '%'
+    noControlRaw :: UserParser Control
+    noControlRaw = do
+      controlPrefix <- getControlPrefix
+      variablePrefix <- getVariablePrefix
+      (NoControl . ContentRaw) <$>
+        many (noneOf [controlPrefix, variablePrefix])
+
+parseControlStatement :: UserParser (Either String Control)
+parseControlStatement = do
+  a <- parseControl
   optional eol
   return a
  where
   eol :: UserParser ()
   eol = void (char '\n') <|> void (string "\r\n")
 
-parseControl :: Char -> UserParser (Either String Control)
-parseControl c = do
-  _ <- char c
-  let escape = char '\\' $> Left [c]
-  escape <|> (Right <$> parseControlBetweenBrackets) <|> return (Left [c])
+parseControl :: UserParser (Either String Control)
+parseControl = do
+  controlPrefix <- getControlPrefix
+  void $ char controlPrefix
+  let escape = char '\\' $> Left [controlPrefix]
+  escape <|>
+    (Right <$> parseControlBetweenBrackets) <|>
+    return (Left [controlPrefix])
 
 parseControlBetweenBrackets :: UserParser Control
 parseControlBetweenBrackets =
@@ -112,10 +127,14 @@
     parseEndForall = string "endforall" $> ControlEndForall
 
     parseIf :: UserParser Control
-    parseIf = string "if" *> spaces *> fmap ControlIf parseDeref
+    parseIf =
+      string "if" *> spaces *> fmap ControlIf (identityToReader parseDeref)
 
     parseElseIf :: UserParser Control
-    parseElseIf = string "elseif" *> spaces *> fmap ControlElseIf parseDeref
+    parseElseIf =
+      string "elseif" *>
+      spaces *>
+      fmap ControlElseIf (identityToReader parseDeref)
 
     parseElse :: UserParser Control
     parseElse = string "else" $> ControlElse
@@ -124,7 +143,10 @@
     parseEndIf = string "endif" $> ControlEndIf
 
     parseCase :: UserParser Control
-    parseCase = string "case" *> spaces *> fmap ControlCase parseDeref
+    parseCase =
+      string "case" *>
+      spaces *>
+      fmap ControlCase (identityToReader parseDeref)
 
     parseCaseOf :: UserParser Control
     parseCaseOf = string "of" *> spaces *> fmap ControlCaseOf identPattern
@@ -138,7 +160,7 @@
       spaces
       _ <- string "<-"
       spaces
-      x <- parseDeref
+      x <- identityToReader parseDeref
       _ <- spaceTabs
       return (x, y)
 
@@ -319,3 +341,7 @@
 
         listpat :: UserParser Binding
         listpat = BindList <$> identPattern `sepBy` comma
+
+identityToReader :: Parsec String () a -> UserParser a
+identityToReader p =
+  mkPT $ pure . fmap (pure . runIdentity) . runIdentity . runParsecT p
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse/Option.hs 
new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse/Option.hs
--- old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse/Option.hs  
1970-01-01 01:00:00.000000000 +0100
+++ new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse/Option.hs  
2017-06-05 10:32:26.000000000 +0200
@@ -0,0 +1,33 @@
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE FlexibleContexts #-}
+
+module Text.Heterocephalus.Parse.Option where
+
+import Control.Monad.Reader (MonadReader, reader)
+
+data ParseOptions = ParseOptions
+  { parseOptionsControlPrefix :: Char
+  , parseOptionsVariablePrefix :: Char
+  }
+
+-- | Default set of parser options.
+--
+-- Sets 'parseOptionsControlPrefix' to @\'%\'@  and
+-- 'parseOptionsVariablePrefix' to @\'#\'@.
+defaultParseOptions :: ParseOptions
+defaultParseOptions = createParseOptions '%' '#'
+
+createParseOptions
+  :: Char  -- ^ The control prefix.
+  -> Char  -- ^ The variable prefix.
+  -> ParseOptions
+createParseOptions controlPrefix varPrefix = ParseOptions
+  { parseOptionsControlPrefix = controlPrefix
+  , parseOptionsVariablePrefix = varPrefix
+  }
+
+getControlPrefix :: MonadReader ParseOptions m => m Char
+getControlPrefix = reader parseOptionsControlPrefix
+
+getVariablePrefix :: MonadReader ParseOptions m => m Char
+getVariablePrefix = reader parseOptionsVariablePrefix
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' 
old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse.hs 
new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse.hs
--- old/heterocephalus-1.0.4.0/src/Text/Heterocephalus/Parse.hs 2017-01-10 
05:06:31.000000000 +0100
+++ new/heterocephalus-1.0.5.0/src/Text/Heterocephalus/Parse.hs 2017-06-05 
10:32:26.000000000 +0200
@@ -9,21 +9,24 @@
   ( module Text.Heterocephalus.Parse
   , module Text.Heterocephalus.Parse.Control
   , module Text.Heterocephalus.Parse.Doc
+  , module Text.Heterocephalus.Parse.Option
   ) where
 
 import Text.Heterocephalus.Parse.Control (Content(..), parseLineControl)
 import Text.Heterocephalus.Parse.Doc
        (Doc(..), parseDocFromControls)
+import Text.Heterocephalus.Parse.Option
+       (ParseOptions(..), createParseOptions, defaultParseOptions)
 
-docFromString :: String -> [Doc]
-docFromString s =
-  case parseDoc s of
+docFromString :: ParseOptions -> String -> [Doc]
+docFromString opts s =
+  case parseDoc opts s of
     Left s' -> error s'
     Right d -> d
 
-parseDoc :: String -> Either String [Doc]
-parseDoc s = do
-  controls <- parseLineControl s
+parseDoc :: ParseOptions -> String -> Either String [Doc]
+parseDoc opts s = do
+  controls <- parseLineControl opts s
   case parseDocFromControls controls of
     Left parseError -> Left $ show parseError
     Right docs -> Right docs
diff -urN '--exclude=CVS' '--exclude=.cvsignore' '--exclude=.svn' 
'--exclude=.svnignore' old/heterocephalus-1.0.4.0/src/Text/Heterocephalus.hs 
new/heterocephalus-1.0.5.0/src/Text/Heterocephalus.hs
--- old/heterocephalus-1.0.4.0/src/Text/Heterocephalus.hs       2017-02-07 
14:19:54.000000000 +0100
+++ new/heterocephalus-1.0.5.0/src/Text/Heterocephalus.hs       2017-06-05 
10:32:26.000000000 +0200
@@ -39,6 +39,9 @@
   , HeterocephalusSetting(..)
   , textSetting
   , htmlSetting
+  , ParseOptions(..)
+  , defaultParseOptions
+  , createParseOptions
   , DefaultScope
   , compile
   , compileWith
@@ -85,7 +88,8 @@
        (Deref, Ident(..), Scope, derefToExp, readUtf8File)
 
 import Text.Heterocephalus.Parse
-       (Doc(..), Content(..), docFromString)
+       (Doc(..), Content(..), ParseOptions(..), createParseOptions,
+        defaultParseOptions, docFromString)
 
 {- $setup
   >>> :set -XTemplateHaskell -XQuasiQuotes
@@ -332,6 +336,20 @@
   contents <- fmap TL.unpack $ qRunIO $ readUtf8File fp
   compileFromStringWithDefault scope' set contents
 
+{-| Same as 'compileFile', but just compile the 'String' given.
+
+  >>> let as = ["<a>", "b"]
+  >>> let template = "sample %{ forall a <- as }key: #{a}, %{ endforall }"
+  >>> renderMarkup $(compileFromString textSetting template)
+  "sample key: <a>, key: b, "
+
+  >>> let as = ["<a>", "b"]
+  >>> let options = createParseOptions '|' '?'
+  >>> let setting = textSetting { parseOptions = options }
+  >>> let template = "sample |{ forall a <- as }key: ?{a}, |{ endforall }"
+  >>> renderMarkup $(compileFromString setting template)
+  "sample key: <a>, key: b, "
+-}
 compileFromString :: HeterocephalusSetting -> String -> Q Exp
 compileFromString = compileFromStringWithDefault []
 
@@ -341,7 +359,7 @@
     forM defScope $ \(ident, qexp) -> (ident, ) <$> overwriteScope ident qexp
   owScope' <-
     forM owScope $ \(ident, qexp) -> (ident, ) <$> qexp
-  docsToExp set (owScope' ++ defScope') $ docFromString s
+  docsToExp set (owScope' ++ defScope') $ docFromString (parseOptions set) s
  where
   (defDList, owDList) = runScopeM scopeM
   defScope = DList.toList defDList
@@ -351,7 +369,7 @@
 compileFromStringWithDefault scope' set s = do
   scope <-
     forM scope' $ \(ident, qexp) -> (ident, ) <$> overwriteScope ident qexp
-  docsToExp set scope $ docFromString s
+  docsToExp set scope $ docFromString (parseOptions set) s
 
 overwriteScope :: Ident -> Q Exp -> Q Exp
 overwriteScope (Ident str) qexp = do
@@ -366,6 +384,7 @@
   { escapeExp :: Q Exp
   -- ^ Template variables are passed to 'escapeExp' in the output.  This allows
   -- things like escaping HTML entities.  (See 'htmlSetting'.)
+  , parseOptions :: ParseOptions
   }
 
 {-| A setting that escapes template variables for Html
@@ -375,6 +394,7 @@
 htmlSetting :: HeterocephalusSetting
 htmlSetting = HeterocephalusSetting
   { escapeExp = [|toHtml|]
+  , parseOptions = defaultParseOptions
   }
 
 {-| A setting that DOES NOT escape template variables.
@@ -384,6 +404,7 @@
 textSetting :: HeterocephalusSetting
 textSetting = HeterocephalusSetting
   { escapeExp = [|preEscapedToMarkup|]
+  , parseOptions = defaultParseOptions
   }
 
 type DefaultScope = [(Ident, Q Exp)]


Reply via email to