(.using
  [library
   [lux {"-" Type}
    [abstract
     [monad {"+" do}]
     [equivalence {"+" Equivalence}]]
    [control
     [pipe {"+" do> case>}]
     ["[0]" try {"+" Try}]
     ["[0]" exception {"+" exception:}]
     ["<>" parser
      ["<[0]>" xml {"+" Parser}]
      ["<[0]>" text]]
     [concurrency
      ["[0]" async {"+" Async}]]]
    [data
     ["[0]" product]
     ["[0]" text
      ["%" format]
      [encoding
       ["[0]" utf8]]]
     [format
      ["[0]" xml {"+" XML}]]
     [collection
      ["[0]" list ("[1]#[0]" functor)]]]
    [math
     [number
      ["n" nat]]]
    ["[0]" time {"+" Time}
     ["[0]" instant {"+" Instant}]
     ["[0]" date {"+" Date}]
     ["[0]" year]
     ["[0]" month]]
    [world
     [net
      ["[0]" uri {"+" URI}]]]]]
  ["[0]" //
   ["/[1]" // "_"
    [repository {"+" Repository}]
    ["[1][0]" artifact {"+" Group Name Version Artifact}
     ["[1]/[0]" time]
     ["[1]/[0]" type {"+" Type}]
     ["[1]/[0]" versioning {"+" Versioning}]
     ["[1]/[0]" snapshot
      ["[1]/[0]" version]
      ["[1]/[0]" stamp]]]]])

(type: .public Metadata
  (Record
   [#artifact Artifact
    #versioning Versioning]))

(template [<definition> <tag>]
  [(def: <definition> xml.Tag ["" <tag>])]

  [<group> "groupId"]
  [<name> "artifactId"]
  [<version> "version"]
  [<metadata> "metadata"]
  )

(template [<name> <type> <tag> <pre>]
  [(def: <name>
     (-> <type> XML)
     (|>> <pre> {xml.#Text} list {xml.#Node <tag> xml.attributes}))]

  [group_format Group ..<group> (|>)]
  [name_format Name ..<name> (|>)]
  [version_format Version ..<version> (|>)]
  )

(def: .public (format (^open "/[0]"))
  (-> Metadata XML)
  (let [(^open "//[0]") /#artifact]
    {xml.#Node ..<metadata>
               xml.attributes
               (list (..group_format //#group)
                     (..name_format //#name)
                     (..version_format //#version)
                     (///artifact/versioning.format /#versioning))}))

(def: (text tag)
  (-> xml.Tag (Parser Text))
  (<| (<xml>.node tag)
      <xml>.text))

(def: .public parser
  (Parser Metadata)
  (<| (<xml>.node ..<metadata>)
      (do [! <>.monad]
        [group (<xml>.somewhere (..text ..<group>))
         name (<xml>.somewhere (..text ..<name>))
         version (<xml>.somewhere (..text ..<version>))
         versioning (with_expansions [<default_version> [///artifact/snapshot/version.#extension ///artifact/type.jvm_library
                                                         ///artifact/snapshot/version.#value version
                                                         ///artifact/snapshot/version.#updated ///artifact/time.epoch]]
                      (|> (<xml>.somewhere ///artifact/versioning.parser)
                          (# ! each
                             (revised@ ///artifact/versioning.#versions
                                       (: (-> (List ///artifact/snapshot/version.Version)
                                              (List ///artifact/snapshot/version.Version))
                                          (|>> (case> (^ (list))
                                                      (list <default_version>)

                                                      versions
                                                      versions)))))
                          (<>.else [///artifact/versioning.#snapshot {///artifact/snapshot.#Local}
                                    ///artifact/versioning.#last_updated ///artifact/time.epoch
                                    ///artifact/versioning.#versions (list <default_version>)])))]
        (in [#artifact [///artifact.#group group
                        ///artifact.#name name
                        ///artifact.#version version]
             #versioning versioning]))))

(def: .public equivalence
  (Equivalence Metadata)
  ($_ product.equivalence
      ///artifact.equivalence
      ///artifact/versioning.equivalence
      ))

(def: .public uri
  (-> Artifact URI)
  //.remote_artifact_uri)

(def: .public (read repository artifact)
  (-> (Repository Async) Artifact (Async (Try Metadata)))
  (do async.monad
    [project (# repository download (..uri artifact))]
    (case project
      {try.#Success project}
      (in (|> project
              (do> try.monad
                   [(# utf8.codec decoded)]
                   [(# xml.codec decoded)]
                   [list (<xml>.result ..parser)])))
      
      {try.#Failure error}
      (in {try.#Success
           [#artifact artifact
            #versioning ///artifact/versioning.init]}))))

(def: .public (write repository artifact metadata)
  (-> (Repository Async) Artifact Metadata (Async (Try Any)))
  (|> metadata
      ..format
      (# xml.codec encoded)
      (# utf8.codec encoded)
      (# repository upload (..uri artifact))))