From c6c1ad94816dc3c4d139cce46e93a9721d05e2a2 Mon Sep 17 00:00:00 2001
From: Eric Mertens <emertens@galois.com>
Date: Thu, 4 Jun 2009 13:12:47 -0700
Subject: [PATCH] Add System.Environment.UTF8 wrapper

bump to 0.3.5
---
 Data/String/UTF8.hs        |  3 +--
 System/Environment/UTF8.hs | 25 +++++++++++++++++++++++++
 utf8-string.cabal          |  3 ++-
 3 files changed, 28 insertions(+), 3 deletions(-)
 create mode 100644 System/Environment/UTF8.hs

diff --git a/Data/String/UTF8.hs b/Data/String/UTF8.hs
index 281076a..fe1589f 100644
--- a/Data/String/UTF8.hs
+++ b/Data/String/UTF8.hs
@@ -1,5 +1,4 @@
-{-# LANGUAGE MultiParamTypeClasses #-}
-{-# OPTIONS_GHC -fallow-undecidable-instances #-}
+{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-}
 module Data.String.UTF8
   ( -- * Representation
     UTF8
diff --git a/System/Environment/UTF8.hs b/System/Environment/UTF8.hs
new file mode 100644
index 0000000..fe838e8
--- /dev/null
+++ b/System/Environment/UTF8.hs
@@ -0,0 +1,25 @@
+module System.Environment.UTF8
+  (getArgs, getProgName, getEnv, withArgs, withProgName, getEnvironment)
+  where
+
+import Codec.Binary.UTF8.String (decodeString)
+import qualified System.Environment as Sys
+
+getArgs :: IO [String]
+getArgs = map decodeString `fmap` Sys.getArgs
+
+getProgName :: IO String
+getProgName = decodeString `fmap` Sys.getProgName
+
+getEnv :: String -> IO String
+getEnv x = decodeString `fmap` Sys.getEnv x
+
+withArgs :: [String] -> IO a -> IO a
+withArgs = Sys.withArgs
+
+withProgName :: String -> IO a -> IO a
+withProgName = Sys.withProgName
+
+getEnvironment :: IO [(String,String)]
+getEnvironment = map f `fmap` Sys.getEnvironment
+  where f (a,b) = (decodeString a, decodeString b)
diff --git a/utf8-string.cabal b/utf8-string.cabal
index 0585cf3..c050bb0 100644
--- a/utf8-string.cabal
+++ b/utf8-string.cabal
@@ -1,5 +1,5 @@
 Name:               utf8-string
-Version:            0.3.4
+Version:            0.3.5
 Author:             Eric Mertens
 Maintainer:         emertens@galois.com
 License:            BSD3
@@ -29,6 +29,7 @@ library
   Exposed-modules:    Codec.Binary.UTF8.String
                       Codec.Binary.UTF8.Generic
                       System.IO.UTF8
+                      System.Environment.UTF8
                       Data.String.UTF8
                       Data.ByteString.UTF8
                       Data.ByteString.Lazy.UTF8
-- 
GitLab