Skip to content
Snippets Groups Projects
Commit c6c1ad94 authored by emertens's avatar emertens
Browse files

Add System.Environment.UTF8 wrapper

bump to 0.3.5
parent 17c5d61d
No related branches found
Tags v0.3.5
No related merge requests found
{-# LANGUAGE MultiParamTypeClasses #-}
{-# OPTIONS_GHC -fallow-undecidable-instances #-}
{-# LANGUAGE MultiParamTypeClasses, UndecidableInstances #-}
module Data.String.UTF8
( -- * Representation
UTF8
......
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)
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
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment