mirror of
https://github.com/natefaubion/purescript-tidy.git
synced 2024-11-26 00:09:27 +03:00
Add default operators from core and contrib
This commit is contained in:
parent
1febcf1793
commit
9fab3f7cf7
358
bin/DefaultOperators.purs
Normal file
358
bin/DefaultOperators.purs
Normal file
@ -0,0 +1,358 @@
|
||||
--------------------------------------------
|
||||
-- This module is generated. DO NOT EDIT! --
|
||||
--------------------------------------------
|
||||
module DefaultOperators where
|
||||
|
||||
defaultOperators :: Array String
|
||||
defaultOperators =
|
||||
[ """Control.Alt.($>) 4"""
|
||||
, """Control.Alt.(<#>) 1"""
|
||||
, """Control.Alt.(<$) 4"""
|
||||
, """Control.Alt.(<$>) 4"""
|
||||
, """Control.Alt.(<@>) 4"""
|
||||
, """Control.Alt.(<|>) 3"""
|
||||
, """Control.Alternative.($>) 4"""
|
||||
, """Control.Alternative.(*>) 4"""
|
||||
, """Control.Alternative.(<#>) 1"""
|
||||
, """Control.Alternative.(<$) 4"""
|
||||
, """Control.Alternative.(<$>) 4"""
|
||||
, """Control.Alternative.(<*) 4"""
|
||||
, """Control.Alternative.(<*>) 4"""
|
||||
, """Control.Alternative.(<@>) 4"""
|
||||
, """Control.Alternative.(<|>) 3"""
|
||||
, """Control.Applicative.($>) 4"""
|
||||
, """Control.Applicative.(*>) 4"""
|
||||
, """Control.Applicative.(<#>) 1"""
|
||||
, """Control.Applicative.(<$) 4"""
|
||||
, """Control.Applicative.(<$>) 4"""
|
||||
, """Control.Applicative.(<*) 4"""
|
||||
, """Control.Applicative.(<*>) 4"""
|
||||
, """Control.Applicative.(<@>) 4"""
|
||||
, """Control.Apply.($>) 4"""
|
||||
, """Control.Apply.(*>) 4"""
|
||||
, """Control.Apply.(<#>) 1"""
|
||||
, """Control.Apply.(<$) 4"""
|
||||
, """Control.Apply.(<$>) 4"""
|
||||
, """Control.Apply.(<*) 4"""
|
||||
, """Control.Apply.(<*>) 4"""
|
||||
, """Control.Apply.(<@>) 4"""
|
||||
, """Control.Biapply.(*>>) 4"""
|
||||
, """Control.Biapply.(<<$>>) 4"""
|
||||
, """Control.Biapply.(<<*) 4"""
|
||||
, """Control.Biapply.(<<*>>) 4"""
|
||||
, """Control.Bind.($>) 4"""
|
||||
, """Control.Bind.(*>) 4"""
|
||||
, """Control.Bind.(<#>) 1"""
|
||||
, """Control.Bind.(<$) 4"""
|
||||
, """Control.Bind.(<$>) 4"""
|
||||
, """Control.Bind.(<*) 4"""
|
||||
, """Control.Bind.(<*>) 4"""
|
||||
, """Control.Bind.(<=<) 1"""
|
||||
, """Control.Bind.(<@>) 4"""
|
||||
, """Control.Bind.(=<<) 1"""
|
||||
, """Control.Bind.(>=>) 1"""
|
||||
, """Control.Bind.(>>=) 1"""
|
||||
, """Control.Category.(<<<) 9"""
|
||||
, """Control.Category.(>>>) 9"""
|
||||
, """Control.Comonad.($>) 4"""
|
||||
, """Control.Comonad.(<#>) 1"""
|
||||
, """Control.Comonad.(<$) 4"""
|
||||
, """Control.Comonad.(<$>) 4"""
|
||||
, """Control.Comonad.(<<=) 1"""
|
||||
, """Control.Comonad.(<@>) 4"""
|
||||
, """Control.Comonad.(=<=) 1"""
|
||||
, """Control.Comonad.(=>=) 1"""
|
||||
, """Control.Comonad.(=>>) 1"""
|
||||
, """Control.Comonad.Cofree.(:<) 5"""
|
||||
, """Control.Coroutine.($$) 2"""
|
||||
, """Control.Coroutine.($~) 2"""
|
||||
, """Control.Coroutine.(/\) 3"""
|
||||
, """Control.Coroutine.(\/) 3"""
|
||||
, """Control.Coroutine.(~$) 2"""
|
||||
, """Control.Coroutine.(~~) 2"""
|
||||
, """Control.Extend.($>) 4"""
|
||||
, """Control.Extend.(<#>) 1"""
|
||||
, """Control.Extend.(<$) 4"""
|
||||
, """Control.Extend.(<$>) 4"""
|
||||
, """Control.Extend.(<<=) 1"""
|
||||
, """Control.Extend.(<@>) 4"""
|
||||
, """Control.Extend.(=<=) 1"""
|
||||
, """Control.Extend.(=>=) 1"""
|
||||
, """Control.Extend.(=>>) 1"""
|
||||
, """Control.Monad.($>) 4"""
|
||||
, """Control.Monad.(*>) 4"""
|
||||
, """Control.Monad.(<#>) 1"""
|
||||
, """Control.Monad.(<$) 4"""
|
||||
, """Control.Monad.(<$>) 4"""
|
||||
, """Control.Monad.(<*) 4"""
|
||||
, """Control.Monad.(<*>) 4"""
|
||||
, """Control.Monad.(<=<) 1"""
|
||||
, """Control.Monad.(<@>) 4"""
|
||||
, """Control.Monad.(=<<) 1"""
|
||||
, """Control.Monad.(>=>) 1"""
|
||||
, """Control.Monad.(>>=) 1"""
|
||||
, """Control.MonadPlus.($>) 4"""
|
||||
, """Control.MonadPlus.(*>) 4"""
|
||||
, """Control.MonadPlus.(<#>) 1"""
|
||||
, """Control.MonadPlus.(<$) 4"""
|
||||
, """Control.MonadPlus.(<$>) 4"""
|
||||
, """Control.MonadPlus.(<*) 4"""
|
||||
, """Control.MonadPlus.(<*>) 4"""
|
||||
, """Control.MonadPlus.(<=<) 1"""
|
||||
, """Control.MonadPlus.(<@>) 4"""
|
||||
, """Control.MonadPlus.(<|>) 3"""
|
||||
, """Control.MonadPlus.(=<<) 1"""
|
||||
, """Control.MonadPlus.(>=>) 1"""
|
||||
, """Control.MonadPlus.(>>=) 1"""
|
||||
, """Control.MonadZero.($>) 4"""
|
||||
, """Control.MonadZero.(*>) 4"""
|
||||
, """Control.MonadZero.(<#>) 1"""
|
||||
, """Control.MonadZero.(<$) 4"""
|
||||
, """Control.MonadZero.(<$>) 4"""
|
||||
, """Control.MonadZero.(<*) 4"""
|
||||
, """Control.MonadZero.(<*>) 4"""
|
||||
, """Control.MonadZero.(<=<) 1"""
|
||||
, """Control.MonadZero.(<@>) 4"""
|
||||
, """Control.MonadZero.(<|>) 3"""
|
||||
, """Control.MonadZero.(=<<) 1"""
|
||||
, """Control.MonadZero.(>=>) 1"""
|
||||
, """Control.MonadZero.(>>=) 1"""
|
||||
, """Control.Plus.($>) 4"""
|
||||
, """Control.Plus.(<#>) 1"""
|
||||
, """Control.Plus.(<$) 4"""
|
||||
, """Control.Plus.(<$>) 4"""
|
||||
, """Control.Plus.(<@>) 4"""
|
||||
, """Control.Plus.(<|>) 3"""
|
||||
, """Control.Semigroupoid.(<<<) 9"""
|
||||
, """Control.Semigroupoid.(>>>) 9"""
|
||||
, """Data.Argonaut.(.!=) 6"""
|
||||
, """Data.Argonaut.(.:) 7"""
|
||||
, """Data.Argonaut.(.:!) 7"""
|
||||
, """Data.Argonaut.(.:?) 7"""
|
||||
, """Data.Argonaut.(:=) 7"""
|
||||
, """Data.Argonaut.(:=?) 7"""
|
||||
, """Data.Argonaut.(~>) 6"""
|
||||
, """Data.Argonaut.(~>?) 6"""
|
||||
, """Data.Argonaut.Decode.(.!=) 6"""
|
||||
, """Data.Argonaut.Decode.(.:) 7"""
|
||||
, """Data.Argonaut.Decode.(.:!) 7"""
|
||||
, """Data.Argonaut.Decode.(.:?) 7"""
|
||||
, """Data.Argonaut.Decode.Combinators.(.!=) 6"""
|
||||
, """Data.Argonaut.Decode.Combinators.(.:) 7"""
|
||||
, """Data.Argonaut.Decode.Combinators.(.:!) 7"""
|
||||
, """Data.Argonaut.Decode.Combinators.(.:?) 7"""
|
||||
, """Data.Argonaut.Encode.(:=) 7"""
|
||||
, """Data.Argonaut.Encode.(:=?) 7"""
|
||||
, """Data.Argonaut.Encode.(~>) 6"""
|
||||
, """Data.Argonaut.Encode.(~>?) 6"""
|
||||
, """Data.Argonaut.Encode.Combinators.(:=) 7"""
|
||||
, """Data.Argonaut.Encode.Combinators.(:=?) 7"""
|
||||
, """Data.Argonaut.Encode.Combinators.(~>) 6"""
|
||||
, """Data.Argonaut.Encode.Combinators.(~>?) 6"""
|
||||
, """Data.Array.(!!) 8"""
|
||||
, """Data.Array.(..) 8"""
|
||||
, """Data.Array.(:) 6"""
|
||||
, """Data.Array.(\\) 5"""
|
||||
, """Data.Array.NonEmpty.(!!) 8"""
|
||||
, """Data.Array.NonEmpty.(..) 8"""
|
||||
, """Data.Array.NonEmpty.(:) 6"""
|
||||
, """Data.Array.NonEmpty.(\\) 5"""
|
||||
, """Data.BooleanAlgebra.(&&) 3"""
|
||||
, """Data.BooleanAlgebra.(||) 2"""
|
||||
, """Data.Bounded.(<) 4"""
|
||||
, """Data.Bounded.(<=) 4"""
|
||||
, """Data.Bounded.(>) 4"""
|
||||
, """Data.Bounded.(>=) 4"""
|
||||
, """Data.CommutativeRing.(*) 7"""
|
||||
, """Data.CommutativeRing.(+) 6"""
|
||||
, """Data.CommutativeRing.(-) 6"""
|
||||
, """Data.DivisionRing.(*) 7"""
|
||||
, """Data.DivisionRing.(+) 6"""
|
||||
, """Data.DivisionRing.(-) 6"""
|
||||
, """Data.Either.Nested.(\/) type 6"""
|
||||
, """Data.Either.Nested.(\/) 6"""
|
||||
, """Data.Eq.(/=) 4"""
|
||||
, """Data.Eq.(==) 4"""
|
||||
, """Data.EuclideanRing.(*) 7"""
|
||||
, """Data.EuclideanRing.(+) 6"""
|
||||
, """Data.EuclideanRing.(-) 6"""
|
||||
, """Data.EuclideanRing.(/) 7"""
|
||||
, """Data.Field.(*) 7"""
|
||||
, """Data.Field.(+) 6"""
|
||||
, """Data.Field.(-) 6"""
|
||||
, """Data.Field.(/) 7"""
|
||||
, """Data.Function.(#) 1"""
|
||||
, """Data.Function.($) 0"""
|
||||
, """Data.Function.(<<<) 9"""
|
||||
, """Data.Function.(>>>) 9"""
|
||||
, """Data.Functor.($>) 4"""
|
||||
, """Data.Functor.(<#>) 1"""
|
||||
, """Data.Functor.(<$) 4"""
|
||||
, """Data.Functor.(<$>) 4"""
|
||||
, """Data.Functor.(<@>) 4"""
|
||||
, """Data.Functor.Contravariant.(>#<) 4"""
|
||||
, """Data.Functor.Contravariant.(>$<) 4"""
|
||||
, """Data.Functor.Coproduct.Nested.(<\/>) type 6"""
|
||||
, """Data.Functor.Coproduct.Nested.(<\/>) 6"""
|
||||
, """Data.Functor.Product.Nested.(</\>) type 6"""
|
||||
, """Data.Functor.Product.Nested.(</\>) 6"""
|
||||
, """Data.HeytingAlgebra.(&&) 3"""
|
||||
, """Data.HeytingAlgebra.(||) 2"""
|
||||
, """Data.HugeNum.(^) 8"""
|
||||
, """Data.Int.Bits.(.&.) 10"""
|
||||
, """Data.Int.Bits.(.^.) 10"""
|
||||
, """Data.Int.Bits.(.|.) 10"""
|
||||
, """Data.Lens.(%=) 4"""
|
||||
, """Data.Lens.(%~) 4"""
|
||||
, """Data.Lens.(&&&) 3"""
|
||||
, """Data.Lens.(&&=) 4"""
|
||||
, """Data.Lens.(&&~) 4"""
|
||||
, """Data.Lens.(***) 3"""
|
||||
, """Data.Lens.(*=) 4"""
|
||||
, """Data.Lens.(*~) 4"""
|
||||
, """Data.Lens.(+++) 2"""
|
||||
, """Data.Lens.(+=) 4"""
|
||||
, """Data.Lens.(+~) 4"""
|
||||
, """Data.Lens.(-=) 4"""
|
||||
, """Data.Lens.(-~) 4"""
|
||||
, """Data.Lens.(.=) 4"""
|
||||
, """Data.Lens.(.~) 4"""
|
||||
, """Data.Lens.(//=) 4"""
|
||||
, """Data.Lens.(//~) 4"""
|
||||
, """Data.Lens.(<>=) 4"""
|
||||
, """Data.Lens.(<>~) 4"""
|
||||
, """Data.Lens.(?=) 4"""
|
||||
, """Data.Lens.(?~) 4"""
|
||||
, """Data.Lens.(^.) 8"""
|
||||
, """Data.Lens.(^..) 8"""
|
||||
, """Data.Lens.(^?) 8"""
|
||||
, """Data.Lens.(||=) 4"""
|
||||
, """Data.Lens.(|||) 2"""
|
||||
, """Data.Lens.(||~) 4"""
|
||||
, """Data.Lens.Common.(&&&) 3"""
|
||||
, """Data.Lens.Common.(***) 3"""
|
||||
, """Data.Lens.Common.(+++) 2"""
|
||||
, """Data.Lens.Common.(|||) 2"""
|
||||
, """Data.Lens.Fold.(^..) 8"""
|
||||
, """Data.Lens.Fold.(^?) 8"""
|
||||
, """Data.Lens.Fold.Partial.(^?!) 8"""
|
||||
, """Data.Lens.Fold.Partial.(^@?!) 8"""
|
||||
, """Data.Lens.Getter.(^.) 8"""
|
||||
, """Data.Lens.Lens.Tuple.(&&&) 3"""
|
||||
, """Data.Lens.Lens.Tuple.(***) 3"""
|
||||
, """Data.Lens.Prism.Either.(+++) 2"""
|
||||
, """Data.Lens.Prism.Either.(|||) 2"""
|
||||
, """Data.Lens.Setter.(%=) 4"""
|
||||
, """Data.Lens.Setter.(%~) 4"""
|
||||
, """Data.Lens.Setter.(&&=) 4"""
|
||||
, """Data.Lens.Setter.(&&~) 4"""
|
||||
, """Data.Lens.Setter.(*=) 4"""
|
||||
, """Data.Lens.Setter.(*~) 4"""
|
||||
, """Data.Lens.Setter.(+=) 4"""
|
||||
, """Data.Lens.Setter.(+~) 4"""
|
||||
, """Data.Lens.Setter.(-=) 4"""
|
||||
, """Data.Lens.Setter.(-~) 4"""
|
||||
, """Data.Lens.Setter.(.=) 4"""
|
||||
, """Data.Lens.Setter.(.~) 4"""
|
||||
, """Data.Lens.Setter.(//=) 4"""
|
||||
, """Data.Lens.Setter.(//~) 4"""
|
||||
, """Data.Lens.Setter.(<>=) 4"""
|
||||
, """Data.Lens.Setter.(<>~) 4"""
|
||||
, """Data.Lens.Setter.(?=) 4"""
|
||||
, """Data.Lens.Setter.(?~) 4"""
|
||||
, """Data.Lens.Setter.(||=) 4"""
|
||||
, """Data.Lens.Setter.(||~) 4"""
|
||||
, """Data.List.(!!) 8"""
|
||||
, """Data.List.(..) 8"""
|
||||
, """Data.List.(:) 6"""
|
||||
, """Data.List.(\\) 5"""
|
||||
, """Data.List.Lazy.(!!) 8"""
|
||||
, """Data.List.Lazy.(..) 8"""
|
||||
, """Data.List.Lazy.(:) 6"""
|
||||
, """Data.List.Lazy.(\\) 5"""
|
||||
, """Data.List.Lazy.NonEmpty.(:) 6"""
|
||||
, """Data.List.Lazy.Types.(:) 6"""
|
||||
, """Data.List.NonEmpty.(!!) 8"""
|
||||
, """Data.List.NonEmpty.(:) 6"""
|
||||
, """Data.List.Types.(:) 6"""
|
||||
, """Data.Monoid.(<>) 5"""
|
||||
, """Data.NaturalTransformation.(~>) type 4"""
|
||||
, """Data.NonEmpty.(:|) 5"""
|
||||
, """Data.Number.Approximate.(~=) 4"""
|
||||
, """Data.Number.Approximate.(≅) 4"""
|
||||
, """Data.Number.Approximate.(≇) 4"""
|
||||
, """Data.Options.(:=) 6"""
|
||||
, """Data.Ord.(<) 4"""
|
||||
, """Data.Ord.(<=) 4"""
|
||||
, """Data.Ord.(>) 4"""
|
||||
, """Data.Ord.(>=) 4"""
|
||||
, """Data.Profunctor.Choice.(+++) 2"""
|
||||
, """Data.Profunctor.Choice.(|||) 2"""
|
||||
, """Data.Profunctor.Strong.(&&&) 3"""
|
||||
, """Data.Profunctor.Strong.(***) 3"""
|
||||
, """Data.Ring.(*) 7"""
|
||||
, """Data.Ring.(+) 6"""
|
||||
, """Data.Ring.(-) 6"""
|
||||
, """Data.Semigroup.(<>) 5"""
|
||||
, """Data.Semiring.(*) 7"""
|
||||
, """Data.Semiring.(+) 6"""
|
||||
, """Data.Tuple.Nested.(/\) type 6"""
|
||||
, """Data.Tuple.Nested.(/\) 6"""
|
||||
, """Foreign.Index.(!) 9"""
|
||||
, """Math.(%) 7"""
|
||||
, """Pathy.(<..>) 6"""
|
||||
, """Pathy.(<.>) 6"""
|
||||
, """Pathy.(</>) 6"""
|
||||
, """Pathy.Path.(<..>) 6"""
|
||||
, """Pathy.Path.(<.>) 6"""
|
||||
, """Pathy.Path.(</>) 6"""
|
||||
, """Prelude.(~>) type 4"""
|
||||
, """Prelude.(#) 1"""
|
||||
, """Prelude.($) 0"""
|
||||
, """Prelude.($>) 4"""
|
||||
, """Prelude.(&&) 3"""
|
||||
, """Prelude.(*) 7"""
|
||||
, """Prelude.(*>) 4"""
|
||||
, """Prelude.(+) 6"""
|
||||
, """Prelude.(-) 6"""
|
||||
, """Prelude.(/) 7"""
|
||||
, """Prelude.(/=) 4"""
|
||||
, """Prelude.(<) 4"""
|
||||
, """Prelude.(<#>) 1"""
|
||||
, """Prelude.(<$) 4"""
|
||||
, """Prelude.(<$>) 4"""
|
||||
, """Prelude.(<*) 4"""
|
||||
, """Prelude.(<*>) 4"""
|
||||
, """Prelude.(<<<) 9"""
|
||||
, """Prelude.(<=) 4"""
|
||||
, """Prelude.(<=<) 1"""
|
||||
, """Prelude.(<>) 5"""
|
||||
, """Prelude.(<@>) 4"""
|
||||
, """Prelude.(=<<) 1"""
|
||||
, """Prelude.(==) 4"""
|
||||
, """Prelude.(>) 4"""
|
||||
, """Prelude.(>=) 4"""
|
||||
, """Prelude.(>=>) 1"""
|
||||
, """Prelude.(>>=) 1"""
|
||||
, """Prelude.(>>>) 9"""
|
||||
, """Prelude.(||) 2"""
|
||||
, """Test.QuickCheck.(/==) 2"""
|
||||
, """Test.QuickCheck.(/=?) 2"""
|
||||
, """Test.QuickCheck.(<=?) 2"""
|
||||
, """Test.QuickCheck.(<?) 2"""
|
||||
, """Test.QuickCheck.(<?>) 2"""
|
||||
, """Test.QuickCheck.(===) 2"""
|
||||
, """Test.QuickCheck.(==?) 2"""
|
||||
, """Test.QuickCheck.(>=?) 2"""
|
||||
, """Test.QuickCheck.(>?) 2"""
|
||||
, """Text.Parsing.Indent.(<*/>) 11"""
|
||||
, """Text.Parsing.Indent.(<+/>) 9"""
|
||||
, """Text.Parsing.Indent.(<-/>) 10"""
|
||||
, """Text.Parsing.Indent.(<?/>) 12"""
|
||||
, """Text.Parsing.Parser.Combinators.(<?>) 3"""
|
||||
, """Text.Parsing.Parser.Combinators.(<??>) 3"""
|
||||
, """Text.Parsing.StringParser.Combinators.(<?>) 3"""
|
||||
, """Type.Function.($) type 0"""
|
||||
, """Type.Prelude.(+) type 0"""
|
||||
, """Type.Row.(+) type 0"""
|
||||
]
|
@ -15,6 +15,7 @@ import Data.Number as Number
|
||||
import Data.String (Pattern(..))
|
||||
import Data.String as String
|
||||
import Data.Tuple (Tuple(..), snd, uncurry)
|
||||
import DefaultOperators (defaultOperators)
|
||||
import Dodo as Dodo
|
||||
import Effect (Effect)
|
||||
import Effect.Aff (Aff, launchAff_, makeAff)
|
||||
@ -41,7 +42,7 @@ main :: Effect Unit
|
||||
main = launchAff_ do
|
||||
args <- Array.drop 1 <$> liftEffect Process.argv
|
||||
case Array.uncons args of
|
||||
Just { head, tail } | head == "gen-operator-table" ->
|
||||
Just { head, tail } | head == "generate-operators" ->
|
||||
operatorTableCommand tail
|
||||
_ ->
|
||||
formatCommand args
|
||||
@ -63,7 +64,8 @@ formatCommand args = do
|
||||
|
||||
operators <-
|
||||
case findMap (String.stripPrefix (Pattern "--operators=")) args of
|
||||
Nothing -> pure Map.empty
|
||||
Nothing ->
|
||||
pure $ parseOperatorTable defaultOperators
|
||||
Just path -> do
|
||||
table <- liftEffect <<< Buffer.toString UTF8 =<< FS.readFile path
|
||||
pure $ parseOperatorTable $ String.split (Pattern "\n") table
|
||||
|
6
script/GenerateDefaultOperatorsModule.js
Normal file
6
script/GenerateDefaultOperatorsModule.js
Normal file
@ -0,0 +1,6 @@
|
||||
const fs = require("fs");
|
||||
const os = require("os");
|
||||
const path = require("path");
|
||||
|
||||
exports.tmpdir = (prefix) => () =>
|
||||
fs.mkdtempSync(path.join(os.tmpdir(), prefix), "utf-8");
|
170
script/GenerateDefaultOperatorsModule.purs
Normal file
170
script/GenerateDefaultOperatorsModule.purs
Normal file
@ -0,0 +1,170 @@
|
||||
module GenerateDefaultOperatorsModule where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Data.Array (mapWithIndex)
|
||||
import Data.Array as Array
|
||||
import Data.Maybe (Maybe(..))
|
||||
import Data.String (Pattern(..), Replacement(..))
|
||||
import Data.String as String
|
||||
import Effect (Effect)
|
||||
import Node.Buffer as Buffer
|
||||
import Node.ChildProcess as ChildProcess
|
||||
import Node.Encoding (Encoding(..))
|
||||
import Node.FS.Sync (writeTextFile)
|
||||
import Node.Path as Path
|
||||
import Node.Process (cwd)
|
||||
|
||||
foreign import tmpdir :: String -> Effect String
|
||||
|
||||
main :: Effect Unit
|
||||
main = do
|
||||
cwdPath <- cwd
|
||||
tmpPath <- tmpdir "purs-tidy-generate-default-operators-"
|
||||
|
||||
let opts = ChildProcess.defaultExecSyncOptions { cwd = Just tmpPath }
|
||||
let genCmd = "node -e \"require('" <> cwdPath <> "/output/Main/index.js').main()\" generate-operators '.spago/*/*/src/**/*.purs'"
|
||||
|
||||
writeTextFile UTF8 (Path.concat [ tmpPath, "spago.dhall" ]) defaultSpagoDhall
|
||||
_ <- ChildProcess.execSync "spago install" opts
|
||||
output <- Buffer.toString UTF8 =<< ChildProcess.execSync genCmd opts
|
||||
|
||||
let
|
||||
header =
|
||||
[ "--------------------------------------------"
|
||||
, "-- This module is generated. DO NOT EDIT! --"
|
||||
, "--------------------------------------------"
|
||||
, "module DefaultOperators where"
|
||||
, ""
|
||||
, "defaultOperators :: Array String"
|
||||
, "defaultOperators ="
|
||||
]
|
||||
|
||||
lines = output # String.trim # String.split (Pattern "\n") # mapWithIndex \ix line ->
|
||||
if ix == 0 then
|
||||
" [ \"\"\"" <> line <> "\"\"\""
|
||||
else
|
||||
" , \"\"\"" <> line <> "\"\"\""
|
||||
|
||||
footer =
|
||||
[ " ]"
|
||||
, ""
|
||||
]
|
||||
|
||||
contents =
|
||||
Array.intercalate "\n" (header <> lines <> footer)
|
||||
|
||||
writeTextFile UTF8 (Path.concat [ cwdPath, "bin", "DefaultOperators.purs" ]) contents
|
||||
|
||||
defaultSpagoDhall :: String
|
||||
defaultSpagoDhall = """
|
||||
{ name = "purs-tidy-generate-default-operators"
|
||||
, dependencies =
|
||||
[ "ace"
|
||||
, "aff"
|
||||
, "aff-bus"
|
||||
, "aff-coroutines"
|
||||
, "affjax"
|
||||
, "argonaut"
|
||||
, "argonaut-codecs"
|
||||
, "argonaut-core"
|
||||
, "argonaut-generic"
|
||||
, "argonaut-traversals"
|
||||
, "arraybuffer-types"
|
||||
, "arrays"
|
||||
, "assert"
|
||||
, "avar"
|
||||
, "bifunctors"
|
||||
, "catenable-lists"
|
||||
, "concurrent-queues"
|
||||
, "console"
|
||||
, "const"
|
||||
, "contravariant"
|
||||
, "control"
|
||||
, "coroutines"
|
||||
, "datetime"
|
||||
, "distributive"
|
||||
, "effect"
|
||||
, "either"
|
||||
, "enums"
|
||||
, "exceptions"
|
||||
, "exists"
|
||||
, "filterable"
|
||||
, "fixed-points"
|
||||
, "foldable-traversable"
|
||||
, "foreign"
|
||||
, "foreign-object"
|
||||
, "fork"
|
||||
, "form-urlencoded"
|
||||
, "formatters"
|
||||
, "free"
|
||||
, "freet"
|
||||
, "functions"
|
||||
, "functors"
|
||||
, "gen"
|
||||
, "github-actions-toolkit"
|
||||
, "graphs"
|
||||
, "http-methods"
|
||||
, "identity"
|
||||
, "integers"
|
||||
, "invariant"
|
||||
, "js-date"
|
||||
, "js-timers"
|
||||
, "js-uri"
|
||||
, "lazy"
|
||||
, "lcg"
|
||||
, "lists"
|
||||
, "machines"
|
||||
, "math"
|
||||
, "matryoshka"
|
||||
, "maybe"
|
||||
, "media-types"
|
||||
, "minibench"
|
||||
, "newtype"
|
||||
, "nonempty"
|
||||
, "now"
|
||||
, "nullable"
|
||||
, "numbers"
|
||||
, "options"
|
||||
, "ordered-collections"
|
||||
, "orders"
|
||||
, "parallel"
|
||||
, "parsing"
|
||||
, "partial"
|
||||
, "pathy"
|
||||
, "precise"
|
||||
, "prelude"
|
||||
, "profunctor"
|
||||
, "profunctor-lenses"
|
||||
, "psci-support"
|
||||
, "quickcheck"
|
||||
, "quickcheck-laws"
|
||||
, "random"
|
||||
, "react"
|
||||
, "react-dom"
|
||||
, "record"
|
||||
, "refs"
|
||||
, "routing"
|
||||
, "safe-coerce"
|
||||
, "semirings"
|
||||
, "st"
|
||||
, "string-parsers"
|
||||
, "strings"
|
||||
, "strings-extra"
|
||||
, "tailrec"
|
||||
, "these"
|
||||
, "transformers"
|
||||
, "tuples"
|
||||
, "type-equality"
|
||||
, "typelevel-prelude"
|
||||
, "unfoldable"
|
||||
, "unicode"
|
||||
, "unsafe-coerce"
|
||||
, "unsafe-reference"
|
||||
, "uri"
|
||||
, "validation"
|
||||
]
|
||||
, packages = https://github.com/purescript/package-sets/releases/download/psc-0.14.0-20210304/packages.dhall sha256:c88151fe7c05f05290224c9c1ae4a22905060424fb01071b691d3fe2e5bad4ca
|
||||
, sources = [] : List Text
|
||||
}
|
||||
"""
|
10
script/spago.dhall
Normal file
10
script/spago.dhall
Normal file
@ -0,0 +1,10 @@
|
||||
{ name = "purescript-tidy-script"
|
||||
, dependencies =
|
||||
[ "effect"
|
||||
, "node-child-process"
|
||||
, "node-fs"
|
||||
, "node-process"
|
||||
]
|
||||
, packages = ../packages.dhall
|
||||
, sources = [ "script/**/*.purs" ]
|
||||
}
|
Loading…
Reference in New Issue
Block a user