module Text.XML.HaXml.Schema.NameConversion
  ( module Text.XML.HaXml.Schema.NameConversion
  ) where
import Text.XML.HaXml.Types
import Text.XML.HaXml.Namespaces
import Data.Char
import Data.List
newtype XName = XName QName
  deriving (Eq,Show)
newtype HName = HName String
    deriving Show
data NameConverter = NameConverter
                       { modid    :: XName -> HName
                       , conid    :: XName -> HName
                       , varid    :: XName -> HName
                       , unqconid :: XName -> HName
                       , unqvarid :: XName -> HName
                       , fwdconid :: XName -> HName  
                       , fieldid  :: XName -> XName -> HName
                       }
simpleNameConverter :: NameConverter
simpleNameConverter = NameConverter
    { modid    = \(XName qn)-> HName . mkConid . hierarchy $ qn
    , conid    = \(XName qn)-> HName . mkConid . hierarchy $ qn
    , varid    = \(XName qn)-> HName . mkVarid . last avoidKeywords
                                               . hierarchy $ qn
    , unqconid = \(XName qn)-> HName . mkConid . local $ qn
    , unqvarid = \(XName qn)-> HName . mkVarid . last avoidKeywords
                                               . local $ qn
    , fwdconid = \(XName qn)-> HName . ("Fwd"++) . mkConid . local $ qn
    , fieldid  = \(XName qnt) (XName qnf)->
                               HName $ (mkVarid . last id . hierarchy $ qnt)
                                       ++ "_" ++
                                       (mkVarid . last id . hierarchy $ qnf)
    }
  where
    hierarchy (N n)     = wordsBy (==':') n
    hierarchy (QN ns n) = [nsPrefix ns, n]
    local               = (:[]) . Prelude.last . hierarchy
    mkConid  [c]        | map toLower c == "string"     = "Xsd.XsdString"
                        | otherwise = first toUpper c
    mkConid [m,c]       | map toLower c == "string"     = "Xsd.XsdString"
                        | otherwise = first toUpper m++"."++first toUpper c
    mkVarid  [v]        = first toLower v
    mkVarid [m,v]       = first toUpper m++"."++first toLower v
    first f (x:xs)
      | not (isAlpha x) = f 'v': x: xs
      | otherwise       = f x: xs
    last  f [x]         = [ f x ]
    last  f (x:xs)      = x: last f xs
 
avoidKeywords :: String -> String
avoidKeywords s
    | s `elem` keywords  = s++"_"
    | otherwise          = s
  where
    keywords = [ "case", "of", "data", "default", "deriving", "do"
               , "forall", "foreign", "if", "then", "else", "import"
               , "infix", "infixl", "infixr", "instance", "let", "in"
               , "module", "newtype", "qualified", "type", "where" ]
fpml :: String -> String
fpml = concat
         . intersperse "."    
         . ("Data":)          
         . rearrange          
         . map cap            
         . version            
         . wordsBy (=='-')    
         . basename ".xsd"    
  where
    version ws = let (last2,remain) = splitAt 2 . reverse $ ws in
                 if all (all isDigit) last2 && length ws > 2
                 then head ws: ('V':concat (reverse last2))
                             : tail (reverse remain)
                 else ws
    rearrange [a,v,"PostTrade",c] = [a,v,"PostTrade",c]
    rearrange [a,v,b,c]           = [a,v,c,b]
    rearrange [a,v,b,c,d]         = [a,v,d,b++c]
    rearrange [a,v,b,c,d,e]       = [a,v,e,b++c++d]
    rearrange v                   = v
    cap :: String -> String
    cap "Fpml"      = "FpML"
    cap "fpml"      = "FpML"
    cap "cd"        = "CD"
    cap "eq"        = "EQ"
    cap "fx"        = "FX"
    cap "ird"       = "IRD"
    cap "posttrade" = "PostTrade"
    cap "pretrade"  = "PreTrade"
    cap (c:cs)      = toUpper c: cs
wordsBy :: (a->Bool) -> [a] -> [[a]]
wordsBy pred = wordsBy' pred []
  where wordsBy' p []  []     = []
        wordsBy' p acc []     = [reverse acc]
        wordsBy' p acc (c:cs) | p c       = reverse acc :
                                            wordsBy' p [] (dropWhile p cs)
                              | otherwise = wordsBy' p (c:acc) cs
basename :: String -> String -> String
basename ext = reverse . snip (reverse ext)
                       . takeWhile (not.(`elem`"\\/")) . reverse
    where snip p s = if p `isPrefixOf`s then drop (length p) s else s
fpmlNameConverter :: NameConverter
fpmlNameConverter = simpleNameConverter
    { modid   = (\(HName h)-> HName (fpml h))
                . modid simpleNameConverter
 
 
 
 
    , fwdconid = \(XName qn)-> HName . ("Pseudo"++) . mkConId . local $ qn
    , fieldid  = \(XName qnt) (XName qnf)->
                  let t = mkVarId . local $ qnt
                      f = mkVarId . local $ qnf
                  in HName $ if t==f then f
                             else if t `isPrefixOf` f
                             then t ++"_"++ mkVarId (drop (length t) f)
                             else mkVarId (shorten (mkConId t)) ++"_"++ f
    }
  where
    hierarchy (N n)     = wordsBy (==':') n
    hierarchy (QN ns n) = [nsPrefix ns, n]
    local               = Prelude.last . hierarchy
    mkVarId   ("id")    = "ID"
    mkVarId   (v:vs)    = toLower v: vs
    mkConId   (v:vs)    = toUpper v: vs
    shorten t | length t <= 12 = t
              | length t <  35 = concatMap shortenWord (splitWords t)
              | otherwise      = map toLower (head t: filter isUpper (tail t))
    splitWords "" = []
    splitWords (u:s)  = let (w,rest) = span (not . isUpper) s
                        in (u:w) : splitWords rest
    shortenWord "Request"     = "Req" 
    shortenWord "Reference"   = "Ref"
    shortenWord "Valuation"   = "Val"
    shortenWord "Calendar"    = "Cal"
    shortenWord "Absolute"    = "Abs"
    shortenWord "Additional"  = "Add"
    shortenWord "Business"    = "Bus"
    shortenWord "Standard"    = "Std"
    shortenWord "Calculation" = "Calc"
    shortenWord "Quotation"   = "Quot"
    shortenWord "Information" = "Info"
    shortenWord "Exchange"    = "Exch"
    shortenWord "Characteristics" = "Char"
    shortenWord "Multiple"    = "Multi"
    shortenWord "Constituent" = "Constit"
    shortenWord "Convertible" = "Convert"
    shortenWord "Underlyer"   = "Underly"
    shortenWord "Underlying"  = "Underly"
    shortenWord "Properties"  = "Props"
    shortenWord "Property"    = "Prop"
    shortenWord "Affirmation" = "Affirmation"
    shortenWord "Affirmed"    = "Affirmed"
    shortenWord w | length w < 8 = w   
                  | otherwise    = case splitAt 5 w of
                                     (pref,c:suf) | isVowel c -> pref
                                                  | otherwise -> pref++[c]
    isVowel = (`elem` "aeiouy")