User Tools

Site Tools


codesnippets:octets

Differences

This shows you the differences between two versions of the page.

Link to this comparison view

Both sides previous revisionPrevious revision
Next revision
Previous revision
codesnippets:octets [2021/04/20 13:06] f2b216codesnippets:octets [2025/10/08 00:48] (current) – external edit 127.0.0.1
Line 1: Line 1:
 ====== Octets ====== ====== Octets ======
-~~DISCUSSION~~ 
  
   * type ''class'' ''Octetable''   * type ''class'' ''Octetable''
-    * with type ''Octets'' +    * with type ''Octet'', and ''Octets'' 
-    * with instances for ''Word32'', ''Char'', ''Integer'', and ''Int'' +    * with instances for ''Word32'', ''Char'', ''Utf8Char'', ''Integer'', and ''Int'' 
-  * as an example +  * example
-  * with test execution+
     * code, of module ''Octetable'':<code Haskell>     * code, of module ''Octetable'':<code Haskell>
 {-# LANGUAGE BinaryLiterals #-} {-# LANGUAGE BinaryLiterals #-}
  
-module OctetsVertable+module Octetable
     (     (
-        OctetsVertable(..), +        Octetable(..),  
 +        Octet
         Octets,          Octets, 
         getOctets,          getOctets, 
         putOctets         putOctets
     ) where     ) where
 + 
 import qualified Data.Word as W import qualified Data.Word as W
 import qualified Data.Bits as Bts import qualified Data.Bits as Bts
Line 25: Line 24:
 import           Data.Bits ((.|.), (.&.)) import           Data.Bits ((.|.), (.&.))
  
-type Octets [W.Word8]+type Octet = W.Word8 
 + 
 +type Octets = [Octet]
  
 getOctets :: SysIo.Handle -> IO [W.Word8] getOctets :: SysIo.Handle -> IO [W.Word8]
Line 33: Line 34:
 putOctets hOut octs = BS.hPut hOut (BS.pack octs) putOctets hOut octs = BS.hPut hOut (BS.pack octs)
  
-class (Eq a, Show a) => OctetsVertable a where+class (Eq a, Show a) => Octetable a where
     toOctets :: a -> Octets     toOctets :: a -> Octets
     fromOctets :: Octets -> a     fromOctets :: Octets -> a
  
-instance OctetsVertable W.Word32 where+instance Octetable W.Word32 where
     toOctets w32 =      toOctets w32 = 
         [ fromIntegral (w32 `Bts.shiftR` 24)         [ fromIntegral (w32 `Bts.shiftR` 24)
Line 46: Line 47:
     fromOctets lw = foldl (\w32 w8 -> (w32 `Bts.shiftL` 8) + (fromIntegral w8))  0 lw     fromOctets lw = foldl (\w32 w8 -> (w32 `Bts.shiftL` 8) + (fromIntegral w8))  0 lw
  
-instance OctetsVertable Char where+instance Octetable Char where
     toOctets ch = (fIntegralToOctets . Chr.ord) ch     toOctets ch = (fIntegralToOctets . Chr.ord) ch
     fromOctets [] = '\0'     fromOctets [] = '\0'
Line 64: Line 65:
     deriving (Show, Eq)     deriving (Show, Eq)
  
-instance OctetsVertable Utf8Char where+instance Octetable Utf8Char where
     toOctets (OneByte w81) = [w81]     toOctets (OneByte w81) = [w81]
     toOctets (TwoBytes (w81,w82)) = [w81,w82]     toOctets (TwoBytes (w81,w82)) = [w81,w82]
Line 84: Line 85:
     fromOctets [] = (OneByte 0)     fromOctets [] = (OneByte 0)
  
-instance OctetsVertable Integer where+instance Octetable Integer where
     toOctets n = fIntegralToOctets n     toOctets n = fIntegralToOctets n
     fromOctets lw = integralFromOctets lw     fromOctets lw = integralFromOctets lw
  
-instance OctetsVertable Int where+instance Octetable Int where
     toOctets n = fIntegralToOctets n     toOctets n = fIntegralToOctets n
     fromOctets lw = integralFromOctets lw     fromOctets lw = integralFromOctets lw
Line 126: Line 127:
 </code> </code>
     * code, of module ''Main'', to test fromOctets and toOctets:<code Haskell>     * code, of module ''Main'', to test fromOctets and toOctets:<code Haskell>
-import qualified OctetsVertable as Oct+import qualified Octetable as Oct
  
 main :: IO () main :: IO ()
Line 167: Line 168:
         printExample (-hugeInteger)         printExample (-hugeInteger)
  
-printExample :: Oct.OctetsVertable a => a -> IO ()+printExample :: Oct.Octetable a => a -> IO ()
 printExample x =  printExample x = 
     let     let
Line 330: Line 331:
    -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001    -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
 </code> </code>
 +  * example, used with module FileSystem
 +    * code, of module ''Main'':<code Haskell>
 +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)
 +</code>
 +    * compiles, error and warning free, with compiler: GHC 8.10.4, using compiler option -Wall
 +    * input, file "a.txt":<code>
 +The quick brown fox jumps over the lazy dog.
 +</code>
 +    * executes, with output, first line stdout, second line stderr:<code>
 +The quick brown fox jumps over the lazy dog.
 +The_quick_brown_fox_jumps_over_the_lazy_dog.
 +</code>
 +    * executes, with output file "b.txt":<code>
 +The_quick_brown_fox_jumps_over_the_lazy_dog.
 +</code>
 +
 +
 +===== ✎ =====
 +~~DISCUSSION~~
codesnippets/octets.1618916777.txt.gz · Last modified: (external edit)

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