-----------------------------------------------------------------------------
-- |
-- Module      :  UTF8Prelude
-- Copyright   :  (c) Péter Diviánszky 2008
-- License     :  BSD3-style (see LICENSE)
-- 
-- Maintainer:    divip@aszt.inf.elte.hu
-- Stability   :  alpha
-- Portability :  portable
--
-- "UTF8Prelude" defines the same entities as "Prelude" but with UTF8 text I/O operations.
--
-- Usage:
--
-- > {-# LANGUAGE NoImplicitPrelude #-}
-- >
-- > import UTF8Prelude
--
-- or
--
-- > import Prelude()
-- > import UTF8Prelude
--
-- or
--
-- > import qualified Prelude
-- > import UTF8Prelude
--
-- "UTF8Prelude" re-exports "System.IO.UTF8" but hides the definitions not defined in "Prelude".

module UTF8Prelude 
    ( module Prelude
    , module System.IO.UTF8
    , error
    ) where

import Codec.Binary.UTF8.String (encodeString)

import System.IO.UTF8 hiding
    ( hGetLine
    , hGetContents
    , hPutStr
    , hPutStrLn
    )

import Prelude hiding 
    ( error
    , print
    , putStr
    , putStrLn
    , getLine
    , readLn
    , readFile
    , writeFile
    , appendFile
    , getContents
    )

import qualified Prelude

-- | UTF8 encoded error messages.
error :: String -> a
error = Prelude.error . encodeString