parser/src/Main.purs

145 lines
4.6 KiB
Text

module Main where
import Parser
import DomainParser
import Prelude (Unit, discard, show, ($), (==), (<>))
import Effect (Effect)
import Effect.Console (log)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))
import Data.String.CodeUnits (fromCharArray)
-- isf :: Parser Boolean
-- isf = (_ == 'f') <$> itemP
--
-- isf2 :: Parser Boolean
-- isf2 = (==) <$> itemP <*> pure 'f'
--
-- isf3 :: Parser Boolean
-- isf3 = charP 'f'
--
-- ishi :: Parser (Tuple Boolean Boolean)
-- ishi = Tuple <$> ((_ == 'h') <$> itemP) <*> ((_ == 'i') <$> itemP)
--
-- ishi2 :: Parser (Tuple Boolean Boolean)
-- ishi2 = ado
-- h <- itemP
-- i <- itemP
-- in Tuple (h == 'h') (i == 'i')
--
-- isffound :: Maybe (Tuple Boolean String) -> Effect Unit
-- isffound maybe = case maybe of
-- Nothing -> log "no more data"
-- Just (Tuple b str) -> do
-- let toprint = if b then "FOUND IT" else "not found"
-- log $ toprint <> ", rest: " <> str
logtest :: forall a. String -> Parser a -> String -> (a -> String) -> Effect Unit
logtest fname p str r = do
log $ "(" <> fname <> ") parsing '" <> str <> "': "
<> case parse p str of
Just (Tuple x y) -> show (r x) <> " " <> show y
Nothing -> "failed"
id :: forall a. a -> a
id a = a
main :: Effect Unit
main = do
logtest "ldh_str" ldh_str "a12B.fl" fromCharArray
logtest "ldh_str" ldh_str "1efg.x1" fromCharArray
logtest "ldh_str" ldh_str ".qjzleb" fromCharArray
logtest "ldh_str" ldh_str "a-b.b-a" fromCharArray
logtest "ldh_str" ldh_str "" fromCharArray
log ""
logtest "label" label "example.org" id
logtest "label" label "" id
logtest "label" label "a.x" id
logtest "label" label "a2.org" id
logtest "label" label "a33.org" id
logtest "label" label "a444.org" id
logtest "label" label "a5555.org" id
logtest "label" label "a66666.org" id
logtest "label" label "a777777.org" id
logtest "label" label "a8888888.org" id
log ""
logtest "label" label "-" id
logtest "label" label "a-" id
log ""
logtest "subdomain" subdomain "example.org" id
logtest "subdomain" subdomain "" id
logtest "subdomain" subdomain "a.x" id
logtest "subdomain" subdomain "a2.org" id
logtest "subdomain" subdomain "a33.org" id
logtest "subdomain" subdomain "a444.org" id
logtest "subdomain" subdomain "a5555.org" id
logtest "subdomain" subdomain "a66666.org" id
logtest "subdomain" subdomain "a777777.org" id
logtest "subdomain" subdomain "a8888888.org" id
logtest "subdomain" subdomain "xblah.a.x" id
logtest "subdomain" subdomain "xblah.a2.org" id
logtest "subdomain" subdomain "xblah.a33.org" id
logtest "subdomain" subdomain "xblah.a444.org" id
logtest "subdomain" subdomain "xblah.a5555.org" id
logtest "subdomain" subdomain "xblah.a66666.org" id
logtest "subdomain" subdomain "xblah.a777777.org" id
logtest "subdomain" subdomain "xblah.a8888888.org" id
logtest "subdomain" subdomain "-" id
logtest "subdomain" subdomain "a-" id
-- log $ "parsing the first 'f' in 'fiction' (sat): " <> case parse (sat (\x -> x == 'f')) "fiction" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "failed"
--
-- log $ "parsing 'fic' in 'fiction' (string): " <> case parse (string "fic") "fiction" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "failed"
--
-- log $ "parsing ident (all first alphanum) in 'ab123-blah' (ident): " <>
-- case parse ident "ab123-blah" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "failed"
--
-- log $ "parsing integer in '-19ab' (integer): " <>
-- case parse integer "-19ab" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "failed"
-- JUST WORKS
-- isffound $ parse isf "fable"
-- isffound $ parse isf "f"
-- isffound $ parse isf "n"
-- isffound $ parse isf ""
--
-- isffound $ parse isf2 "fable"
-- isffound $ parse isf2 "f"
-- isffound $ parse isf2 "n"
-- isffound $ parse isf2 ""
-- log $ "parsing 'hi': " <> case parse ishi2 "hi" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "coudn't parse two letters"
--
-- log $ "parsing 'no': " <> case parse ishi2 "no" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "coudn't parse two letters"
--
-- log $ "parsing 'ho': " <> case parse ishi2 "ho" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "coudn't parse two letters"
--
-- log $ "parsing 'ni': " <> case parse ishi2 "ni" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "coudn't parse two letters"
--
-- log $ "parsing '': " <> case parse ishi2 "" of
-- Just (Tuple x y) -> show x <> " " <> show y
-- Nothing -> "coudn't parse two letters"