(.module: [lux (#- Name Type) [abstract [monad (#+ do)] [equivalence (#+ Equivalence)]] [control [pipe (#+ do> case>)] ["." try (#+ Try)] ["." exception (#+ exception:)] ["<>" parser ["<.>" xml (#+ Parser)] ["<.>" text]] [concurrency ["." promise (#+ Promise)]]] [data ["." product] ["." text ["%" format] [encoding ["." utf8]]] [format ["." xml (#+ XML)]] [collection ["." list ("#\." functor)]]] [math [number ["n" nat]]] ["." time (#+ Time) ["." instant (#+ Instant)] ["." date (#+ Date)] ["." year] ["." month]] [world [net ["." uri (#+ URI)]]]] ["." // ["/#" // #_ [repository (#+ Repository)] ["#." artifact (#+ Group Name Version Artifact) ["#/." time] ["#/." type (#+ Type)] ["#/." versioning (#+ Versioning)] ["#/." snapshot ["#/." version]]]]]) (type: #export Metadata {#artifact Artifact #versioning Versioning}) (template [ ] [(def: xml.Tag ["" ])] [ "groupId"] [ "artifactId"] [ "version"] [ "metadata"] ) (template [
]
  [(def: 
     (->  XML)
     (|>> 
 #xml.Text list (#xml.Node  xml.attributes)))]

  [format_group Group .. (|>)]
  [format_name Name .. (|>)]
  [format_version Version .. (|>)]
  )

(def: #export (format (^slots [#artifact #versioning]))
  (-> Metadata XML)
  (let [(^slots [#///artifact.group #///artifact.name #///artifact.version]) artifact]
    (#xml.Node ..
               xml.attributes
               (list (..format_group group)
                     (..format_name name)
                     (..format_version version)
                     (///artifact/versioning.format versioning)))))

(def: (sub tag parser)
  (All [a] (-> xml.Tag (Parser a) (Parser a)))
  (do <>.monad
    [_ (.node tag)]
    (.children parser)))

(def: (text tag)
  (-> xml.Tag (Parser Text))
  (..sub tag .text))

(def: #export parser
  (Parser Metadata)
  (<| (..sub ..)
      (do {! <>.monad}
        [group (.somewhere (..text ..))
         name (.somewhere (..text ..))
         version (.somewhere (..text ..))
         versioning (\ ! map
                       (update@ #///artifact/versioning.versions
                                (: (-> (List ///artifact/snapshot/version.Version)
                                       (List ///artifact/snapshot/version.Version))
                                   (|>> (case> (^ (list))
                                               (list {#///artifact/snapshot/version.extension ///artifact/type.jvm_library
                                                      #///artifact/snapshot/version.value version
                                                      #///artifact/snapshot/version.updated ///artifact/time.epoch})

                                               versions
                                               versions))))
                       (.somewhere ///artifact/versioning.parser))]
        (wrap {#artifact {#///artifact.group group
                          #///artifact.name name
                          #///artifact.version version}
               #versioning versioning}))))

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

(def: #export (uri artifact)
  (-> Artifact URI)
  (let [/ uri.separator
        group (|> artifact
                  (get@ #///artifact.group)
                  (///artifact.directory /))
        name (get@ #///artifact.name artifact)
        version (get@ #///artifact.version artifact)]
    (%.format group / name / version / //.remote_file)))

(def: #export (read repository artifact)
  (-> (Repository Promise) Artifact (Promise (Try Metadata)))
  (do promise.monad
    [project (\ repository download (..uri artifact))]
    (case project
      (#try.Success project)
      (wrap (|> project
                (do> try.monad
                     [(\ utf8.codec decode)]
                     [(\ xml.codec decode)]
                     [list (.run ..parser)])))
      
      (#try.Failure error)
      (wrap (#try.Success
             {#artifact artifact
              #versioning ///artifact/versioning.init})))))

(def: #export (write repository artifact metadata)
  (-> (Repository Promise) Artifact Metadata (Promise (Try Any)))
  (|> metadata
      ..format
      (\ xml.codec encode)
      (\ utf8.codec encode)
      (\ repository upload (..uri artifact))))