Skip to content

Commit

Permalink
Update dependencies and fix some compiler warnings
Browse files Browse the repository at this point in the history
Rationale for not upgrading some packages:

- clipboardy 3.x.x needs to be imported with ESM imports
- ditto for xdg-basedir 5.x.x
- I have no idea if latest decimal.js works with `purescript-decimals`
  or not
  • Loading branch information
triallax authored and sharkdp committed Mar 25, 2022
1 parent d30194e commit a884b58
Show file tree
Hide file tree
Showing 8 changed files with 8,240 additions and 2,040 deletions.
10,205 changes: 8,208 additions & 1,997 deletions package-lock.json

Large diffs are not rendered by default.

10 changes: 5 additions & 5 deletions package.json
Original file line number Diff line number Diff line change
Expand Up @@ -34,20 +34,20 @@
"url": "https://github.com/sharkdp/insect/issues"
},
"dependencies": {
"clipboardy": "^2.3.0",
"decimal.js": "^7.1.1",
"historic-readline": "^1.0.8",
"jquery.terminal": "^2.18.0",
"keyboardevent-key-polyfill": "=1.1.0",
"line-reader": "^0.4.0",
"xdg-basedir": "^2.0.0",
"clipboardy": "^2.3.0"
"xdg-basedir": "^4.0.0"
},
"devDependencies": {
"fs-extra": "^9.0.1",
"fs-extra": "^10.0.1",
"live-server": "^1.2.1",
"npm-run-all": "^4.1.5",
"psc-package": "^4.0.1",
"pulp": "^15.0.0",
"purescript": "^0.13.8"
"pulp": "^16.0.0-0",
"purescript": "^0.14.7"
}
}
3 changes: 1 addition & 2 deletions psc-package.json
Original file line number Diff line number Diff line change
@@ -1,12 +1,11 @@
{
"name": "insect",
"set": "psc-0.13.6-20200123",
"set": "psc-0.14.7-20220321",
"source": "https://github.com/purescript/package-sets.git",
"depends": [
"quantities",
"parsing",
"ordered-collections",
"generics-rep",
"psci-support",
"test-unit"
]
Expand Down
30 changes: 13 additions & 17 deletions src/Insect/Interpreter.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,24 +14,20 @@ import Data.Foldable (foldMap, intercalate, foldl)
import Data.Int (round, toNumber)
import Data.List (List(..), sortBy, filter, groupBy, (..))
import Data.List.NonEmpty (NonEmptyList(..), head, length, zip)
import Data.Maybe (Maybe(..))
import Data.NonEmpty (NonEmpty, (:|), foldl1)
import Data.Map (lookup, insert, delete, toUnfoldable)
import Data.Maybe (Maybe(..))
import Data.NonEmpty (NonEmpty, (:|))
import Data.Semigroup.Foldable (foldl1)
import Data.String (toLower)
import Data.Traversable (traverse)
import Data.Tuple (Tuple(..), fst, snd)

import Quantities (Quantity, ConversionError(..))
import Quantities as Q

import Insect.Language (BinOp(..), Expression(..), Command(..), Identifier,
Statement(..), EvalError(..))
import Insect.Environment (Environment, StorageType(..), StoredValue(..),
FunctionDescription(..), StoredFunction(..),
initialEnvironment, MathFunction)
import Insect.Environment (Environment, StorageType(..), StoredValue(..), FunctionDescription(..), StoredFunction(..), initialEnvironment, MathFunction)
import Insect.Format (FormattedString, Markup)
import Insect.Format as F
import Insect.Language (BinOp(..), Expression(..), Command(..), Identifier, Statement(..), EvalError(..))
import Insect.PrettyPrint (pretty, prettyQuantity)
import Quantities (Quantity, ConversionError(..))
import Quantities as Q

-- | A type synonym for error handling. A value of type `Expect Number` is
-- | expected to be a number but might also result in an evaluation error.
Expand Down Expand Up @@ -100,8 +96,8 @@ evalSpecial func _ _ _ _ _ = Left (InvalidIdentifier func)

-- | Evaluate Either.. mathematical expression involving physical quantities.
eval Environment Expression Expect Quantity
eval env (Scalar n) = pure $ Q.scalar' n
eval env (Unit u) = pure $ Q.quantity 1.0 u
eval _ (Scalar n) = pure $ Q.scalar' n
eval _ (Unit u) = pure $ Q.quantity 1.0 u
eval env (Variable name) = case lookup name env.values of
Just (StoredValue _ q) → pure q
NothingLeft (LookupError name)
Expand Down Expand Up @@ -316,7 +312,7 @@ runInsect env (PrettyPrintFunction name) =
where
message =
case lookup name env.functions of
Just (StoredFunction _ fn (BuiltinFunction args)) →
Just (StoredFunction _ _ (BuiltinFunction args)) →
Message Info [ F.optional (F.text " "),
F.ident name,
F.text "(",
Expand All @@ -328,7 +324,7 @@ runInsect env (PrettyPrintFunction name) =
Just 2 -> "x, y"
Just _ -> "x, y, …"
Nothing -> "x1, x2, …"
Just (StoredFunction _ fn (UserFunction args expr)) →
Just (StoredFunction _ _ (UserFunction args expr)) →
Message Info $ (F.optional <$> (F.text " " : (prettyPrintFunction name args))) <> pretty expr
NothingMessage Error [ F.text "Unknown function" ]

Expand Down Expand Up @@ -372,11 +368,11 @@ runInsect env (Command List) =
(singleton <<< F.ident <<< fst) <$> kvPairs
val = storedValue (snd (head kvPairs))

runInsect env (Command Reset) =
runInsect _ (Command Reset) =
{ msg: Message Info [F.text "Environment has been reset."]
, newEnv: initialEnvironment }

runInsect env (Command Quit) = { msg: MQuit, newEnv: initialEnvironment }
runInsect _ (Command Quit) = { msg: MQuit, newEnv: initialEnvironment }

runInsect env (Command Copy) = { msg: MCopy, newEnv: env }

Expand Down
2 changes: 1 addition & 1 deletion src/Insect/Language.purs
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ import Prelude hiding (Unit)

import Data.Decimal (Decimal)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Show (genericShow)
import Data.Show.Generic (genericShow)
import Data.List (List)
import Data.NonEmpty (NonEmpty)
import Data.Units (DerivedUnit)
Expand Down
26 changes: 10 additions & 16 deletions src/Insect/Parser.purs
Original file line number Diff line number Diff line change
Expand Up @@ -14,31 +14,25 @@ import Prelude hiding (degree)

import Control.Alt ((<|>))
import Control.Lazy (fix)

import Quantities (DerivedUnit, (./))
import Quantities as Q

import Data.Array (some, fromFoldable)
import Data.Decimal (Decimal, fromString, fromNumber, isFinite)
import Data.Either (Either, isRight)
import Data.Foldable (foldr, traverse_)
import Data.Foldable as F
import Data.List (List, many, init, last)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.NonEmpty (NonEmpty, (:|), foldl1)
import Data.Map (lookup)
import Data.Maybe (Maybe(..), fromMaybe)
import Data.NonEmpty (NonEmpty, (:|))
import Data.Semigroup.Foldable (foldl1)
import Data.String (fromCodePointArray, codePointFromChar, singleton)

import Insect.Environment (Environment, StoredFunction(..))
import Insect.Language (BinOp(..), Expression(..), Command(..), Statement(..), Identifier)
import Quantities (DerivedUnit, (./))
import Quantities as Q
import Text.Parsing.Parser (ParserT, Parser, ParseError, runParser, fail)
import Text.Parsing.Parser.Combinators (option, optionMaybe, try, (<?>),
notFollowedBy)
import Text.Parsing.Parser.Combinators (option, optionMaybe, try, (<?>), notFollowedBy)
import Text.Parsing.Parser.String (string, char, eof, oneOf)
import Text.Parsing.Parser.Token (GenLanguageDef(..), LanguageDef, TokenParser,
digit, letter, makeTokenParser)

import Insect.Language (BinOp(..), Expression(..), Command(..), Statement(..),
Identifier)
import Insect.Environment (Environment, StoredFunction(..))
import Text.Parsing.Parser.Token (GenLanguageDef(..), LanguageDef, TokenParser, digit, letter, makeTokenParser)

-- | A type synonym for the main Parser type with `String` as input.
type P a = Parser String a
Expand Down Expand Up @@ -351,7 +345,7 @@ function env = do
pure name
else
case lookup name env.functions of
Just (StoredFunction _ fn _) → pure name
Just (StoredFunction _ _ _) → pure name
Nothing → fail ("Unknown function '" <> name <> "'")

-- | Parse a full mathematical expression.
Expand Down
2 changes: 1 addition & 1 deletion src/Insect/PrettyPrint.purs
Original file line number Diff line number Diff line change
Expand Up @@ -75,7 +75,7 @@ withParens' x = parens (pretty x)
-- | Add parenthesis, if needed - liberal version, can not be used for
-- | Exponentiation.
withParens Expression Markup
withParens e@(BinOp Mul (Scalar s) (Unit u)) = pretty e
withParens e@(BinOp Mul (Scalar _) (Unit _)) = pretty e
withParens e = withParens' e

-- | Pretty print an Insect expression.
Expand Down
2 changes: 1 addition & 1 deletion test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ shouldFail ∷ String → Aff Unit
shouldFail input = do
case parseInsect initialEnvironment input of
Left _ → pure unit
Right output → failure $ "input is expected to throw a parse error: '" <> input <> "'"
Right _ → failure $ "input is expected to throw a parse error: '" <> input <> "'"

expectOutput Environment String String Aff Unit
expectOutput env expected inp =
Expand Down

0 comments on commit a884b58

Please sign in to comment.