Merge branch 'master' of github.com:colah/ImplicitCAD

This commit is contained in:
Julia Longtin 2020-03-01 19:43:03 +00:00
commit 604ac45620
9 changed files with 10 additions and 38 deletions

View File

@ -5,9 +5,6 @@
-- FIXME: describe why we need this.
{-# LANGUAGE OverloadedStrings #-}
-- allow us to select what package to import what module from. We don't care, but our examples do.
{-# LANGUAGE PackageImports #-}
-- output SCAD code, AKA an implicitcad to openscad converter.
module Graphics.Implicit.Export.SymbolicFormats (scad2, scad3) where
@ -16,7 +13,7 @@ import Prelude(Either(Left, Right), ($), (*), ($!), (-), (/), pi, error, (+), (=
import Graphics.Implicit.Definitions(, SymbolicObj2(RectR, Circle, PolygonR, Complement2, UnionR2, DifferenceR2, IntersectR2, Translate2, Scale2, Rotate2, Outset2, Shell2, EmbedBoxedObj2), SymbolicObj3(Rect3R, Sphere, Cylinder, Complement3, UnionR3, IntersectR3, DifferenceR3, Translate3, Scale3, Rotate3, Rotate3V, Outset3, Shell3, ExtrudeR, ExtrudeRotateR, ExtrudeRM, EmbedBoxedObj3, RotateExtrude, ExtrudeOnEdgeOf))
import Graphics.Implicit.Export.TextBuilderUtils(Text, Builder, toLazyText, fromLazyText, bf)
import "monads-tf" Control.Monad.Reader (Reader, runReader, ask)
import Control.Monad.Reader (Reader, runReader, ask)
import Data.List (intersperse)
import Data.Function (fix)

View File

@ -2,10 +2,6 @@
-- Copyright (C) 2014 2015 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
-- An executor, which parses openscad code, and executes it.
module Graphics.Implicit.ExtOpenScad (runOpenscad) where
@ -27,7 +23,7 @@ import Graphics.Implicit.ExtOpenScad.Util.OVal (divideObjs)
import Text.Parsec.Error (errorPos, errorMessages, showErrorMessages, ParseError)
import "monads-tf" Control.Monad.State.Lazy (runStateT)
import Control.Monad.State.Lazy (runStateT)
import System.Directory (getCurrentDirectory)

View File

@ -2,10 +2,6 @@
-- Copyright 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- Allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
module Graphics.Implicit.ExtOpenScad.Definitions (ArgParser(AP, APTest, APBranch, APTerminator, APFailIf, APExample),
Symbol(Symbol),
Pattern(Wild, Name, ListP),
@ -40,7 +36,7 @@ import Data.Maybe (fromMaybe)
import Data.List (intercalate)
import "monads-tf" Control.Monad.State (StateT)
import Control.Monad.State (StateT)
-- | This is the state of a computation. It contains a hash of variables/functions, an array of OVals, a path, messages, and options controlling code execution.
data CompState = CompState

View File

@ -2,10 +2,6 @@
-- Copyright (C) 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
module Graphics.Implicit.ExtOpenScad.Eval.Constant (addConstants, runExpr) where
import Prelude (String, IO, ($), pure, (+), Either, Bool(False), (.), either, (<$>), (<*), (<*>))
@ -36,7 +32,7 @@ import Graphics.Implicit.ExtOpenScad.Eval.Expr (evalExpr, matchPat, rawRunExpr)
import Graphics.Implicit.ExtOpenScad.Default (defaultObjects)
import "monads-tf" Control.Monad.State (liftIO, runStateT, (>>=))
import Control.Monad.State (liftIO, runStateT, (>>=))
import System.Directory (getCurrentDirectory)

View File

@ -40,7 +40,7 @@ import Data.Traversable (for)
import Control.Monad (zipWithM)
import "monads-tf" Control.Monad.State (StateT, get, modify, runState)
import Control.Monad.State (StateT, get, modify, runState)
data ExprState = ExprState
{ _scadVars :: VarLookup

View File

@ -2,10 +2,6 @@
-- Copyright 2014 2015 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
module Graphics.Implicit.ExtOpenScad.Eval.Statement (runStatementI) where
import Prelude(Maybe(Just, Nothing), Bool(True, False), Either(Left, Right), (.), ($), show, pure, (<>), reverse, fst, snd, readFile, filter, length, (&&), (==), (/=), fmap, notElem, elem, not, zip, init, last, null, String, (*>), (<$>), traverse, (<$))
@ -39,7 +35,7 @@ import Data.Maybe (isJust, fromMaybe, mapMaybe, catMaybes)
import Control.Monad (when, unless, (>>=))
import "monads-tf" Control.Monad.State (gets, liftIO, runStateT)
import Control.Monad.State (gets, liftIO, runStateT)
import Data.Foldable (traverse_, for_)

View File

@ -3,15 +3,11 @@
-- Copyright 2014 2015 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
module Graphics.Implicit.ExtOpenScad.Parser.Lexer (whiteSpace, matchTrue, matchFalse, matchFunction, matchInclude, matchUse, matchIf, matchElse, matchModule, matchLet, matchUndef, matchTok, matchColon, matchSemi, matchComma, matchIdentifier, surroundedBy, matchLT, matchLE, matchGT, matchGE, matchEQ, matchNE, matchCAT, matchOR, matchAND, matchEach, lexer) where
import Prelude (String, Char, Bool(True), (>>), pure)
import "monads-tf" Control.Monad.Identity (Identity)
import Data.Functor.Identity (Identity)
import Text.Parsec.String (GenParser)

View File

@ -2,11 +2,6 @@
-- Copyright 2016, Julia Longtin (julial@turinglace.com)
-- Released under the GNU AGPLV3+, see LICENSE
-- allow us to specify what package to import what module from.
-- We don't actually care, but when we compile our haskell examples, we do.
{-# LANGUAGE PackageImports #-}
module Graphics.Implicit.ExtOpenScad.Util.StateC (addMessage, getVarLookup, modifyVarLookup, lookupVar, pushVals, getVals, putVals, withPathShiftedBy, getPath, getRelPath, errorC, warnC, scadOptions) where
import Prelude(FilePath, String, Maybe, ($), (<>), pure)
@ -15,7 +10,7 @@ import Graphics.Implicit.ExtOpenScad.Definitions(VarLookup(VarLookup), OVal, Sym
import Data.Map (lookup)
import "monads-tf" Control.Monad.State (modify, gets)
import Control.Monad.State (modify, gets)
import System.FilePath((</>))

View File

@ -27,14 +27,14 @@ Library
vector-space,
hspec,
text,
monads-tf,
bytestring,
blaze-builder,
blaze-markup,
blaze-svg,
storable-endian,
JuicyPixels,
transformers
transformers,
mtl
Ghc-options:
-O2