mirror of
https://github.com/Haskell-Things/ImplicitCAD.git
synced 2024-11-04 01:26:48 +03:00
tiny changes from alt-parser. mostly spacing, comments, and more explicit type definitions.
This commit is contained in:
parent
03b5862286
commit
216bc207ec
@ -96,7 +96,7 @@ data Expr = Var Symbol
|
||||
| Expr :$ [Expr]
|
||||
deriving (Show, Eq)
|
||||
|
||||
-- | A statement, along with the line and column number it is found on.
|
||||
-- | A statement, along with the line, column number, and file it is found at.
|
||||
data StatementI = StatementI SourcePosition (Statement StatementI)
|
||||
deriving (Show, Eq)
|
||||
|
||||
|
@ -14,19 +14,17 @@
|
||||
-- The entry point for parsing an ExtOpenScad program.
|
||||
module Graphics.Implicit.ExtOpenScad.Parser.Statement (parseProgram) where
|
||||
|
||||
import Prelude(Char, Either, String, Monad, return, fmap, ($), (>>), Bool(False, True), map)
|
||||
import Prelude(Char, Either, String, return, fmap, ($), (>>), Bool(False, True), map)
|
||||
|
||||
import Data.Maybe(Maybe(Just, Nothing))
|
||||
|
||||
import Data.Functor.Identity(Identity)
|
||||
|
||||
import Data.Kind (Type)
|
||||
|
||||
-- We use parsec to parse.
|
||||
import Text.ParserCombinators.Parsec (SourceName, try, sepBy, GenParser, oneOf, space, char, getPosition, parse, many1, eof, string, ParseError, many, noneOf, Line, Column, (<|>), (<?>))
|
||||
import Text.ParserCombinators.Parsec (SourceName, try, sepBy, GenParser, oneOf, space, char, getPosition, parse, many1, eof, string, ParseError, many, noneOf, (<|>), (<?>))
|
||||
import Text.Parsec.Prim (ParsecT)
|
||||
|
||||
import Graphics.Implicit.ExtOpenScad.Definitions (Statement(DoNothing, NewModule, Include, Echo, If, For, ModuleCall, (:=)), Expr(LamE), StatementI(StatementI), Symbol(Symbol), SourcePosition)
|
||||
import Graphics.Implicit.ExtOpenScad.Definitions (Statement(DoNothing, NewModule, Include, Echo, If, For, ModuleCall,(:=)),Expr(LamE), StatementI(StatementI), Symbol(Symbol), SourcePosition)
|
||||
|
||||
import qualified Graphics.Implicit.ExtOpenScad.Definitions as GIED (Pattern(Name))
|
||||
|
||||
@ -39,7 +37,7 @@ import Graphics.Implicit.ExtOpenScad.Parser.Expr (expr0)
|
||||
pattern Name n = GIED.Name (Symbol n)
|
||||
|
||||
parseProgram :: SourceName -> String -> Either ParseError [StatementI]
|
||||
parseProgram name s = parse program name s where
|
||||
parseProgram name s = parse program name s where
|
||||
program :: ParsecT String u Identity [StatementI]
|
||||
program = do
|
||||
sts <- many1 computation
|
||||
|
@ -26,7 +26,7 @@ import Graphics.Implicit.Definitions (toFastℕ)
|
||||
|
||||
import Data.Kind (Type)
|
||||
|
||||
-- white space, including tabs, newlines and comments
|
||||
-- | Consume white space, including tabs, newlines and comments.
|
||||
genSpace :: ParsecT String u Identity String
|
||||
genSpace = many $
|
||||
oneOf " \t\n\r"
|
||||
|
@ -490,9 +490,9 @@ unit = moduleWithSuite "unit" $ \children -> do
|
||||
(<|>) :: ArgParser a -> ArgParser a -> ArgParser a
|
||||
(<|>) = mplus
|
||||
|
||||
moduleWithSuite :: String -> t1 -> (Symbol, t1)
|
||||
moduleWithSuite :: String -> ([OVal] -> ArgParser (IO [OVal])) -> (Symbol, [OVal] -> ArgParser (IO [OVal]))
|
||||
moduleWithSuite name modArgMapper = ((Symbol name), modArgMapper)
|
||||
moduleWithoutSuite :: String -> a -> (Symbol, b -> a)
|
||||
moduleWithoutSuite :: String -> ArgParser (IO [OVal]) -> (Symbol, b -> ArgParser (IO [OVal]))
|
||||
moduleWithoutSuite name modArgMapper = ((Symbol name), const modArgMapper)
|
||||
|
||||
addObj2 :: SymbolicObj2 -> ArgParser (IO [OVal])
|
||||
|
@ -40,7 +40,7 @@ argument (Symbol name) =
|
||||
val :: Maybe desiredType
|
||||
val = fromOObj oObjVal
|
||||
errmsg = case oObjVal of
|
||||
OError errs -> "error in computing value for arugment " ++ name
|
||||
OError errs -> "error in computing value for argument " ++ name
|
||||
++ ": " ++ concat errs
|
||||
_ -> "arg " ++ show oObjVal ++ " not compatible with " ++ name
|
||||
-- Using /= Nothing would require Eq desiredType
|
||||
|
Loading…
Reference in New Issue
Block a user