Skip to content

Commit

Permalink
Add data dependent experiment
Browse files Browse the repository at this point in the history
  • Loading branch information
noughtmare committed Apr 10, 2023
1 parent 83aa65a commit 2e5df18
Show file tree
Hide file tree
Showing 2 changed files with 51 additions and 3 deletions.
43 changes: 43 additions & 0 deletions experiments/DataDependent.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,43 @@
{-# LANGUAGE DeriveFunctor #-}
import Control.Applicative
import Data.Char

newtype Parser s a = Parser { parse :: String -> s -> [(a, String, s)] } deriving Functor

instance Applicative (Parser s) where
pure x = Parser $ \xs s -> [(x, xs, s)]
Parser p <*> Parser q = Parser $ \xs s -> do
(f, xs', s') <- p xs s
(x, xs'', s'') <- q xs' s'
pure (f x, xs'', s'')

instance Alternative (Parser s) where
empty = Parser $ \_ _ -> []
Parser p <|> Parser q = Parser $ \xs s ->
p xs s ++ q xs s

char :: Char -> Parser s Char
char c = Parser $ \xs s ->
case xs of
c' : xs' | c == c' -> [(c, xs', s)]
_ -> []

put :: Parser s' s -> Parser s a -> Parser s' a
put (Parser p) (Parser q) = Parser $ \xs s -> do
(s', xs', _) <- p xs s
(x, xs'', _) <- q xs' s'
pure (x, xs'', s)

modify :: (s -> [s]) -> Parser s ()
modify f = Parser $ \xs s -> [((), xs, s') | s' <- f s]

dependentReplicate :: Parser s Int -> Parser Int a -> Parser s [a]
dependentReplicate p1 p2 = put p1 rest where
rest = (:) <$ modify (\s -> [s | s > 0]) <*> p2 <* modify (\s -> [s - 1]) <*> rest
<|> [] <$ modify (\s -> [s | s == 0])

digit :: Parser s Int
digit = asum [digitToInt <$> char (intToDigit i) | i <- [0..9]]

main :: IO ()
main = print $ parse (dependentReplicate digit (char '.')) "4...." ()
11 changes: 8 additions & 3 deletions gigaparsec.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -20,8 +20,8 @@ description:
I have also not put any effort in making this library performant yet.

source-repository head
type: git
location: https://github.com/noughtmare/gigaparsec
type: git
location: https://github.com/noughtmare/gigaparsec

common common
build-depends: base >= 4.14 && <5
Expand All @@ -40,4 +40,9 @@ executable gigaparsec-examples
import: common
main-is: Main.hs
hs-source-dirs: examples
build-depends: gigaparsec
build-depends: gigaparsec

executable gigaparsec-experiments-datadependent
import: common
main-is: DataDependent.hs
hs-source-dirs: experiments

0 comments on commit 2e5df18

Please sign in to comment.