For source code, the line length is up to 80 characters, at the maximum.
------------------------------------------------------------------------------ |---... ... instance Formatting a => Formatting (Ds.Tree a) where format t = format' (Indent []) t where format' :: Formatting a => Indent -> (Ds.Tree a) -> String format' ind (Ds.Node s tl) = (format ind) ++ (format s) ++ "\n" ++ (prettyFormatTL' (pushIndent ind Continuing) tl) prettyFormatTL' :: Formatting a => Indent -> [Ds.Tree a] -> String prettyFormatTL' _ ([]) = "" prettyFormatTL' ind (tn:[]) = (format' (finishIndent ind) tn) prettyFormatTL' ind (tn:rtl) = (format' ind tn) ++ (prettyFormatTL' ind rtl)
For comments code, the line length is up to 160 characters, at the maximum.
------------------------------------------------------------------------------ |---... ... chSetInline :: [Char] -> Char -> Integer -> [Char] chSetInline [] chToSet nCol -- there is no character at all | nCol > 0 = ' ' : (chSetInline ([]) chToSet (nCol-1)) -- -> extend with blank, recursively | nCol == 0 = chToSet : [] -- -> add character | otherwise = [] -- -> leave as is (empty) chSetInline lch0@(ch:lch) chToSet nCol -- there is at least one character | nCol > 0 = ch : (chSetInline lch chToSet (nCol-1)) -- -> go to next character, recursively | nCol == 0 = chToSet : lch -- -> set character here | otherwise = lch0 -- -> leave as is
| Abbreviation | Meaning |
|---|---|
| Char | Character |
| In | Input |
| Out | Output |
| Pos | Position |
Example outFromCmpOut with function name using custom prefix out to indicate the resulting custom type:
outFromCmpOut :: (ComposableOutput usrSym) -> (Output usrSym)
Example symTree as matched pattern name using custom prefix sym to indicate the custom type:
outFromCmpOut (CmpOut (CmpValid symTree _ _) _) = Valid symTree
Example lErr as matched name using standard prefix l plus err to indicate the custom list type combined with custom prefix err:
outFromCmpOut (CmpOut (CmpInvalid lerr) _) = Invalid lerr
| Type or type class | Prefix | Examples |
|---|---|---|
a | x | xMax for a maximum value of an arbitrary type |
Num ⇒ | n | nRowPos for the line number of a row |
Int | n or nj | njExp for the exponent in a power operation |
Integer | n or ni | niLength to provide the length of a list |
Double | n or nd | ndDegreesCentigrade to indicate a temperature |
Float | n or nf | nfVolt to indicate a voltage |
Bool | is, do, does, are, has | isHead, doAllOutFileExist, areAllOpen, hasBeenUpdated |
[<a>] | l<a> | lerr to match with list of elements of a data type that is defined with prefix err |
(<a>,<b>) | tpl, tpl2 | tpl2 just a tuple with two elements |
(<a>,<b>,<3>) | tpl, tpl3 | tpl just a tuple |
(<elem>:lr<elem>) | none, and lr | (ch:lrch) for a list of Char |
l<elem>@(<elem>:lr<elem>) | l, none, and lr | lch@(ch:lrch) for a list of Char |
Char | ch | chRead for a charater to read |
String, [Char] | s, lch | sStream record name to get a string from stream |
Maybe <a> | m<a> | mch for a binding of type Maybe Char |
Either <e> <n> | e<n> | en or eni for a binding of type Either String Integer |
IO | io | io for a function result type IO () or ios for a function result type IO String |
Word8 | w8 | w8FromChar converts char to a Word8 value |
Word16 | w16 | |
Word32 | w32 | |
Word64 | w64 | |
*→* | f | fConvert to name a function as parameter or fioWrite for a function that writes to IO () |
| Module | Prefix | Import directive |
|---|---|---|
| Control.Exception.Base | Ex | import qualified Control.Exception.Base as Ex |
| Data.Bits | Bts | import qualified Data.Bits as Bts |
| Data.ByteString | BS | import qualified Data.ByteString as BS |
| Data.Char | Chr | import qualified Data.Char as Chr |
| Data.List | Lst | import qualified Data.List as Lst |
| Data.Time | Tm | import qualified Data.Time as Tm |
| Data.Word | Wrd | import qualified Data.Word as Wrd |
| Debug.Trace | Dbg | import qualified Debug.Trace as Dbg |
| Numeric | Nm | import qualified Numeric as Nm |
| System.Directory | Dir | import qualified System.Directory as Dir |
| System.IO | SIo | import qualified System.IO as SIo |
* prefix: <prefix>-- EOLMode -- | ...EOL (end of line) mode. {-| * prefix: eol ... -} data EOLMode = ...
reolStream :: EOLMode,
-- Code -- | ... {-| * prefix: cd ... -} class Code cd where ...
fx :: Code cd => cd -> Char ...
{-|
Description : supports transformation from multiple system stream inputs like files and stdin to multiple system output stream like files, stdout and stderr.
Copyright : (c) Jörg K.-H. W. Brüggmann, 2021-2024
License : proprietary, to be dual licensed
Maintainer : info@joerg-brueggmann.de
Stability : experimental
Portability : POSIX
...provides support for transformation from multiple system stream inputs like files and stdin to multiple system output stream like files, stdout and stderr.
* suggested prefix: 'Mio'
import qualified MultiOctetStreamIO as Mio
Description)HPowerLib.ExportTest makes it easier to export functional tests that are not exported themselves.Maintainer), always an email addressStability), possible values:Portability), possible values:-- >>> fact 5 -- 120
{-|
Description : makes it easier to export functional tests that are not exported themselves.
Copyright : (c) Jörg K.-H. W. Brüggmann, 2021-2024
License : All rights reserved
Maintainer : info@joerg-brueggmann.de
Stability : experimental
Portability : POSIX
* makes it easier to export functional tests that are not exported themselves.
* suggested prefix: __/Exp/__
* See also module HPowerLib.ImportTests, which supports import of the tests into the test framework Tasty.
==== __Example code to export tests__
@
...
module HPowerLib.Parser
(
...
, ...
, testGroup_parseComposable
) where
...
@
-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE StandaloneDeriving #-}
module HPowerLib.BitSeqContext ( -- * data types and its instances Context( .. ) , Position( .. ) , LineNumber , ColumnNumber , BitPosition -- * functions regarding 'Context' , initFromOctets , initFromBits , startPositionMemory , position , isEOS -- * functions to test at context position -- ** class 'TestableEncoding' to test encodings , TestableEncoding( .. ) -- * functions to test number of available bits , testAvailableBits -- * functions to test particular sequences , testCode , testBits ) where
-------------------------------------------------------------------------------- -- data types and its instances data Context = Context { rBits :: Bits.Sequence, rPositionMemory :: ( Position, Maybe Char ) } deriving ( Eq, Show ) ... -------------------------------------------------------------------------------- -- functions regarding 'Context' initFromOctets :: Oct.Octets -> Context initFromOctets octets = Context ( Bits.Sequence Bits.NoSubOctet octets Bits.NoSubOctet ) startPositionMemory ... -------------------------------------------------------------------------------- -- functions to test at context position -------------------------------------------------------------------------------- -- class 'TestableEncoding' to test encodings class Cd.Code code => TestableEncoding code where decodeTest :: Context -> ( Maybe code, Context ) instance TestableEncoding Cd.CharUtf8 where decodeTest :: Context -> (Maybe Cd.CharUtf8, Context) decodeTest context0@( Context _ pos0 ) = ... instance TestableEncoding Cd.CharIso1 where decodeTest context0 = ... instance TestableEncoding Cd.CharWin1 where decodeTest context0 = ... nextOctet :: Context -> ( Maybe Oct.Octet, Context ) nextOctet context = ... -------------------------------------------------------------------------------- -- functions to test number of available bits -------------------------------------------------------------------------------- -- function 'testAvailableBits' testAvailableBits :: Context -> Integer -> ( Maybe Bits.Sequence, Context ) testAvailableBits context0@( Context bits0 ( pos0, _ ) ) numberOfBits = ... -------------------------------------------------------------------------------- -- functions to test particular sequences -------------------------------------------------------------------------------- -- function 'testCode' testCode :: Cd.Code cd => Context -> cd -> ( Bool, Context ) testCode context code = ( contextBits == charBits, nextContext ) ... nextCode :: Cd.Code cd => Context -> cd -> ( Bits.Sequence, Bits.Sequence, Context ) nextCode ( Context bits pos ) code = ... nextPositionMemoryFromChar :: ( Position, Maybe Char ) -> Char -> Integer -> ( Position, Maybe Char ) nextPositionMemoryFromChar ( BitPosition bitPosition0, _ ) _ nBits = ( BitPosition ( bitPosition0 + nBits ), Nothing ) nextPositionMemoryFromChar ( CharAndBitPosition lineNumber0 columnNumber0 bitPosition0, mch0 ) ch nBits = ... -------------------------------------------------------------------------------- -- function 'testBits' testBits :: Context -> Bits.Sequence -> ( Bool, Context ) testBits context bitsToTest = ...
-- HUnit -- | ...capability to compare the expected value with the actual one, -- | and to display the difference if there is one. {-| -} class ( Show cmp ) => HUnit cmp where -- equals {- | ...compares the expected value with the actual one. * result 'True' if both values are equal, otherwise 'False' -} equals :: cmp -- ^ actual value -> cmp -- ^ expected value -> Bool -- ^ 'True' when actual value and expected value is considered equal, otherwise 'False'
…-- EOLMode -- | ...EOL (end of line) mode. {-| * prefix: eol * to determine row * to control generation of new lines -} data EOLMode = -- | for Windows, a new line is "\r\n", and "\x0d\x0A", respectively WindowsEOL -- | for Unix, a new line is "\n", and "\x0A", respectively | UnixEOL -- for macOS, anew line is "\r", and "\x0d", respectively | MacEOL deriving Show
-- | parser output that supports composition of all syntax elements including selections, sequences, repetitions, and so on data ComposableOutput = -- | previous input was valid or not yet parsed CmpValid -- | remaining input InputStream -- | symbol tree SymTree -- | lErrHintCmp [ErrorTree] -- | previous input was invalid | CmpInvalid -- | remaining input InputStream -- | error tree ErrorTree deriving Show
data <TypeName> =<Constructor> {r to avoid shadowing when names are also used in pattern matching-- Stream -- | ...string as input stream. {- | * prefix: st * that starts at column 1, row 1 * going from left to right, and for each new line from top to bottom -} data Stream = Stream { -- | controls the recognition of line breaks, which is important to calculate text positions ('Pos') reolStream :: EOLMode, -- | keeps the rest of the stream if used by 'strFwdToNextChar' rsStream :: String, -- | keeps the current position of the stream rposStream :: Pos } deriving Show
NOTE: Usage of record syntax in sums of algebraic types is “dangerous”. They can lead to runtime errors. Don't use them! See the example below - went wrong.
XYZ-exe: No match in record selector rniA1
Rather use the safe alternative below.
23
-- stInitalStream {-| ...'Stream' that is initialised. * from end of line mode ('EOLMode'), and content of the stream ('String') * resets posStream (:: Pos) to initial position -} stInitalStream :: EOLMode -- ^ end of line mode -> String -- ^ content of the stream -> Stream -- ^ the initialised stream stInitalStream eolMode s = Stream eolMode s initPos