Skip to content

Instantly share code, notes, and snippets.

@beckyconning
Created May 1, 2019 18:33
Show Gist options
  • Save beckyconning/cd72b8395d80a1bf4dc66460c3ff0ef1 to your computer and use it in GitHub Desktop.
Save beckyconning/cd72b8395d80a1bf4dc66460c3ff0ef1 to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Control.Alt ((<|>))
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 (between, manyTill, try, optionMaybe, (<?>))
import Text.Parsing.Parser.String (anyChar, eof, string)
import Debug.Trace (spy)
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 <?> "initial"
middle <- optionMaybe $ many $ try do
middleCleanShaven <- (CleanShaven <<< fromCharArray <<< fromFoldable <$> manyTill anyChar mustache) <?> "middleClean"
middleMustache <- mustache <?> "middleMustache"
pure [middleCleanShaven, middleMustache]
end <- optionMaybe $ CleanShaven <<< fromCharArray <<< fromFoldable <$> many anyChar <?> "end"
pure $ join $ catMaybes [pure <$> spy "initial" initial, join <$> spy "middle" middle, pure <$> spy "end" end]
mustache :: forall m. Monad m => ParserT String m Template
mustache =
between (string "{{") (string "}}") (Mustache <<< fromCharArray <$> many anyChar)
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)
initial: Nothing {}
middle: Just { value0: [] }
end: Just { value0: CleanShaven { value0: '{{hey}}yeah {{lets go}}' } }
(Right [(CleanShaven "{{hey}}yeah {{lets go}}")])
initial: Nothing {}
middle: Just { value0: [] }
end: Just {
value0: CleanShaven { value0: 'yeah {{lets go}} lets do {{it}}' } }
(Right [(CleanShaven "yeah {{lets go}} lets do {{it}}")])
initial: Nothing {}
middle: Just { value0: [] }
end: Just { value0: CleanShaven { value0: '{{lets go}}' } }
(Right [(CleanShaven "{{lets go}}")])
initial: Nothing {}
middle: Just { value0: [] }
end: Just { value0: CleanShaven { value0: 'lets go' } }
(Right [(CleanShaven "lets go")])
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment