(.require [library [lux (.except) [abstract [monad (.only do)] [equivalence (.only Equivalence)]] [control ["<>" parser] ["[0]" pipe] ["[0]" try (.only Try)] [concurrency ["[0]" async (.only Async)]]] [data ["[0]" product] ["[0]" text (.only) ["%" \\format] ["<[1]>" \\parser] [encoding ["[0]" utf8]]] [format ["[0]" xml (.only XML) ["<[1]>" \\parser (.only Parser)]]] [collection ["[0]" list (.use "[1]#[0]" functor)]]] [math [number ["n" nat]]] [world [net ["[0]" uri (.only URI)]] ["[0]" time (.only Time) ["[0]" instant (.only Instant)] ["[0]" date (.only Date)] ["[0]" year] ["[0]" month]]]]] ["[0]" // (.only) ["/[1]" // [repository (.only Repository)] ["[1][0]" artifact (.only Group Name Version Artifact)]]]) (type .public Metadata (Record [#group Group #name Name #versions (List Version) #last_updated Instant])) (def (pad value) (-> Nat Text) (if (n.< 10 value) (%.format "0" (%.nat value)) (%.nat value))) (def (date_format value) (%.Format Date) (%.format (|> value date.year year.value .nat %.nat) (|> value date.month month.number ..pad) (|> value date.day_of_month ..pad))) (def (time_format value) (%.Format Time) (let [(open "[0]") (time.clock value)] (%.format (..pad #hour) (..pad #minute) (..pad #second)))) (def (instant_format value) (%.Format Instant) (%.format (..date_format (instant.date value)) (..time_format (instant.time value)))) (with_template [ ] [(def xml.Tag ["" ])] [ "groupId"] [ "artifactId"] [ "version"] [ "versioning"] [ "versions"] [ "lastUpdated"] [ "metadata"] ) (with_template [
]
  [(def 
     (->  XML)
     (|>> 
 {xml.#Text} list {xml.#Node  xml.attributes}))]

  [group_format Group .. (|>)]
  [name_format Name .. (|>)]
  [version_format Version .. (|>)]
  [last_updated_format Instant .. ..instant_format]
  )

(def versions_format
  (-> (List Version) XML)
  (|>> (list#each ..version_format) {xml.#Node .. xml.attributes}))

(def .public (format value)
  (-> Metadata XML)
  {xml.#Node ..
             xml.attributes
             (list (..group_format (the #group value))
                   (..name_format (the #name value))
                   {xml.#Node ..
                              xml.attributes
                              (list (..versions_format (the #versions value))
                                    (..last_updated_format (the #last_updated value)))})})

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

(def date_parser
  (.Parser Date)
  (do <>.monad
    [year (<>.codec n.decimal (.exactly 4 .decimal))
     year (<>.lifted (year.year (.int year)))
     month (<>.codec n.decimal (.exactly 2 .decimal))
     month (<>.lifted (month.by_number month))
     day_of_month (<>.codec n.decimal (.exactly 2 .decimal))]
    (<>.lifted (date.date year month day_of_month))))

(def time_parser
  (.Parser Time)
  (do <>.monad
    [hour (<>.codec n.decimal (.exactly 2 .decimal))
     minute (<>.codec n.decimal (.exactly 2 .decimal))
     second (<>.codec n.decimal (.exactly 2 .decimal))]
    (<>.lifted (time.time
                [time.#hour hour
                 time.#minute minute
                 time.#second second
                 time.#milli_second 0]))))

(def last_updated_parser
  (Parser Instant)
  (.then (do <>.monad
                 [date ..date_parser
                  time ..time_parser]
                 (in (instant.of_date_time date time)))
               (..text ..)))

(def .public parser
  (Parser Metadata)
  (<| (.node ..)
      (all <>.and
           (.somewhere (..text ..))
           (.somewhere (..text ..))
           (<| (.node ..)
               ... Handle any ignorable tag.
               (<>.before (<>.some .any))
               (all <>.and
                    (<| .somewhere
                        (.node ..)
                        (<>.many (..text ..)))
                    (.somewhere ..last_updated_parser)
                    )))))

(def .public equivalence
  (Equivalence Metadata)
  (all product.equivalence
       text.equivalence
       text.equivalence
       (list.equivalence text.equivalence)
       instant.equivalence
       ))

(def .public uri
  (-> Artifact URI)
  //.remote_project_uri)

(def epoch
  Instant
  (instant.of_millis +0))

(def .public (read repository artifact)
  (-> (Repository Async) Artifact (Async (Try Metadata)))
  (do async.monad
    [project (at repository download (..uri artifact))]
    (when project
      {try.#Success binary_metadata}
      (in (|> binary_metadata
              (pipe.do try.monad
                [(at utf8.codec decoded)]
                [(at xml.codec decoded)]
                [list (.result ..parser)])))
      
      {try.#Failure error}
      (in {try.#Success
           (let [(open "[0]") artifact]
             [..#group #group
              ..#name #name
              ..#versions (list)
              ..#last_updated ..epoch])}))))

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