|
|
@@ -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
|