User Tools

Site Tools


codesnippets:octets

Octets

  • type class Octetable
    • with type Octet, and Octets
    • with instances for Word32, Char, Utf8Char, Integer, and Int
  • example
    • code, of module Octetable:
      {-# LANGUAGE BinaryLiterals #-}
       
      module Octetable
          (
              Octetable(..), 
              Octet, 
              Octets, 
              getOctets, 
              putOctets
          ) where
       
      import qualified Data.Word as W
      import qualified Data.Bits as Bts
      import qualified Data.Char as Chr
      import qualified System.IO as SysIo
      import qualified Data.ByteString as BS
      import           Data.Bits ((.|.), (.&.))
       
      type Octet = W.Word8
       
      type Octets = [Octet]
       
      getOctets :: SysIo.Handle -> IO [W.Word8]
      getOctets = (fmap BS.unpack) . BS.hGetContents
       
      putOctets :: SysIo.Handle -> [W.Word8] -> IO ()
      putOctets hOut octs = BS.hPut hOut (BS.pack octs)
       
      class (Eq a, Show a) => Octetable a where
          toOctets :: a -> Octets
          fromOctets :: Octets -> a
       
      instance Octetable W.Word32 where
          toOctets w32 = 
              [ fromIntegral (w32 `Bts.shiftR` 24)
              , fromIntegral (w32 `Bts.shiftR` 16)
              , fromIntegral (w32 `Bts.shiftR` 8)
              , fromIntegral w32
              ]
          fromOctets lw = foldl (\w32 w8 -> (w32 `Bts.shiftL` 8) + (fromIntegral w8))  0 lw
       
      instance Octetable Char where
          toOctets ch = (fIntegralToOctets . Chr.ord) ch
          fromOctets [] = '\0'
          fromOctets lw = Chr.chr (integralFromOctets lw)
       
      {-| UTF-8 character
       
      * prefix: cu8
      * represent on UTF-8 character
      * keeps one, two, three or four character
      -}
      data Utf8Char = 
            OneByte (W.Word8)
          | TwoBytes (W.Word8, W.Word8)
          | ThreeBytes (W.Word8, W.Word8, W.Word8)
          | FourBytes (W.Word8, W.Word8, W.Word8, W.Word8)
          deriving (Show, Eq)
       
      instance Octetable Utf8Char where
          toOctets (OneByte w81) = [w81]
          toOctets (TwoBytes (w81,w82)) = [w81,w82]
          toOctets (ThreeBytes (w81,w82,w83)) = [w81,w82,w83]
          toOctets (FourBytes (w81,w82,w83,w84)) = [w81,w82,w83,w84]
          fromOctets (w81:w82:w83:w84:_)
              | (w81 .&. 0b10000000) == 0b00000000 = OneByte w81
              | (w81 .&. 0b11100000) == 0b11000000 = TwoBytes (w81,w82)
              | (w81 .&. 0b11110000) == 0b11100000 = ThreeBytes (w81,w82,w83)
              | otherwise                          = FourBytes (w81,w82,w83,w84)
          fromOctets (w81:w82:w83:[])
              | (w81 .&. 0b10000000) == 0b00000000 = OneByte w81
              | (w81 .&. 0b11100000) == 0b11000000 = TwoBytes (w81,w82)
              | otherwise                          = ThreeBytes (w81,w82,w83)
          fromOctets (w81:w82:[])
              | (w81 .&. 0b10000000) == 0b00000000 = OneByte w81
              | otherwise                          = TwoBytes (w81,w82)
          fromOctets (w81:[]) = OneByte w81
          fromOctets [] = (OneByte 0)
       
      instance Octetable Integer where
          toOctets n = fIntegralToOctets n
          fromOctets lw = integralFromOctets lw
       
      instance Octetable Int where
          toOctets n = fIntegralToOctets n
          fromOctets lw = integralFromOctets lw
       
      fIntegralToOctets :: (Integral a) => a -> Octets
      fIntegralToOctets n 
          | n > 0 = 
              let (_, lw8) = fIntegralToOctets' (n, [])
              in keepOctetsPositive lw8
          | n < 0 =
              let (_, lw8) = fIntegralToOctets' ((0 - n) - 1, [])
              in (keepOctetsNegative . (fmap Bts.complement)) lw8
          | otherwise = []
       
      fIntegralToOctets' :: (Integral a) => (a,Octets) -> (a,Octets)
      fIntegralToOctets' tpl@(0,lw) = 
          tpl
      fIntegralToOctets' (n,lw) = 
          fIntegralToOctets' (n `div` 256, (fromIntegral (n `mod` 256)) : lw)
       
      keepOctetsPositive :: Octets -> Octets
      keepOctetsPositive [] = []
      keepOctetsPositive lw8
          | Bts.testBit (head lw8) 7 = 0 : lw8 -- highest bit is set, hence would be interpreted as negative by integralFromOctets -> append 0x00 to keep positive
          | otherwise                =     lw8 -- highest bit is NOT set, hence positive -> keep as is
       
      keepOctetsNegative :: Octets -> Octets
      keepOctetsNegative [] = []
      keepOctetsNegative lw8
          | Bts.testBit (head lw8) 7 =        lw8 -- highest bit is set, hence would be interpreted as negative by integralFromOctets -> append 0x00 to keep positive
          | otherwise                = 0xff : lw8 -- highest bit is NOT set, hence positive -> keep as is
       
      integralFromOctets :: (Integral a) => Octets -> a
      integralFromOctets lw8
          | Bts.testBit (head lw8) 7 = (negate . (+1) . integralFromOctets . (fmap Bts.complement)) lw8
          | otherwise                = foldl (\n w8 -> (n * 256) + (fromIntegral w8))  0 lw8
    • code, of module Main, to test fromOctets and toOctets:
      import qualified Octetable as Oct
       
      main :: IO ()
      main = 
          do
              printExample 'a'
              printExample 'z'
              printExample 'A'
              printExample 'Z'
              printExample '0'
              printExample '9'
              printExample '禅'
              printExample (127 :: Int)
              printExample (128 :: Int)
              printExample (255 :: Int)
              printExample (256 :: Int)
              printExample (257 :: Int)
              printExample (258 :: Int)
              printExample (-127 :: Int)
              printExample (-128 :: Int)
              printExample (-129 :: Int)
              printExample (-130 :: Int)
              printExample (-255 :: Int)
              printExample (-256 :: Int)
              printExample (-257 :: Int)
              printExample (-258 :: Int)
              printExample (127 :: Integer)
              printExample (128 :: Integer)
              printExample (255 :: Integer)
              printExample (256 :: Integer)
              printExample (257 :: Integer)
              printExample (258 :: Integer)
              printExample (-127 :: Integer)
              printExample (-128 :: Integer)
              printExample (-255 :: Integer)
              printExample (-256 :: Integer)
              printExample (-257 :: Integer)
              printExample (-258 :: Integer)
              printExample hugeInteger
              printExample (-hugeInteger)
       
      printExample :: Oct.Octetable a => a -> IO ()
      printExample x = 
          let
              octX :: Oct.Octets
              octX = Oct.toOctets x
              x' = Oct.fromOctets octX
          in
              do
                  if (x /= x')
                      then
                          putStrLn "Error: x is not equal x'"
                      else
                          putStrLn "OK"
                  putStrLn $ "   " ++ (show x)
                  putStrLn $ "   " ++ (show octX)
                  putStrLn $ "   " ++ (show x')
       
      hugeInteger :: Integer
      hugeInteger = 31 ^ (1000 :: Int)
    • compiles, error and warning free, with compiler: GHC 8.10.4, using compiler option -Wall
    • executes, with output:
      OK
         'a'
         [97]
         'a'
      OK
         'z'
         [122]
         'z'
      OK
         'A'
         [65]
         'A'
      OK
         'Z'
         [90]
         'Z'
      OK
         '0'
         [48]
         '0'
      OK
         '9'
         [57]
         '9'
      OK
         '\31109'
         [121,133]
         '\31109'
      OK
         127
         [127]
         127
      OK
         128
         [0,128]
         128
      OK
         255
         [0,255]
         255
      OK
         256
         [1,0]
         256
      OK
         257
         [1,1]
         257
      OK
         258
         [1,2]
         258
      OK
         -127
         [129]
         -127
      OK
         -128
         [128]
         -128
      OK
         -129
         [255,127]
         -129
      OK
         -130
         [255,126]
         -130
      OK
         -255
         [255,1]
         -255
      OK
         -256
         [255,0]
         -256
      OK
         -257
         [254,255]
         -257
      OK
         -258
         [254,254]
         -258
      OK
         127
         [127]
         127
      OK
         128
         [0,128]
         128
      OK
         255
         [0,255]
         255
      OK
         256
         [1,0]
         256
      OK
         257
         [1,1]
         257
      OK
         258
         [1,2]
         258
      OK
         -127
         [129]
         -127
      OK
         -128
         [128]
         -128
      OK
         -255
         [255,1]
         -255
      OK
         -256
         [255,0]
         -256
      OK
         -257
         [254,255]
         -257
      OK
         -258
         [254,254]
         -258
      OK
         2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
         [4,149,67,65,167,171,197,84,43,162,252,95,56,177,166,129,96,183,154,213,154,18,207,221,0,24,120,56,207,187,186,22,231,30,251,149,224,155,142,17,207,38,241,206,35,169,131,176,13,53,10,109,111,17,228,182,148,81,170,116,211,195,239,32,58,235,93,194,66,253,218,226,121,190,3,200,233,116,193,9,229,50,179,177,189,6,28,166,55,191,165,48,184,13,122,195,5,8,110,125,38,187,215,113,16,60,205,109,173,17,222,220,165,94,76,33,235,165,112,217,168,132,158,190,22,217,67,82,140,3,102,177,221,81,251,106,56,124,186,104,241,15,101,129,136,57,191,182,15,3,124,116,252,183,148,161,29,140,28,34,121,183,153,148,155,139,165,163,120,128,2,86,193,119,49,79,168,192,149,152,193,67,15,171,13,201,25,2,118,247,200,67,112,8,69,57,75,15,215,202,30,25,187,167,78,56,109,75,246,38,128,8,65,56,27,214,231,28,35,234,80,168,28,36,66,89,164,107,207,16,215,30,2,47,230,115,84,50,23,9,237,158,171,103,45,209,243,32,124,33,107,107,7,61,221,122,165,127,132,253,69,89,79,192,243,198,211,176,100,222,217,174,137,175,145,130,94,40,49,239,151,101,218,168,139,40,109,34,60,193,205,238,96,94,10,236,146,196,251,189,59,237,207,133,115,49,171,114,179,186,40,131,22,186,234,165,26,110,209,174,173,209,35,239,197,171,37,233,14,183,133,87,180,74,186,18,10,113,216,78,152,43,140,176,130,17,182,134,236,33,208,14,113,138,105,126,42,1,53,229,235,8,103,41,252,89,8,225,32,47,179,214,240,200,191,224,97,35,139,218,218,144,228,134,5,62,212,6,96,12,86,174,121,214,147,101,16,55,36,22,169,162,203,121,202,122,163,209,197,122,131,116,248,31,209,233,245,73,97,60,5,33,176,150,245,83,204,107,208,177,66,37,128,78,128,152,210,87,107,38,222,83,93,31,133,64,141,203,135,13,204,86,156,147,32,88,46,144,197,185,80,156,167,54,133,180,194,178,167,236,97,72,54,238,22,112,172,127,12,144,6,254,171,69,88,187,51,185,91,191,100,230,83,88,8,89,192,109,154,66,32,176,172,155,110,225,100,182,71,173,219,229,14,162,173,45,4,216,125,37,252,178,0,210,144,246,223,146,118,254,204,36,196,225,45,219,134,32,240,254,160,107,236,99,187,209,57,18,0,176,133,225,115,247,11,125,23,151,6,17,149,255,37,64,96,169,134,210,57,125,160,162,178,85,81,18,118,204,183,193,61,149,195,226,245,93,163,186,155,88,231,61,19,62,235,214,18,203,130,183,69,196,249,106,222,172,114,231,21,152,221,84,131,3,113,217,230,112,51,1]
         2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
      OK
         -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
         [251,106,188,190,88,84,58,171,212,93,3,160,199,78,89,126,159,72,101,42,101,237,48,34,255,231,135,199,48,68,69,233,24,225,4,106,31,100,113,238,48,217,14,49,220,86,124,79,242,202,245,146,144,238,27,73,107,174,85,139,44,60,16,223,197,20,162,61,189,2,37,29,134,65,252,55,22,139,62,246,26,205,76,78,66,249,227,89,200,64,90,207,71,242,133,60,250,247,145,130,217,68,40,142,239,195,50,146,82,238,33,35,90,161,179,222,20,90,143,38,87,123,97,65,233,38,188,173,115,252,153,78,34,174,4,149,199,131,69,151,14,240,154,126,119,198,64,73,240,252,131,139,3,72,107,94,226,115,227,221,134,72,102,107,100,116,90,92,135,127,253,169,62,136,206,176,87,63,106,103,62,188,240,84,242,54,230,253,137,8,55,188,143,247,186,198,180,240,40,53,225,230,68,88,177,199,146,180,9,217,127,247,190,199,228,41,24,227,220,21,175,87,227,219,189,166,91,148,48,239,40,225,253,208,25,140,171,205,232,246,18,97,84,152,210,46,12,223,131,222,148,148,248,194,34,133,90,128,123,2,186,166,176,63,12,57,44,79,155,33,38,81,118,80,110,125,161,215,206,16,104,154,37,87,116,215,146,221,195,62,50,17,159,161,245,19,109,59,4,66,196,18,48,122,140,206,84,141,76,69,215,124,233,69,21,90,229,145,46,81,82,46,220,16,58,84,218,22,241,72,122,168,75,181,69,237,245,142,39,177,103,212,115,79,125,238,73,121,19,222,47,241,142,117,150,129,213,254,202,26,20,247,152,214,3,166,247,30,223,208,76,41,15,55,64,31,158,220,116,37,37,111,27,121,250,193,43,249,159,243,169,81,134,41,108,154,239,200,219,233,86,93,52,134,53,133,92,46,58,133,124,139,7,224,46,22,10,182,158,195,250,222,79,105,10,172,51,148,47,78,189,218,127,177,127,103,45,168,148,217,33,172,162,224,122,191,114,52,120,242,51,169,99,108,223,167,209,111,58,70,175,99,88,201,122,75,61,77,88,19,158,183,201,17,233,143,83,128,243,111,249,1,84,186,167,68,204,70,164,64,155,25,172,167,247,166,63,146,101,189,223,79,83,100,145,30,155,73,184,82,36,26,241,93,82,210,251,39,130,218,3,77,255,45,111,9,32,109,137,1,51,219,59,30,210,36,121,223,15,1,95,148,19,156,68,46,198,237,255,79,122,30,140,8,244,130,232,104,249,238,106,0,218,191,159,86,121,45,198,130,95,93,77,170,174,237,137,51,72,62,194,106,60,29,10,162,92,69,100,167,24,194,236,193,20,41,237,52,125,72,186,59,6,149,33,83,141,24,234,103,34,171,124,252,142,38,25,143,204,255]
         -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
  • example, used with module FileSystem
    • code, of module Main:
      import qualified FileSystem as FS
      import qualified System.IO as SysIo
      import qualified Octetable as Oct
      import qualified Data.Char as Chr
       
      main :: IO ()
      main = 
              FS.processData
                  (FS.DataReader (FS.FileInp ".\\test\\a.txt") (hGetNReplace  octBlank octUnderscore))
                  [
                      FS.DataWriter (FS.FileOut ".\\test\\b.txt") Oct.putOctets, 
                      FS.DataWriter FS.StdOut (hReplaceNPut octUnderscore octBlank), 
                      FS.DataWriter FS.StdErr Oct.putOctets
                  ]
       
      octBlank :: Oct.Octet
      octBlank = ((fromIntegral . Chr.ord) ' ')
       
      octUnderscore :: Oct.Octet
      octUnderscore = ((fromIntegral . Chr.ord) '_')
       
      hGetNReplace :: Oct.Octet -> Oct.Octet -> SysIo.Handle -> IO Oct.Octets
      hGetNReplace a b h = 
          do
              s <- Oct.getOctets h
              return (fmap (\x -> if x == a then b else x) s)
       
      hReplaceNPut :: Oct.Octet -> Oct.Octet -> SysIo.Handle -> Oct.Octets -> IO ()
      hReplaceNPut a b h s = Oct.putOctets h (fmap (\x -> if x == a then b else x) s)
    • compiles, error and warning free, with compiler: GHC 8.10.4, using compiler option -Wall
    • input, file “a.txt”:
      The quick brown fox jumps over the lazy dog.
    • executes, with output, first line stdout, second line stderr:
      The quick brown fox jumps over the lazy dog.
      The_quick_brown_fox_jumps_over_the_lazy_dog.
    • executes, with output file “b.txt”:
      The_quick_brown_fox_jumps_over_the_lazy_dog.

This website uses cookies. By using the website, you agree with storing cookies on your computer. Also you acknowledge that you have read and understand our Privacy Policy. If you do not agree leave the website.More information about cookies
You could leave a comment if you were logged in.
codesnippets/octets.txt · Last modified: by 127.0.0.1

Except where otherwise noted, content on this wiki is licensed under the following license: CC0 1.0 Universal
CC0 1.0 Universal Donate Powered by PHP Valid HTML5 Valid CSS Driven by DokuWiki