Parsim X12 "on the knee"

    imageWhen creating an application that actively interacts with third-party services and systems, it is often necessary to provide information exchange with them, one-way or two-way

    . Often, the third-party service provides the only format and data structures for such interaction.

    One of these electronic document formats is EDI ANSI ASC X12 , which is described in sufficient detail by reference.

    KDPV was taken from this site.


    Under the cut, a simple X12 parser algorithm and Clojure code, which implements the parser and an example of parsed data processing, are given.

    A bit about the format


    Quoting the above link:
    The ANSI ASC X12 electronic document interchange standard (American National Standards Institute Accredited Standards Committee X12) was developed in the 1970s, when the small size of an electronic document was important (for modems with speeds of 300-1200 bits per second) and each byte had to carry maximum information. Thus, the “readability” of an electronic document was abandoned in favor of “information density”.

    Therefore, you will not see in it any human-readable beauties, as in XML. And although the standard allows you to create documents of a rather complex hierarchical structure, with the presence of blocks and so-called loop-s, nevertheless, even closing tags for all blocks (except for ISA / GS / ST) are not provided. According to the link before kata, anyone can get acquainted in detail with the structure and description of the format, then we will deal only with the necessary things.

    Each type of document has its own template structure, which indicates the meaning and purpose of individual fields and segments, their types and possible values, as well as a list of required and optional segments and blocks. Versioning is supported; information about the type and version number is transmitted in the corresponding fields of the document. It is assumed that it is with the use of a template of a specific type of document that it should be analyzed and validated.

    Below is an example of a document containing several transactions of type 835 (document of the type of response response), which will show the parsing and subsequent data processing.

    X12 example
    ISA*00**00**ZZ*EMEDNYBAT      *ZZ*ETIN           *140305*0929*^*00501*111111123*0*P*:~
    GS*HP*EMED*ETIN*20140301*09304100*111111123*X*005010X221A1~
    ST*835*35681~
    BPR*I*810.8*C*CHK************20140331~
    TRN*1*12345*1512345678~
    REF*EV*XYZ CLEARINGHOUSE~
    N1*PR*DENTAL OF ABC~
    N3*225 MAIN STREET~
    N4*CENTERVILLE*PA*17111~
    PER*BL*JANE DOE*TE*9005555555~
    N1*PE*BAN DDS LLC*FI*999994703~
    LX*1~
    CLP*7722337*1*226*132**12*119932404007801~
    NM1*QC*1*DOE*SANDY****MI*SJD11112~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*132~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D0220*25*14~
    DTM*472*20140324~
    CAS*CO*131*11~
    AMT*B6*14~
    SVC*AD:D0230*22*10~
    DTM*472*20140324~
    CAS*CO*131*12~
    AMT*B6*10~
    SVC*AD:D0274*60*34~
    DTM*472*20140324~
    CAS*CO*131*26~
    AMT*B6*34~
    SVC*AD:D1110*73*49~
    DTM*472*20140324~
    CAS*CO*131*24~
    AMT*B6*49~
    LX*2~
    CLP*7722337*1*119*74**12*119932404007801~
    NM1*QC*1*DOE*SALLY****MI*SJD11111~
    NM1*IL*1*DOE*JOHN****MI*123456~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*74~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D1110*73*49~
    DTM*472*20140324~
    CAS*CO*131*24~
    AMT*B6*49~
    LX*3~
    CLP*7722337*1*226*108*24*12*119932404007801~
    NM1*QC*1*SMITH*SALLY****MI*SJD11113~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*132~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D0220*25*0~
    DTM*472*20140324~
    CAS*PR*3*14~
    CAS*CO*131*11~
    AMT*B6*14~
    SVC*AD:D0230*22*0~
    DTM*472*20140324~
    CAS*PR*3*10~
    CAS*CO*131*12~
    AMT*B6*10~
    SVC*AD:D0274*60*34~
    DTM*472*20140324~
    CAS*CO*131*26~
    AMT*B6*34~
    SVC*AD:D1110*73*49~
    DTM*472*20140324~
    CAS*CO*131*24~
    AMT*B6*49~
    LX*4~
    CLP*7722337*1*1145*14*902*12*119932404007801~
    NM1*QC*1*SMITH*SAM****MI*SJD11116~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*14~
    SVC*AD:D0220*25*14~
    DTM*472*20140324~
    CAS*CO*131*11~
    AMT*B6*14~
    SVC*AD:D2790*940*0~
    DTM*472*20140324~
    CAS*PR*3*756~
    CAS*CO*131*184~
    SVC*AD:D2950*180*0~
    DTM*472*20140324~
    CAS*PR*3*146~
    CAS*CO*131*34~
    LX*5~
    CLP*7722337*1*348*16.8*44.2*12*119932404007801~
    NM1*QC*1*JONES*SAM****MI*SJD11122~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*28~
    SVC*AD:D4342*125*0~
    DTM*472*20140313~
    CAS*CO*131*125~
    SVC*AD:D4381*43*0~
    DTM*472*20140313~
    CAS*PR*3*33~
    CAS*CO*131*10~
    SVC*AD:D2950*180*16.8~
    DTM*472*20140313~
    CAS*PR*3*11.2~
    CAS*CO*131*152~
    AMT*B6*28~
    LX*6~
    CLP*7722337*1*226*132**12*119932404007801~
    NM1*QC*1*JONES*SALLY****MI*SJD11133~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*132~
    SVC*AD:D0120*46*25~
    DTM*472*20140321~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D0220*25*14~
    DTM*472*20140321~
    CAS*CO*131*11~
    AMT*B6*14~
    SVC*AD:D0230*22*10~
    DTM*472*20140321~
    CAS*CO*131*12~
    AMT*B6*10~
    SVC*AD:D0274*60*34~
    DTM*472*20140321~
    CAS*CO*131*26~
    AMT*B6*34~
    SVC*AD:D1110*73*49~
    DTM*472*20140321~
    CAS*CO*131*24~
    AMT*B6*49~
    LX*7~
    CLP*7722337*1*179*108**12*119932404007801~
    NM1*QC*1*DOE*SAM****MI*SJD99999~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*108~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D0274*60*34~
    DTM*472*20140324~
    CAS*CO*131*26~
    AMT*B6*34~
    SVC*AD:D1110*73*49~
    DTM*472*20140324~
    CAS*CO*131*24~
    AMT*B6*49~
    LX*8~
    CLP*7722337*1*129*82**12*119932404007801~
    NM1*QC*1*DOE*SUE****MI*SJD88888~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*82~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D1120*54*37~
    DTM*472*20140324~
    CAS*CO*131*17~
    AMT*B6*37~
    SVC*AD:D1208*29*20~
    DTM*472*20140324~
    CAS*CO*131*9~
    AMT*B6*20~
    LX*9~
    CLP*7722337*1*221*144**12*119932404007801~
    NM1*QC*1*DOE*DONNA****MI*SJD77777~
    NM1*82*1*BAN*ERIN****XX*1811901945~
    AMT*AU*144~
    SVC*AD:D0120*46*25~
    DTM*472*20140324~
    CAS*CO*131*21~
    AMT*B6*25~
    SVC*AD:D0330*92*62~
    DTM*472*20140324~
    CAS*CO*131*30~
    AMT*B6*62~
    SVC*AD:D1120*54*37~
    DTM*472*20140324~
    CAS*CO*131*17~
    AMT*B6*37~
    SVC*AD:D1208*29*20~
    DTM*472*20140324~
    CAS*CO*131*9~
    AMT*B6*20~
    SE*190*35681~
    GE*1*111111123~
    IEA*1*111111123~
    



    A detailed description of the purpose of each block and segment can be found in analyzing the overall structure 12 and the template structure of this type of document. But the basic concept is common to all types - the contents of the package consist of segments separated by the ~ character (in the example text, each segment is displayed on a new line for readability). In turn, each segment can contain an arbitrary number of fields, separated by the symbol * .

    Such agreements allow us to easily obtain the linear structure of the document as a list of segments with a list of their fields. However, it is not enough to restore the hierarchical structure of the document blocks. For this, as I mentioned, it is supposed to use a schema, which for most types of documents is a fairly large file. But, since we will not consider the task of document validation, but limit ourselves to parsing, the following algorithm is quite suitable for our purposes - for each segment encountered during the sequential parsing of a linear list of document segments, we need to get an answer to the only question: does this segment form A new nested block, whether the end of the current block (and at the same time the beginning of the next),

    Parser


    Below is the Clojure code that parses the linear structure of the segments into a hierarchical block structure. To define the hierarchy structure, a declarative approach is used - the simplest data structure loops, in which lists of segments that form nested blocks and end the current block are specified separately for the listed segments. Of course, this structure depends on the type of document, it actually sets its hierarchy. But the following parsing function is universal, and will work on any patterns of structures correctly defined in this way, of course, provided that the type of document being parsed matches the selected pattern.

    ;; Parse 835 x12 string to hierarchical structure
    (def loops
      {"835" {:nested #{"ISA"}}
       "ISA" {:nested #{"GS"}}
       "GS"  {:nested #{"ST"} :end #{"IEA"}}
       "ST"  {:nested #{"N1""LX"} :end #{"GE""ST"}}
       "N1"  {:end #{"SE""LX""N1"}}
       "LX"  {:nested #{"CLP"} :end #{"SE""LX"}}
       "CLP" {:nested #{"SVC"} :end #{"SE""LX""CLP"}}
       "SVC" {:end #{"SE""LX""CLP""SVC"}}})
    (defn parser-core [id ss acc]
      (let [seg-id               (first (first ss))
            {:keys [nested end]} (loops id)]
        (if (or (empty? ss) (and (contains? end seg-id) (not (empty? acc))))
          [acc ss]
          (let [[v ss-] (if (contains? nested seg-id)
                          (parser-core seg-id ss [])
                          [(first ss) (rest ss)])]
            (recur id ss- (conj acc v))))))
    (defn segments [s] (str/split (str/trim s) #"~"))
    (defn elements [s] (str/split (str/trim s) #"\*"))
    (defn x12 [s] (first (parser-core"835" (mapv elements (segments (or s ""))) [])))


    Presented under the spoiler

    Parsing result
    [[["ISA""00""          ""00""          ""ZZ""EMEDNYBAT      ""ZZ""ETIN           ""140305""0929""^""00501""111111123""0""P"":"]
      [["GS""HP""EMED""ETIN""20140301""09304100""111111123""X""005010X221A1"]
       [["ST""835""35681"]
        ["BPR""I""810.8""C""CHK""""""""""""""""""""""""20140331"]
        ["TRN""1""12345""1512345678"]
        ["REF""EV""XYZ CLEARINGHOUSE"]
        [["N1""PR""DENTAL OF ABC"]
         ["N3""225 MAIN STREET"]
         ["N4""CENTERVILLE""PA""17111"]
         ["PER""BL""JANE DOE""TE""9005555555"]]
        [["N1""PE""BAN DDS LLC""FI""999994703"]]
        [["LX""1"]
         [["CLP""7722337""1""226""132""""12""119932404007801"]
          ["NM1""QC""1""DOE""SANDY""""""""MI""SJD11112"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""132"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D0220""25""14"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""11"]
           ["AMT""B6""14"]]
          [["SVC""AD:D0230""22""10"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""12"]
           ["AMT""B6""10"]]
          [["SVC""AD:D0274""60""34"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""26"]
           ["AMT""B6""34"]]
          [["SVC""AD:D1110""73""49"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""24"]
           ["AMT""B6""49"]]]]
        [["LX""2"]
         [["CLP""7722337""1""119""74""""12""119932404007801"]
          ["NM1""QC""1""DOE""SALLY""""""""MI""SJD11111"]
          ["NM1""IL""1""DOE""JOHN""""""""MI""123456"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""74"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D1110""73""49"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""24"]
           ["AMT""B6""49"]]]]
        [["LX""3"]
         [["CLP""7722337""1""226""108""24""12""119932404007801"]
          ["NM1""QC""1""SMITH""SALLY""""""""MI""SJD11113"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""132"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D0220""25""0"]
           ["DTM""472""20140324"]
           ["CAS""PR""3""14"]
           ["CAS""CO""131""11"]
           ["AMT""B6""14"]]
          [["SVC""AD:D0230""22""0"]
           ["DTM""472""20140324"]
           ["CAS""PR""3""10"]
           ["CAS""CO""131""12"]
           ["AMT""B6""10"]]
          [["SVC""AD:D0274""60""34"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""26"]
           ["AMT""B6""34"]]
          [["SVC""AD:D1110""73""49"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""24"]
           ["AMT""B6""49"]]]]
        [["LX""4"]
         [["CLP""7722337""1""1145""14""902""12""119932404007801"]
          ["NM1""QC""1""SMITH""SAM""""""""MI""SJD11116"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""14"]
          [["SVC""AD:D0220""25""14"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""11"]
           ["AMT""B6""14"]]
          [["SVC""AD:D2790""940""0"]
           ["DTM""472""20140324"]
           ["CAS""PR""3""756"]
           ["CAS""CO""131""184"]]
          [["SVC""AD:D2950""180""0"]
           ["DTM""472""20140324"]
           ["CAS""PR""3""146"]
           ["CAS""CO""131""34"]]]]
        [["LX""5"]
         [["CLP""7722337""1""348""16.8""44.2""12""119932404007801"]
          ["NM1""QC""1""JONES""SAM""""""""MI""SJD11122"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""28"]
          [["SVC""AD:D4342""125""0"]
           ["DTM""472""20140313"]
           ["CAS""CO""131""125"]]
          [["SVC""AD:D4381""43""0"]
           ["DTM""472""20140313"]
           ["CAS""PR""3""33"]
           ["CAS""CO""131""10"]]
          [["SVC""AD:D2950""180""16.8"]
           ["DTM""472""20140313"]
           ["CAS""PR""3""11.2"]
           ["CAS""CO""131""152"]
           ["AMT""B6""28"]]]]
        [["LX""6"]
         [["CLP""7722337""1""226""132""""12""119932404007801"]
          ["NM1""QC""1""JONES""SALLY""""""""MI""SJD11133"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""132"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140321"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D0220""25""14"]
           ["DTM""472""20140321"]
           ["CAS""CO""131""11"]
           ["AMT""B6""14"]]
          [["SVC""AD:D0230""22""10"]
           ["DTM""472""20140321"]
           ["CAS""CO""131""12"]
           ["AMT""B6""10"]]
          [["SVC""AD:D0274""60""34"]
           ["DTM""472""20140321"]
           ["CAS""CO""131""26"]
           ["AMT""B6""34"]]
          [["SVC""AD:D1110""73""49"]
           ["DTM""472""20140321"]
           ["CAS""CO""131""24"]
           ["AMT""B6""49"]]]]
        [["LX""7"]
         [["CLP""7722337""1""179""108""""12""119932404007801"]
          ["NM1""QC""1""DOE""SAM""""""""MI""SJD99999"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""108"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D0274""60""34"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""26"]
           ["AMT""B6""34"]]
          [["SVC""AD:D1110""73""49"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""24"]
           ["AMT""B6""49"]]]]
        [["LX""8"]
         [["CLP""7722337""1""129""82""""12""119932404007801"]
          ["NM1""QC""1""DOE""SUE""""""""MI""SJD88888"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""82"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D1120""54""37"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""17"]
           ["AMT""B6""37"]]
          [["SVC""AD:D1208""29""20"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""9"]
           ["AMT""B6""20"]]]]
        [["LX""9"]
         [["CLP""7722337""1""221""144""""12""119932404007801"]
          ["NM1""QC""1""DOE""DONNA""""""""MI""SJD77777"]
          ["NM1""82""1""BAN""ERIN""""""""XX""1811901945"]
          ["AMT""AU""144"]
          [["SVC""AD:D0120""46""25"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""21"]
           ["AMT""B6""25"]]
          [["SVC""AD:D0330""92""62"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""30"]
           ["AMT""B6""62"]]
          [["SVC""AD:D1120""54""37"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""17"]
           ["AMT""B6""37"]]
          [["SVC""AD:D1208""29""20"]
           ["DTM""472""20140324"]
           ["CAS""CO""131""9"]
           ["AMT""B6""20"]]]]
        ["SE""190""35681"]]
       ["GE""1""111111123"]]
      ["IEA""1""111111123"]]]
    


    our initial example is the hierarchical structure of the segments.

    Actually, this task can already be considered solved. A dozen lines of Clojure-code provide us with a full-featured parser of any X12 documents in a hierarchical AST. But for the sake of completeness, you can show an example of bypassing this AST to perform some useful task — for example, constructing structures of the required format and writing this information to the database. Below is a sample code that bypasses the parsed structure and creates a list of objects based on it. A pair of universal helper functions for convenient access to data, as presented in AST, and a tree crawler, which forms an object with the ability to access the source data at any level of the hierarchy.

    ;; util helpers for extracting information
    (defn v-prefix? [v p]
      (and
       (vector? v)
       (= p (if (vector? p) (subvec v 0 (min (count v) (count p))) (get v 0)))))
    (defn items [v p & path] (filter #(v-prefix? (get-in % (vec path)) p) v))
    (defn item [v p & path] (first (apply items v p path)))
    ;; test function for extracting human-readable structure
    (defn tst [x12-string]
      (for [isa (items (x12 x12-string) "ISA"0)
            gs  (items isa "GS"0)
            st  (items gs "ST"0)
            lx  (items st "LX"0)
            clp (items lx "CLP"0)]
        (let [bpr (item st "BPR")]
          {:message      {:received (get-in isa [09])
                          :created  (get-in gs [04])}
           :transaction  {:check (get (item st "TRN") 2)
                          :payed (get bpr 16)
                          :total (read-string (get bpr 2))}
           :insurer      (get-in (item st ["N1""PR"] 0) [02])
           :organization (get-in (item st ["N1""PE"] 0) [02])
           :claim        {:patient (if-let [x (item clp ["NM1""QC"])]
                                     (str (get x 3) " " (get x 4)))
                          :total   (read-string (get-in clp [04]))}
           :services     (mapv
                          (fn [svc]
                            {:code   (get-in svc [01])
                             :amount (read-string (get-in svc [03]))
                             :date   (get (item svc ["DTM""472"]) 2)})
                          (items clp "SVC"0))})))
    


    Presented under the spoiler

    The result of the function
    ({:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"DOE SANDY", :total132},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D0220", :amount14, :date"20140324"}
       {:code"AD:D0230", :amount10, :date"20140324"}
       {:code"AD:D0274", :amount34, :date"20140324"}
       {:code"AD:D1110", :amount49, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"DOE SALLY", :total74},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D1110", :amount49, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"SMITH SALLY", :total108},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D0220", :amount0, :date"20140324"}
       {:code"AD:D0230", :amount0, :date"20140324"}
       {:code"AD:D0274", :amount34, :date"20140324"}
       {:code"AD:D1110", :amount49, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"SMITH SAM", :total14},
      :services
      [{:code"AD:D0220", :amount14, :date"20140324"}
       {:code"AD:D2790", :amount0, :date"20140324"}
       {:code"AD:D2950", :amount0, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"JONES SAM", :total16.8},
      :services
      [{:code"AD:D4342", :amount0, :date"20140313"}
       {:code"AD:D4381", :amount0, :date"20140313"}
       {:code"AD:D2950", :amount16.8, :date"20140313"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"JONES SALLY", :total132},
      :services
      [{:code"AD:D0120", :amount25, :date"20140321"}
       {:code"AD:D0220", :amount14, :date"20140321"}
       {:code"AD:D0230", :amount10, :date"20140321"}
       {:code"AD:D0274", :amount34, :date"20140321"}
       {:code"AD:D1110", :amount49, :date"20140321"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"DOE SAM", :total108},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D0274", :amount34, :date"20140324"}
       {:code"AD:D1110", :amount49, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"DOE SUE", :total82},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D1120", :amount37, :date"20140324"}
       {:code"AD:D1208", :amount20, :date"20140324"}]}
     {:message {:received"140305", :created"20140301"},
      :transaction {:check"12345", :payed"20140331", :total810.8},
      :insurer"DENTAL OF ABC",
      :organization"BAN DDS LLC",
      :claim {:patient"DOE DONNA", :total144},
      :services
      [{:code"AD:D0120", :amount25, :date"20140324"}
       {:code"AD:D0330", :amount62, :date"20140324"}
       {:code"AD:D1120", :amount37, :date"20140324"}
       {:code"AD:D1208", :amount20, :date"20140324"}]})
    


    - you can submit to the table to write to the database, visualize on the UI, or use it in any other way.

    Similar code and algorithm for parsing X12 documents is used in my working draft - of course, with a bunch of additional functionality. The code examples in the article are the minimum working prototype for demonstrating the algorithm and approach. Sorry, that without abstract factories, combinatorial parsers, recursive grammars and other serious things - only 3 dozen lines of code)

    Those who want can play with this parser in any online replay that supports Clojure - ideone / replit / etc. From dependencies, you only need to connect a namespace clojure.string , well, maybe clojure.pprintfor beautiful print results. You can try to change the code of the test function of creating an object, get other fields from the parsed structure, etc. Examples of X12 type 8 response documents can be found online.

    Also popular now: