-- | Module to generate the config file module Transformer ( generateConfigFile ) where import PhoneNumberMetadata import Text.XML.HXT.Core import Data.Text -- * Pickler-Unpicklers for Phone number types defined in 'Phone' instance XmlPickler PhoneNumberMetadata where xpickle = xpPhoneNumberMetadata instance XmlPickler Territory where xpickle = xpTerritory instance XmlPickler NumberFormat where xpickle = xpNumberFormat xpPhoneNumberMetadata :: PU PhoneNumberMetadata xpPhoneNumberMetadata = xpElem "phoneNumberMetadata" $ xpWrap (\ts -> PhoneNumberMetadata ts, \p -> territories p) (xpElem "territories" (xpList xpTerritory)) xpTerritory :: PU Territory xpTerritory = xpElem "territory" $ xpWrap (territoryPickler, territoryUnpickler) $ xpTerritoryTuples xpNumberFormat :: PU NumberFormat xpNumberFormat = xpElem "numberFormat" $ xpWrap (numberFormatPickler, numberFormatUnPickler) $ xp8Tuple (xpOption (xpAttr "nationalPrefixFormattingRule" xpText)) (xpOption (xpAttr "nationalPrefixOptionalWhenFormatting" xpText)) (xpOption (xpAttr "carrierCodeFormattingRule" xpText)) (xpAttr "pattern" xpText) (xpOption (xpAttr "leadingZeroPossible" xpText)) (xpOption (xpList (xpElem "leadingDigits" xpText))) (xpElem "format" xpText) (xpOption (xpList (xpElem "intlFormat" xpText))) xpPhoneNumberPatterns patternType = xpElem patternType $ xpWrap (\(np, pp, e) -> PhoneNumberPatterns np pp e, \pnp -> ( nationalNumberPattern pnp , possibleNumberPattern pnp , exampleNumber pnp )) $ xpTriple (xpOption (xpElem "nationalNumberPattern" xpText)) (xpOption (xpElem "possibleNumberPattern" xpText)) (xpOption (xpElem "exampleNumber" xpText)) numberFormatPickler (npfr, npowf, ccfr, p, lzp, ld, f, intlf) = NumberFormat npfr (toBool npowf) ccfr p (toBool lzp) ld f intlf numberFormatUnPickler nf = ( nfNationalPrefixFormattingRule nf, fromBool $ nfNationalPrefixOptionalWhenFormatting nf, nfCarrierCodeFormattingRule nf, nfPattern nf, fromBool $ nfLeadingZeroPossible nf, nfLeadingDigits nf, nfFormat nf, nfInternationalFormat nf ) xpTerritoryTuples = xp30Tuple( xpAttr "id" xpText ) ( xpAttr "countryCode" xpText ) (xpOption(xpAttr "mainCountryForCode" xpText )) (xpOption(xpAttr "leadingDigits" xpText )) (xpOption(xpAttr "preferredInternationalPrefix" xpText )) (xpOption(xpAttr "internationalPrefix" xpText )) (xpOption(xpAttr "nationalPrefix" xpText )) (xpOption(xpAttr "nationalPrefixForParsing" xpText )) (xpOption(xpAttr "nationalPrefixTransformRule" xpText )) (xpOption(xpAttr "preferredExtnPrefix" xpText )) (xpOption(xpAttr "nationalPrefixFormattingRule" xpText )) (xpOption(xpAttr "nationalPrefixOptionalWhenFormatting" xpText )) (xpOption(xpAttr "leadingZeroPossible" xpText )) (xpOption(xpAttr "carrierCodeFormattingRule" xpText )) (xpOption(xpAttr "mobileNumberPortableRegion" xpText )) (xpElem "references" (xpList (xpElem "sourceUrl" xpText ))) (xpOption(xpElem "availableFormats" (xpList xpNumberFormat))) (xpOption(xpPhoneNumberPatterns "generalDesc")) (xpOption(xpPhoneNumberPatterns "noInternationalDialling")) (xpOption(xpPhoneNumberPatterns "areaCodeOptional")) (xpOption(xpPhoneNumberPatterns "fixedLine")) (xpOption(xpPhoneNumberPatterns "mobile")) (xpOption(xpPhoneNumberPatterns "pager")) (xpOption(xpPhoneNumberPatterns "tollFree")) (xpOption(xpPhoneNumberPatterns "premiumRate")) (xpOption(xpPhoneNumberPatterns "sharedCost")) (xpOption(xpPhoneNumberPatterns "personalNumber")) (xpOption(xpPhoneNumberPatterns "voip")) (xpOption(xpPhoneNumberPatterns "uan")) (xpOption(xpPhoneNumberPatterns "voicemail")) territoryPickler ( abbreviation , countryCode , mainCountryForCode , leadingDigits , preferredInternationalPrefix , internationalPrefix , nationalPrefix , nationalPrefixForParsing , nationalPrefixTransformRule , preferredExtensionPrefix , nationalPrefixFormattingRule , nationalPrefixOptionalWhenFormatting , leadingZeroPossible , carrierCodeFormattingRule , mobileNumberPortableRegion , references , availableFormats , generalDescription , noInternationalDialling , areaCodeOptional , fixedLine , mobile , pager , tollFree , premiumRate , sharedCost , personalNumber , voip , uan , voicemail ) = Territory abbreviation countryCode ( toBool mainCountryForCode ) leadingDigits preferredInternationalPrefix internationalPrefix nationalPrefix nationalPrefixForParsing nationalPrefixTransformRule preferredExtensionPrefix nationalPrefixFormattingRule ( toBool nationalPrefixOptionalWhenFormatting ) ( toBool leadingZeroPossible ) carrierCodeFormattingRule ( toBool mobileNumberPortableRegion ) references availableFormats generalDescription noInternationalDialling areaCodeOptional fixedLine mobile pager tollFree premiumRate sharedCost personalNumber voip uan voicemail territoryUnpickler t = ( abbreviation t , countryCode t , fromBool $ mainCountryForCode t , leadingDigits t , preferredInternationalPrefix t , internationalPrefix t , nationalPrefix t , nationalPrefixForParsing t , nationalPrefixTransformRule t , preferredExtensionPrefix t , nationalPrefixFormattingRule t , fromBool $ nationalPrefixOptionalWhenFormatting t , fromBool $ leadingZeroPossible t , carrierCodeFormattingRule t , fromBool $ mobileNumberPortableRegion t , references t , availableFormats t , generalDescription t , noInternationalDialling t , areaCodeOptional t , fixedLine t , mobile t , pager t , tollFree t , premiumRate t , sharedCost t , personalNumber t , voip t , uan t , voicemail t ) toBool:: Maybe String -> Maybe Bool toBool ( Just "true" ) = Just True toBool ( Just "false" ) = Just False toBool _ = Nothing fromBool:: Maybe Bool -> Maybe String fromBool ( Just x ) = Just ((unpack . toLower . pack . show) x) fromBool Nothing = Nothing generateConfigFile = do runX (xunpickleDocument xpPhoneNumberMetadata [ withValidate no , withTrace 1 , withRemoveWS yes , withPreserveComment no ] "config/phoneNumberMetadata.xml" >>> processXML ) return () processXML :: IOSArrow PhoneNumberMetadata PhoneNumberMetadata processXML = arrIO (\x -> do { writeFile "config/phoneNumberMetadata.hs" $ show x; return x; }) -- | HXT defines tuples upto 24 elements ('xp24Tuple'). -- We need a 30-tuple to handle all our attributes & elements of 'Territory' xp30Tuple :: PU a -> PU b -> PU c -> PU d -> PU e -> PU f -> PU g -> PU h -> PU i -> PU j -> PU k -> PU l -> PU m -> PU n -> PU o -> PU p -> PU q -> PU r -> PU s -> PU t -> PU u -> PU v -> PU w -> PU x -> PU aa -> PU bb -> PU cc -> PU dd -> PU ee -> PU ff -> PU ( a, b, c, d, e, f , g, h, i, j, k, l , m, n, o, p, q, r , s, t, u, v, w, x , aa, bb, cc, dd, ee, ff) xp30Tuple a b c d e f g h i j k l m n o p q r s t u v w x aa bb cc dd ee ff = xpWrap (\( (a, b, c, d, e, f) , (g, h, i, j, k, l) , (m, n, o, p, q, r) , (s, t, u, v, w, x) , (aa, bb, cc, dd, ee, ff)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, aa, bb, cc, dd, ee, ff), \(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, aa, bb, cc, dd, ee, ff) -> ( (a, b, c, d, e, f) , (g, h, i, j, k, l) , (m, n, o, p, q, r) , (s, t, u, v, w, x) , (aa, bb, cc, dd, ee, ff)) ) $ (xp5Tuple (xp6Tuple a b c d e f) (xp6Tuple g h i j k l) (xp6Tuple m n o p q r) (xp6Tuple s t u v w x) (xp6Tuple aa bb cc dd ee ff))