{- |
Module:        Network.Monad.Body
Copyright:     (c) 2009 Henning Thielemann
License:       BSD

Stability:     experimental
Portability:   non-portable (not tested)
-}
module Network.Monad.Body (C(..), CharType(..) {- for Transfer.Offline -}) where

import qualified Network.BufferType as BT

import Data.Monoid (Monoid, )
import qualified Data.ByteString      as BS
import qualified Data.ByteString.Lazy as BL
import Network.Monad.Utility (crlf, )


class Monoid body => C body where
   fromString   :: String -> body
   toString     :: body -> String
   isLineTerm   :: body -> Bool
   isEmpty      :: body -> Bool

class CharType char where
   fromChar :: Char -> char
   toChar   :: char -> Char

instance CharType Char where
   fromChar = id
   toChar   = id

instance CharType char => C [char] where
   fromString = map fromChar
   toString   = map toChar
   isLineTerm = (crlf==) . toString
   isEmpty    = null

instance C BS.ByteString where
   fromString = BT.buf_fromStr    BT.strictBufferOp
   toString   = BT.buf_toStr      BT.strictBufferOp
   isLineTerm = BT.buf_isLineTerm BT.strictBufferOp
   isEmpty    = BT.buf_isEmpty    BT.strictBufferOp

instance C BL.ByteString where
   fromString = BT.buf_fromStr    BT.lazyBufferOp
   toString   = BT.buf_toStr      BT.lazyBufferOp
   isLineTerm = BT.buf_isLineTerm BT.lazyBufferOp
   isEmpty    = BT.buf_isEmpty    BT.lazyBufferOp