{-# LINE 1 "src/Xmobar/System/Localize.hsc" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Xmobar.System.Localize
( setupTimeLocale,
getTimeLocale
) where
import Foreign.C
{-# LINE 25 "src/Xmobar/System/Localize.hsc" #-}
import qualified Data.Time.Format as L
{-# LINE 27 "src/Xmobar/System/Localize.hsc" #-}
import Codec.Binary.UTF8.String
type NlItem = CInt
foreign import ccall unsafe "langinfo.h nl_langinfo"
nl_langinfo :: NlItem -> IO CString
amStr :: NlItem
amStr :: NlItem
amStr = NlItem
131110
pmStr :: NlItem
pmStr :: NlItem
pmStr = NlItem
131111
dTFmt :: NlItem
dTFmt :: NlItem
dTFmt = NlItem
131112
dFmt :: NlItem
dFmt :: NlItem
dFmt = NlItem
131113
tFmt :: NlItem
tFmt :: NlItem
tFmt = 131114
tFmtAmpm :: NlItem
tFmtAmpm :: NlItem
tFmtAmpm = NlItem
131115
abday1 :: NlItem
abday1 :: NlItem
abday1 = NlItem
131072
abday7 :: NlItem
abday7 :: NlItem
abday7 = NlItem
131078
day1 :: NlItem
day1 :: NlItem
day1 = 131079
day7 :: NlItem
day7 :: NlItem
day7 = 131085
abmon1 :: NlItem
abmon1 :: NlItem
abmon1 = NlItem
131086
abmon12 :: NlItem
abmon12 :: NlItem
abmon12 = NlItem
131097
mon1 :: NlItem
mon1 :: NlItem
mon1 = NlItem
131098
mon12 :: NlItem
mon12 :: NlItem
mon12 = NlItem
131109
{-# LINE 45 "src/Xmobar/System/Localize.hsc" #-}
getLangInfo :: NlItem -> IO String
getLangInfo item = do
itemStr <- nl_langinfo item
str <- peekCString itemStr
return $ if isUTF8Encoded str then decodeString str else str
foreign import ccall unsafe "locale.h setlocale"
setlocale :: CInt -> CString -> IO CString
setupTimeLocale :: String -> IO ()
setupTimeLocale l = withCString l (setlocale 2) >> return ()
{-# LINE 58 "src/Xmobar/System/Localize.hsc" #-}
getTimeLocale :: IO L.TimeLocale
getTimeLocale = do
days <- mapM getLangInfo [day1 .. day7]
abdays <- mapM getLangInfo [abday1 .. abday7]
mons <- mapM getLangInfo [mon1 .. mon12]
abmons <- mapM getLangInfo [abmon1 .. abmon12]
amstr <- getLangInfo amStr
pmstr <- getLangInfo pmStr
dtfmt <- getLangInfo dTFmt
dfmt <- getLangInfo dFmt
tfmt <- getLangInfo tFmt
tfmta <- getLangInfo tFmtAmpm
let t = L.defaultTimeLocale {L.wDays = zip days abdays
,L.months = zip mons abmons
,L.amPm = (amstr, pmstr)
,L.dateTimeFmt = dtfmt
,L.dateFmt = dfmt
,L.timeFmt = tfmt
,L.time12Fmt = tfmta}
return t