User Tools

Site Tools


codesnippets:codingconventions

Coding conventions

General rules

Line length

For source code, the line length is up to 80 characters, at the maximum.

  • Example:
    ------------------------------------------------------------------------------ |---...
     
    ...
     
    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.

  • Example:
    ------------------------------------------------------------------------------ |---...
     
    ...
    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

Indentation

  • four spaces
  • no tabs

Binding names in pattern and functions

  • lower camel case
  • if the result has a dedicated type or is restricted to type class
    • then the first word (prefix) may suggest a type or type class
    • continues with capital speaking names
      • e.g. Size, Replicate
      • Abbreviated names if to long
        • if available one of the suggested below
        • e.g. Pos for Position, Long for Longitude, In, Out
      • Combined as usually written
        • e.g. CursorPosition
      • If heavy abbreviation is needed without vowels
        • e.g. Cmp for Composition
  • otherwise
    • the first word is a uncapitalized speaking name or a lower camel case of composed speaking names
  • speaking names
    • noun (preferable to emphasise functional programming)
      • e.g. count/Count, matrix/Matrix, cursor/Cursor, length/Length
    • verbs
      • e.g. take/Take, replicate/Peplicate
  • dependent on better readability abreviations within a name may be also written in camel case e.g. Sql for SQL, Ascii for ASCII
  • examples:
    • takeEnd
    • niLength
    • length
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

Standard prefixes

  • Prefixes for may be used types, type classes, and pattern
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 ()
  • Prefixes may be used for commonly used modules
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

Custom prefixes

  • Prefixes for custom types, type classes, and pattern
    • custom prefixes are to be declared for each data type and type class
    • as in the example below
      • first bullet: * prefix: <prefix>
      • prefix in lower camel case
  • -- EOLMode
    -- | ...EOL (end of line) mode.
    {-| 
    * prefix: eol
    ...
    -}
    data EOLMode = 
        ...
  • example, in record syntax:
    • reolStream :: EOLMode, 
  • -- Code
    -- | ...
    {-| 
    * prefix: cd
    ...
    -}
    class Code cd where 
        ...
  • example, in a type constraint
    • fx :: Code cd => cd -> Char
      ...
  • Prefixes for custom modules
  • example:
    {-|
    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

Outline of a module

Module description

  • Haddock comment
  • contains
    • description (Description)
      • in way that it becomes a complete sentence when started with module name
        • like in the code below it translates to HPowerLib.ExportTest makes it easier to export functional tests that are not exported themselves.
    • copyright according to the example below
    • license
      • All rights reserved
      • GPLv3+, see also file 'LICENSE' and 'README.md'
    • maintainer (Maintainer), always an email address
    • stability (Stability), possible values:
      • unstable
      • experimental
      • provisional
      • stable
      • frozen
    • portability (Portability), possible values:
      • portable
      • non-portable (<reason>)
    • bullets
      • most important properties
    • expandable example
      • may be with output of example
      • ideally using doc test
        • example:
          -- >>> fact 5
          -- 120 
  • Example:
    {-|
    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
     
    ...
        @
    -}

GHC extensions and options

  • after module documentation
  • just listed one after the other
  • only if needed
  • Example:
    {-# LANGUAGE OverloadedStrings #-}
    {-# LANGUAGE GADTs #-}
    {-# LANGUAGE StandaloneDeriving #-}

Module declaration and export list

  • with export list
  • each exported item classified according to sections
  • Example:
    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

Sections

  • in order to get better overview
    • module's code is sectioned by comments, as shown below
    • two blank lines away from the text above
    • also to see whether the code is 80 character wide
  • sections may separate
    • type class by type class
      • with its functions, if they can be associated
    • type by type
      • with its instances, if they are in the module, and can be associated
      • with its functions, if they can be associated
  • example:
    --------------------------------------------------------------------------------
    --  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 =
    ...

Class declaration

  • example:
    -- 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'

Instance declaration

  • example:
    instance Format Prs.CharCode where
        display ( Prs.Utf8Code code ) = show ( Cd.chFromCode code ) ++ "(UTF-8)"
        display ( Prs.Iso1Code code ) = show ( Cd.chFromCode code ) ++ "(iso 8859-1)"
        display ( Prs.Win1Code code ) = show ( Cd.chFromCode code ) ++ "(Windows-1252)"

Data type declaration

  • it starts with the name in a single line comment, completed with
  • continues with multi line haddock comment
    • short description at the very top
    • blank line
    • bullets of properties, if neccessary

Sum type

  • example:
    -- 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

Product type

  • example:
    -- Geoposition
    -- | ...geocoordinates in degrees.
    {-| 
    * prefix: gps
    -}
    data Geoposition = 
        Geoposition
            -- | Latitude
            Double
            -- | Longitude
            Double
        deriving Show

Mixed type

  • example:
    -- | 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

Record syntax

  • indentation, line, comments and bracketing as in the example below
    • first line data <TypeName> =
    • second line <Constructor> {
    • haddock compliant comment, explaining the row below
    • record
      • bindings start with r to avoid shadowing when names are also used in pattern matching
      • the rest of the binding is as explained here
  • -- 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

In sums of algebraic types: "dangerous"

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.

  • example:
    someFunc :: IO ()
    someFunc = print crash
     
    data Unsafe = UnsafeA { rniA1 :: Int, rniA2 :: Int } | UnsafeB { rniB1 :: Int, rniB2 :: Int }
     
    unsafe = UnsafeB 23 34
     
    crash :: Int
    crash =  rniA1 unsafe
  • output:
    XYZ-exe: No match in record selector rniA1

Rather use the safe alternative below.

  • example:
    someFunc :: IO ()
    someFunc = print cannotCrash
     
    data Safe = SafeA Int Int | SafeB Int Int
     
    safe = SafeB 23 34
     
    cannotCrash :: Int
    cannotCrash =  first safe
        where
            first :: Safe -> Int
            first (SafeA ni1 _) = ni1
            first (SafeB ni1 _) = ni1
  • output:
    23

Function declaration

  • function name and description should focus on what it provides, not what it does
    • e.g. “'Stream' that is initialised” instead of “initialises a 'Stream'”
  • function name in single line comment, as idicated below
  • Haddock comment
    • starts with what the function is doing
    • does not necessarily have to be a complete sentence
    • goes right into it
    • refers to the resulting type (in single quotes)
    • later bullets, after blank line, may indicate properties
  • all rules for Binding names apply also to function name
  • -- 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

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/codingconventions.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