Created
May 1, 2019 18:58
-
-
Save beckyconning/64d28d230d0b3b0d53b5ba112493efac to your computer and use it in GitHub Desktop.
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
module Main where | |
import Prelude | |
import Control.Apply (lift2) | |
import Data.Array (catMaybes, fromFoldable, many) | |
import Data.List (List(..)) | |
import Data.List as List | |
import Data.String.CodeUnits (fromCharArray) | |
import Effect (Effect) | |
import Effect.Console (log) | |
import Text.Parsing.Parser (ParserT, runParserT) | |
import Text.Parsing.Parser.Combinators (try, lookAhead, manyTill, optionMaybe) | |
import Text.Parsing.Parser.Combinators as PC | |
import Text.Parsing.Parser.String (anyChar, string) | |
data Template = Mustache String | CleanShaven String | |
instance showTemplate :: Show Template where | |
show (Mustache s) = "(Mustache " <> show s <> ")" | |
show (CleanShaven s) = "(CleanShaven " <> show s <> ")" | |
main :: Effect Unit | |
main = do | |
_ <- log <<< show =<< runParserT example1 template | |
_ <- log <<< show =<< runParserT example2 template | |
_ <- log <<< show =<< runParserT example3 template | |
_ <- log <<< show =<< runParserT example4 template | |
pure unit | |
template :: forall m. Monad m => ParserT String m (Array Template) | |
template = do | |
initial <- optionMaybe $ try mustache | |
middle <- optionMaybe $ many $ try do | |
middleCleanShaven <- (CleanShaven <<< fromCharArray <<< fromFoldable <$> manyTill anyChar (lookAhead mustache)) | |
middleMustache <- mustache | |
pure [middleCleanShaven, middleMustache] | |
end <- optionMaybe $ CleanShaven <<< fromCharArray <<< fromFoldable <$> many1 anyChar | |
pure $ join $ catMaybes [pure <$> initial, join <$> middle, pure <$> end] | |
mustache :: forall m. Monad m => ParserT String m Template | |
mustache = | |
PC.between (string "{{") (string "}}") (Mustache <<< fromCharArray <<< fromFoldable <$> manyTill anyChar (lookAhead $ string "}}")) | |
example1 :: String | |
example1 = "{{hey}}yeah {{lets go}}" | |
example2 :: String | |
example2 = "yeah {{lets go}} lets do {{it}}" | |
example3 :: String | |
example3 = "{{lets go}}" | |
example4 :: String | |
example4 = "lets go" | |
many1 :: forall s m a. (Monad m) => ParserT s m a -> ParserT s m (List a) | |
many1 p = lift2 Cons p (List.many p) |
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
(Right [(Mustache "hey"),(CleanShaven "yeah "),(Mustache "lets go")]) | |
(Right [(CleanShaven "yeah "),(Mustache "lets go"),(CleanShaven " lets do "),(Mustache "it")]) | |
(Right [(Mustache "lets go")]) | |
(Right [(CleanShaven "lets go")]) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment