{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeSynonymInstances #-} {-# LANGUAGE TemplateHaskell #-} {- | Module : Data.Convertible.Instances.C Copyright : Copyright (C) 2009 John Goerzen License : LGPL Maintainer : Michael Snoyman Stability : provisional Portability: portable Numeric instances for Convertible for C types. See comments in "Data.Convertible.Instances.Num". Copyright (C) 2009 John Goerzen All rights reserved. For license and copyright information, see the file COPYRIGHT -} module Data.Convertible.Instances.C() where import Data.Convertible.Base import Data.Convertible.Utils import Data.Convertible.Instances.Num() import Data.Int import Data.Word import Foreign.C.Types $(deriveAttempts [ (''CChar, ''Integer) , (''CDouble, ''CFloat) , (''CDouble, ''Double) , (''CDouble, ''Float) , (''CDouble, ''Integer) , (''CDouble, ''Rational) , (''CFloat, ''CDouble) , (''CFloat, ''Double) , (''CFloat, ''Float) , (''CFloat, ''Integer) , (''CFloat, ''Rational) , (''CInt, ''Integer) , (''CLLong, ''Integer) , (''CLong, ''Integer) , (''CSChar, ''Integer) , (''CShort, ''Integer) , (''CSize, ''Integer) , (''CUChar, ''Integer) , (''CUInt, ''Integer) , (''CULLong, ''Integer) , (''CULong, ''Integer) , (''CUShort, ''Integer) , (''CWchar, ''Integer) , (''Double, ''CDouble) , (''Double, ''CFloat) , (''Float, ''CDouble) , (''Float, ''CFloat) , (''Int16, ''CDouble) , (''Int16, ''CFloat) , (''Int32, ''CDouble) , (''Int32, ''CFloat) , (''Int64, ''CDouble) , (''Int64, ''CFloat) , (''Int8, ''CDouble) , (''Int8, ''CFloat) , (''Int, ''CDouble) , (''Int, ''CFloat) , (''Integer, ''CDouble) , (''Integer, ''CFloat) , (''Rational, ''CDouble) , (''Rational, ''CFloat) , (''Word16, ''CDouble) , (''Word16, ''CFloat) , (''Word32, ''CDouble) , (''Word32, ''CFloat) , (''Word64, ''CDouble) , (''Word64, ''CFloat) , (''Word8, ''CDouble) , (''Word8, ''CFloat) , (''Word, ''CDouble) , (''Word, ''CFloat) ]) -- remainder of this file generated by utils/genCinstances.hs -- Section 1 instance ConvertAttempt CFloat Int where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Int8 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int8 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Int16 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int16 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Int32 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int32 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Int64 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int64 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Word where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Word8 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word8 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Word16 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word16 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Word32 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word32 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CFloat Word64 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word64 CFloat where convertSuccess= fromIntegral instance ConvertAttempt CDouble Int where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Int8 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int8 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Int16 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int16 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Int32 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int32 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Int64 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Int64 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Word where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Word8 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word8 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Word16 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word16 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Word32 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word32 CDouble where convertSuccess= fromIntegral instance ConvertAttempt CDouble Word64 where convertAttempt = boundedConversion (return . truncate) instance ConvertSuccess Word64 CDouble where convertSuccess= fromIntegral -- Section 2 instance ConvertSuccess CFloat Double where convertSuccess = realToFrac instance ConvertSuccess Double CFloat where convertSuccess = realToFrac instance ConvertSuccess CFloat Float where convertSuccess = realToFrac instance ConvertSuccess Float CFloat where convertSuccess = realToFrac instance ConvertSuccess CFloat Rational where convertSuccess = realToFrac instance ConvertSuccess Rational CFloat where convertSuccess = realToFrac instance ConvertSuccess CDouble Double where convertSuccess = realToFrac instance ConvertSuccess Double CDouble where convertSuccess = realToFrac instance ConvertSuccess CDouble Float where convertSuccess = realToFrac instance ConvertSuccess Float CDouble where convertSuccess = realToFrac instance ConvertSuccess CDouble Rational where convertSuccess = realToFrac instance ConvertSuccess Rational CDouble where convertSuccess = realToFrac -- Section 3 instance ConvertAttempt CChar Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Int where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Int8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int8 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Int16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int16 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Int32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int32 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Int64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Int64 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Word where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Word8 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word8 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Word16 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word16 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Word32 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word32 CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong Word64 where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt Word64 CULLong where convertAttempt = boundedConversion (return . fromIntegral) -- Section 4 instance ConvertAttempt CChar CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CChar CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSChar CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUChar CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CShort CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUShort CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CInt CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CUInt CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLong CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULong CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CSize CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CWchar CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CLLong CULLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertAttempt CULLong CLLong where convertAttempt = boundedConversion (return . fromIntegral) -- Section 5 instance ConvertSuccess CFloat CDouble where convertSuccess = realToFrac instance ConvertSuccess CDouble CFloat where convertSuccess = realToFrac -- Section 6 instance ConvertSuccess CFloat Integer where convertSuccess = truncate instance ConvertSuccess Integer CFloat where convertSuccess = fromIntegral instance ConvertSuccess CDouble Integer where convertSuccess = truncate instance ConvertSuccess Integer CDouble where convertSuccess = fromIntegral -- Section 7 instance ConvertSuccess CChar Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CSChar Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CSChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CUChar Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CUChar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CShort Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CUShort Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CUShort where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CInt Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CUInt Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CUInt where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CLong Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CULong Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CULong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CSize Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CSize where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CWchar Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CWchar where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CLLong Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CLLong where convertAttempt = boundedConversion (return . fromIntegral) instance ConvertSuccess CULLong Integer where convertSuccess = fromIntegral instance ConvertAttempt Integer CULLong where convertAttempt = boundedConversion (return . fromIntegral) -- Section 8o instance ConvertAttempt CChar Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CChar where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CSChar Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CSChar where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CUChar Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CUChar where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CShort Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CShort where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CUShort Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CUShort where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CInt Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CInt where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CUInt Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CUInt where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CLong Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CLong where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CULong Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CULong where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CSize Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CSize where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CWchar Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CWchar where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CLLong Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CLLong where convertAttempt = boundedConversion (return . fromIntegral . fromEnum) instance ConvertAttempt CULLong Char where convertAttempt = boundedConversion (return . toEnum . fromIntegral) instance ConvertAttempt Char CULLong where convertAttempt = boundedConversion (return . fromIntegral . fromEnum)