[Haskell-cafe] attpoarsec and recursive parsing

PICCA Frederic-Emmanuel frederic-emmanuel.picca at synchrotron-soleil.fr
Fri Nov 22 10:05:15 UTC 2024


Hello, I end up with this solution

in order to parse this data type.

If you have some advice in order to simplify or beautify the Parser part do not hesitate.

Cheers

Fred

data MaskLocation = MaskLocation Text
                  | MaskLocation'Tmpl Text
                  | MaskLocation'Or MaskLocation MaskLocation
    deriving (Eq, Generic, Show)
    deriving anyclass (FromJSON, ToJSON)

instance FieldEmitter MaskLocation where
  fieldEmitter (MaskLocation t)      = t
  fieldEmitter (MaskLocation'Tmpl t) = t
  fieldEmitter (MaskLocation'Or l r) = fieldEmitter l <> " | " <> fieldEmitter r

instance FieldParsable MaskLocation where
  fieldParser = do
    let loc :: Text -> MaskLocation
        loc t = if "{scannumber:" `Data.Text.isInfixOf` t
                then MaskLocation'Tmpl (strip t)
                else MaskLocation (strip t)

    t <- takeTill (== '|')
    if t == ""
      then fail "MaskLocation is Empty"
      else do mc <- peekChar
              case mc of
                Nothing -> pure $ loc t
                Just '|'  -> do
                  _ <- char '|'  -- extract the '|' char
                  MaskLocation'Or (loc t) <$> fieldParser
                Just c -> fail ("MaskLocation " <> [c])


More information about the Haskell-Cafe mailing list