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/22 12:51] 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'', ''Utf8Char'', ''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 #-}
Line 129: 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 170: 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 333: Line 331:
    -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001    -2299819935653645082894452792461391785316838819634854499582649773064497657338657176722815066047012042970707985364005424194851744592589349276289737892620644753316103773332601282923749730891215409124729751179101572661546264659399035941959433049031612193674931427369793499974748103941854396793949658196683481215335075331190973321382630193047486040570710476538476805752828595396636100262237982462365668148474400831819729686520016831142034423035989126884829798702369001522511603033547628403647714677841344568950917375570064143430404597420770773439867113060747581916408770350655859231601822693794335340024703291277047383009545489812044665828872069515086161470043404212964143599392663515383545253369964683097804303493196001346972875807092655666775774755153966987089557598493216241473998446786105682286003208993649406238722161069532282900618217219492148604518557515368241354830826940556257234738134897451091801018568418762856248825737587480173029024436395984067723608292575876261695468817805283649009112581009389828573386359739601662047431757990274166003464056141974382728940618484203465938650973604530113187308736921734424683365243118100998126580691247572322148932020120247574456331416847236654458804902164954387120540919072050362384906504090722699288613319388277341509353032905698955788548406169450791248838342383275106318381042808878054409211203094805561198699897359477344778815969939545770630197346441568662820604992751625101251259774130554173720020589092927339037514717894135290456906563866080001
 </code> </code>
-    * code, of module ''Main'', used with module FileSystem:<code Haskell> +  * example, used with module FileSystem 
-{-# LANGUAGE BinaryLiterals #-} +    * code, of module ''Main'':<code Haskell> 
- +import qualified FileSystem as FS 
-module Octetable +import qualified System.IO as SysIo 
-    ( +import qualified Octetable as Oct
-        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 Data.Char as Chr
-import qualified System.IO as SysIo 
-import qualified Data.ByteString as BS 
-import           Data.Bits ((.|.), (.&.)) 
  
-type Octet W.Word8+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 
 +            ]
  
-type Octets = [Octet]+octBlank :: Oct.Octet 
 +octBlank = ((fromIntegral . Chr.ord) ' ')
  
-getOctets :: SysIo.Handle -> IO [W.Word8] +octUnderscore :: Oct.Octet 
-getOctets = (fmap BS.unpack) BS.hGetContents+octUnderscore = ((fromIntegral Chr.ord) '_')
  
-putOctets :: SysIo.Handle -> [W.Word8] -> IO () +hGetNReplace :: Oct.Octet -> Oct.Octet -> SysIo.Handle -> IO Oct.Octets 
-putOctets hOut octs BS.hPut hOut (BS.pack octs)+hGetNReplace a b h  
 +    do 
 +        s <- Oct.getOctets h 
 +        return (fmap (\x -> if x == a then b else x) s)
  
-class (Eq a, Show a) => Octetable where +hReplaceNPut :: Oct.Octet -> Oct.Octet -> SysIo.Handle -> Oct.Octets -> IO () 
-    toOctets :-> Octets +hReplaceNPut a b h s Oct.putOctets h (fmap (\x -if x == then b else x) s) 
-    fromOctets :: Octets -a+</code> 
 +    * compiles, error and warning free, with compilerGHC 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>
  
-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> 
  
 +===== ✎ =====
 +~~DISCUSSION~~
codesnippets/octets.1619088711.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