File: hiconv.hs

package info (click to toggle)
haskell-iconv 0.4.1.0-2
  • links: PTS, VCS
  • area: main
  • in suites: wheezy
  • size: 108 kB
  • sloc: haskell: 510; ansic: 18; makefile: 2
file content (130 lines) | stat: -rw-r--r-- 4,202 bytes parent folder | download | duplicates (7)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
{-
 - This example is similar to the commandline iconv program.
 - Author: Conrad Parker, July 2007

  Usage: hiconv [options] filename

    -h, -?       --help, --usage       Display this help and exit
    -f encoding  --from-code=encoding  Convert characters from encoding
    -t encoding  --to-code=encoding    Convert characters to encoding
    -c           --discard             Discard invalid characters from output
                 --transliterate       Transliterate unconvertable characters
    -o file      --output=file         Specify output file (instead of stdout)

 -}

module Main where

import Control.Monad (when)
import System.Environment (getArgs, getProgName)
import System.Console.GetOpt (getOpt, usageInfo,
                              OptDescr(..), ArgDescr(..), ArgOrder(..))
import System.Exit (exitFailure)

import qualified Data.ByteString.Lazy as Lazy
import qualified Codec.Text.IConv as IConv

------------------------------------------------------------
-- main
--

main :: IO ()
main = do
    args <- getArgs
    (config, filenames) <- processArgs args

    let inputFile = head filenames
    input <- case inputFile of
        "-" -> Lazy.getContents
        _   -> Lazy.readFile inputFile

    let convert = case fuzzyConvert config of
                    Nothing   -> IConv.convert
                    Just fuzz -> IConv.convertFuzzy fuzz
        output = convert (fromEncoding config) (toEncoding config) input
        o = outputFile config

    case o of
        "-" -> Lazy.putStr output
        _   -> Lazy.writeFile o output

------------------------------------------------------------
-- Option handling
--

data Config =
    Config {
        fromEncoding :: String,
        toEncoding :: String,
	fuzzyConvert :: Maybe IConv.Fuzzy,
        outputFile :: FilePath
    }

defaultConfig =
    Config {
        fromEncoding = "",
        toEncoding = "",
	fuzzyConvert = Nothing,
        outputFile = "-"
    }

data Option = Help
            | FromEncoding String
            | ToEncoding String
	    | Discard | Translit
            | OutputFile String
            deriving Eq

options :: [OptDescr Option]
options = [ Option ['h', '?'] ["help", "usage"] (NoArg Help)
              "Display this help and exit"
          , Option ['f'] ["from-code"] (ReqArg FromEncoding "encoding")
              "Convert characters from encoding"
          , Option ['t'] ["to-code"] (ReqArg ToEncoding "encoding")
              "Convert characters to encoding"
	  , Option ['c'] ["discard"]       (NoArg Discard)
	      "Discard invalid characters from output"
	  , Option []    ["transliterate"] (NoArg Translit)
	      "Transliterate unconvertable characters"
          , Option ['o'] ["output"] (ReqArg OutputFile "file")
              "Specify output file (instead of stdout)"
          ]

processArgs :: [String] -> IO (Config, [String])
processArgs args = do
    case getOpt Permute options args of
        (opts, args, errs) -> do
            processHelp opts
            let config = processConfig defaultConfig opts
            checkConfig errs config args
            return (config, args)

checkConfig :: [String] -> Config -> [String] -> IO ()
checkConfig errs config filenames = do
    when (any null [fromEncoding config, toEncoding config] || null filenames) $
      processHelp [Help]
    when (not (null errs)) $ do
      mapM_ putStr errs
      processHelp [Help]

processHelp :: [Option] -> IO ()
processHelp opts = do
    name <- getProgName
    let header = "\nUsage: " ++ name ++ " [options] filename\n"
    when (Help `elem` opts) $ do
        putStrLn $ usageInfo header options
        exitFailure

processConfig :: Config -> [Option] -> Config
processConfig = foldl processOneOption
    where
        processOneOption config (FromEncoding f) =
            config {fromEncoding = f}
        processOneOption config (ToEncoding t) =
            config {toEncoding = t}
        processOneOption config (OutputFile o) =
            config {outputFile = o}
        processOneOption config Discard =
	    config {fuzzyConvert = Just IConv.Discard}
        processOneOption config Translit =
            config {fuzzyConvert = Just IConv.Transliterate}