Kaynağa Gözat

Split module

jherve 1 yıl önce
ebeveyn
işleme
c245d2c408
3 değiştirilmiş dosya ile 150 ekleme ve 55 silme
  1. 58 0
      src/Command.purs
  2. 2 55
      src/Main.purs
  3. 90 0
      src/RecUtils.purs

+ 58 - 0
src/Command.purs

@@ -0,0 +1,58 @@
+module Command where
+
+import Prelude
+
+import Data.Either (Either(..))
+import Data.Tuple (Tuple(..))
+import Effect.Aff (Aff, launchAff_)
+import Effect.Class.Console (logShow)
+import Node.ChildProcess.Types (Exit(..))
+import Node.Library.Execa (execa)
+
+runCli cmd = launchAff_ do
+  res <- runCommand'' cmd
+  logShow res
+
+runCommand ∷ String → Array String → Aff (Either CommandError String)
+runCommand cmd args = do
+  process <- execa cmd args identity
+  result <- process.getResult
+  let
+    ret = case result.exit of
+      Normally 0 -> Right result.stdout
+      _ -> Left $ Tuple result.exit result.stderr
+
+  pure ret
+
+
+runCommand' ∷ forall e a. (String -> a) -> (CommandError -> e) -> CommandWithOpts → Aff (Either e a)
+runCommand' handleRes handleErr (CommandWithOpts cmd args) = do
+  res <- runCommand cmd args
+
+  let
+    ret = case res of
+      Right s -> Right $ handleRes s
+      Left err -> Left $ handleErr err
+
+  pure ret
+
+data CommandWithOpts = CommandWithOpts String (Array String)
+type CommandError = Tuple Exit String
+
+class HighLevelCommand cmd res err | cmd -> res, cmd -> err where
+  toCommand :: cmd -> CommandWithOpts
+  toResult :: String -> res
+  fromError :: CommandError -> err
+
+runCommand'' ∷ forall cmd res err. HighLevelCommand cmd res err => cmd → Aff (Either err res)
+runCommand'' hlCommand = do
+  let
+    (CommandWithOpts cmd args) = toCommand hlCommand
+  res <- runCommand cmd args
+
+  let
+    ret = case res of
+      Right s -> Right $ toResult @cmd s
+      Left err -> Left $ fromError @cmd err
+
+  pure ret

+ 2 - 55
src/Main.purs

@@ -2,19 +2,14 @@ module Main where
 
 import Prelude
 
-import Data.CodePoint.Unicode (isLetter)
+import Command (class HighLevelCommand, CommandError, CommandWithOpts(..), runCommand, runCommand'')
 import Data.Either (Either(..))
 import Data.Generic.Rep (class Generic)
-import Data.List (List)
 import Data.Show.Generic (genericShow)
 import Data.String (codePointFromChar)
-import Data.Tuple (Tuple(..))
-import Debug (trace)
 import Effect (Effect)
-import Effect.Aff (Aff, launchAff_, try)
+import Effect.Aff (launchAff_, try)
 import Effect.Class.Console (log, logShow)
-import Node.ChildProcess.Types (Exit(..))
-import Node.Library.Execa (execa)
 import Parsing (Parser, runParser)
 import Parsing.Combinators (between, optional)
 import Parsing.Combinators.Array (many)
@@ -31,54 +26,6 @@ main = do
     res <- runCommand'' $ RecSelCommand {filePath: "/tmp/dummy_jobs/jobs.rec", recordType: "job_offer"}
     logShow res
 
-runCli cmd = launchAff_ do
-  res <- runCommand'' cmd
-  logShow res
-
-runCommand ∷ String → Array String → Aff (Either CommandError String)
-runCommand cmd args = do
-  process <- execa cmd args identity
-  result <- process.getResult
-  let
-    ret = case result.exit of
-      Normally 0 -> Right result.stdout
-      _ -> Left $ Tuple result.exit result.stderr
-
-  pure ret
-
-
-runCommand' ∷ forall e a. (String -> a) -> (CommandError -> e) -> CommandWithOpts → Aff (Either e a)
-runCommand' handleRes handleErr (CommandWithOpts cmd args) = do
-  res <- runCommand cmd args
-
-  let
-    ret = case res of
-      Right s -> Right $ handleRes s
-      Left err -> Left $ handleErr err
-
-  pure ret
-
-runCommand'' ∷ forall cmd res err. HighLevelCommand cmd res err => cmd → Aff (Either err res)
-runCommand'' hlCommand = do
-  let
-    (CommandWithOpts cmd args) = toCommand hlCommand
-  res <- runCommand cmd args
-
-  let
-    ret = case res of
-      Right s -> Right $ toResult @cmd s
-      Left err -> Left $ fromError @cmd err
-
-  pure ret
-
-
-data CommandWithOpts = CommandWithOpts String (Array String)
-type CommandError = Tuple Exit String
-
-class HighLevelCommand cmd res err | cmd -> res, cmd -> err where
-  toCommand :: cmd -> CommandWithOpts
-  toResult :: String -> res
-  fromError :: CommandError -> err
 
 data RecSelCommand = RecSelCommand {filePath :: String, recordType :: String}
 data RecSelCommandResult = RecSelCommandResult (Array RecFileRecord)

+ 90 - 0
src/RecUtils.purs

@@ -0,0 +1,90 @@
+module JobSearchExtension.RecUtils where
+
+import Prelude
+
+import Data.Generic.Rep (class Generic)
+import Data.Show.Generic (genericShow)
+
+import Command (class HighLevelCommand, CommandError, CommandWithOpts(..))
+import Data.Either (Either(..))
+import Data.String (codePointFromChar)
+import Effect.Aff (try)
+import Parsing (Parser, runParser)
+import Parsing.Combinators (between, optional)
+import Parsing.Combinators.Array (many)
+import Parsing.String (char, string)
+import Parsing.String.Basic (number, space, takeWhile)
+import Partial.Unsafe (unsafePartial)
+
+
+data RecSelCommand = RecSelCommand {filePath :: String, recordType :: String}
+data RecSelCommandResult = RecSelCommandResult (Array RecFileRecord)
+
+derive instance Generic RecSelCommandResult _
+instance Show RecSelCommandResult where show = genericShow
+
+data RecSelCommandError = RecSelCommandError CommandError
+
+derive instance Generic RecSelCommandError _
+instance Show RecSelCommandError where show = genericShow
+
+instance HighLevelCommand RecSelCommand RecSelCommandResult RecSelCommandError where
+  toCommand (RecSelCommand {filePath, recordType}) = CommandWithOpts "recsel" [filePath, "-t", recordType, "--print-sexps"]
+
+  toResult s = unsafePartial $ case runParser s recordListP of
+    Right rec -> RecSelCommandResult rec
+
+  fromError t = RecSelCommandError t
+
+data RecFileField = RecFileField String String
+derive instance Generic RecFileField _
+instance Show RecFileField where show = genericShow
+
+data RecFileRecord = RecFileRecord (Array RecFileField)
+derive instance Generic RecFileRecord _
+instance Show RecFileRecord where show = genericShow
+
+inParens ∷ ∀ a. Parser String a → Parser String a
+inParens = between openingParen (char ')')
+
+openingParen ∷ Parser String Char
+openingParen = do
+  c <- char '('
+  _ <- optional (try (char '\n'))
+  pure c
+
+inQuotes ∷ ∀ a. Parser String a → Parser String a
+inQuotes = between (char '"') (char '"')
+
+recordP ∷ Parser String RecFileRecord
+recordP = inParens do
+  _ <- string("record")
+  _ <- space
+  _ <- number
+  _ <- space
+  fields <- inParens fieldListP
+  pure $ RecFileRecord fields
+
+recordListP ∷ Parser String (Array RecFileRecord)
+recordListP = many do
+  r <- recordP
+  _ <- optional (try (char '\n'))
+  _ <- optional (try (char '\n'))
+  pure r
+
+fieldListP ∷ Parser String (Array RecFileField)
+fieldListP = many do
+  f <- fieldP
+  _ <- optional (try (char '\n'))
+  pure f
+
+fieldP ∷ Parser String RecFileField
+fieldP = inParens do
+  _ <- string("field")
+  _ <- space
+  _ <- number
+  _ <- space
+  key <- inQuotes $ takeWhile \c -> c /= codePointFromChar '"'
+  _ <- space
+  value <- inQuotes $ takeWhile \c -> c /= codePointFromChar '"'
+  pure $ RecFileField key value