Skip to content

Commit

Permalink
Remove unused code
Browse files Browse the repository at this point in the history
  • Loading branch information
noughtmare committed Apr 30, 2023
1 parent 197e031 commit fd83830
Show file tree
Hide file tree
Showing 5 changed files with 83 additions and 316 deletions.
67 changes: 48 additions & 19 deletions examples/Main.hs
Original file line number Diff line number Diff line change
@@ -1,28 +1,57 @@
import Gigaparsec ( Parser, reify, nt, parse, decode, char )
{-# LANGUAGE GADTs #-}
import Gigaparsec

import Control.Applicative ( asum, Alternative((<|>)) )
import Control.Monad ( void )
import Data.Char ( intToDigit )
import Data.Type.Equality

many :: Parser a -> Parser [a]
many p = res where res = nt $ (:) <$> p <*> res <|> pure []
data Number a where
Number :: Number Int
deriving instance Show (Number a)
instance EqF Number where
eqF Number Number = Just Refl
instance OrdF Number where
compareF Number Number = EQ

-- does not work: many p = nt $ (:) <$> p <*> many p <|> pure []
number :: Number < f => Alt f Int
number = send Number

p1 :: Parser ()
p1 = a *> a where
a = nt $ void (char 'a') <|> e
e = nt $ pure ()
data Digit a where
Digit :: Digit Int
deriving instance Show (Digit a)
instance EqF Digit where
eqF Digit Digit = Just Refl
instance OrdF Digit where
compareF Digit Digit = EQ

p2 :: Parser Int
p2 =
nt $ (*) <$> p2 <* char '*' <*> p2
<|> (+) <$> p2 <* char '+' <*> p2
<|> asum [x <$ char (intToDigit x) | x <- [0..9]]
digit :: Digit < f => Alt f Int
digit = send Digit

main :: IO ()
main = print (decode (parse (g, z) "1+2*3") z 0 5) where
(g, z) = reify p2
-- ergonomics idea: use overloaded labels or template haskell to avoid boilerplate

-- Will print:
-- [7,9]
data Expr a where
Expr :: Expr Int
deriving instance Show (Expr a)
instance EqF Expr where
eqF Expr Expr = Just Refl
instance OrdF Expr where
compareF Expr Expr = EQ

expr :: Expr < f => Alt f Int
expr = send Expr

-- TODO: higher order nonterminals, e.g.:
data Many p a where
Many :: p a -> Many m [a]

-- TODO: This would require using a free monad(plus) rather than just a free alternative:
data ReplicateM p a where
ReplicateM :: Int -> p a -> ReplicateM p [a]

gram :: Gram (Expr + Number + Digit + End)
gram = G (\Expr -> (+) <$> expr <* match '+' <*> expr <|> number)
<||> G (\Number -> (\x y -> 10 * x + y) <$> number <*> digit <|> digit)
<||> G (\Digit -> asum [x <$ match (intToDigit x) | x <- [0..9]])
<||> end

main = print (parse gram (inj Expr) "1+2+3")
4 changes: 1 addition & 3 deletions gigaparsec.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,10 +30,8 @@ common common

library
import: common
exposed-modules: Gigaparsec, Gigaparsec.Core, Gigaparsec.Syntax
exposed-modules: Gigaparsec, Gigaparsec.Core
hs-source-dirs: src
build-depends: data-reify ^>= 0.6,
-- recover-rtti,

executable gigaparsec-examples
import: common
Expand Down
5 changes: 2 additions & 3 deletions src/Gigaparsec.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
module Gigaparsec (module Gigaparsec.Core, module Gigaparsec.Syntax) where
module Gigaparsec (module Gigaparsec.Core) where

import Gigaparsec.Core
import Gigaparsec.Syntax
import Gigaparsec.Core
Loading

0 comments on commit fd83830

Please sign in to comment.