Why not ?

Why ?

Elevator pitch to management

Haskell reduces the total cost of ownership

  • by lowering the probability of defects,
  • easing the maintenance burden,
  • allowing to safely quickly adapt and
  • streamlining the on boarding of developers.

Sales pitch to be taken with a pinch of salt

Elevator pitch to developers

Haskell reduces stress and increases enjoyment.

  • Uncertainty and lack of control makes working with systems more stressful and
  • Haskell provides tools
    • to help you be more certain and
    • give you more control.
  • These same tools allow you to refactor without dread,
    • improving those systems, and
    • who does not enjoy making things better.

Sales pitch to be taken with a pinch of salt

More seriously

Haskell/GHC is

  • a statically typed,
  • purely functional and
  • lazy language, with
  • a sound advanced type system, a
  • powerful optimizing compiler,
  • strong support from academia, but
  • also used in industry, with a excellent support for
  • concurrency and parallelism

concurrency and parallelism is supported by

  • green threads,
  • software transactional memory,
  • primitives and libraries for parallelizing computations, and
  • a statically typed purely functional type system

GHC often optimizes high level functional code to tight loops using

  • aggressive type safe inlining,
  • stream and list fusion, and
  • getting rid of intermediate data structures.

What makes Haskell’s type system different or better than some other languages?

Summed up nicely by this quote:

staticly-typed languages like C# have a type system that attempt to help you to write defensible code; type systems like Haskell’s attempt to help you write correct (i.e provable) code. The basic principle at work is moving things that can be checked into the compile stage; Haskell checks more things at compile time

Robert Harvey on Stack Exchange https://softwareengineering.stackexchange.com/questions/279316/what-exactly-makes-the-haskell-type-system-so-revered-vs-say-java#comment575125_279316

See J. Abrahamson’s nice expanded list of the type system features on Stack Exchange https://softwareengineering.stackexchange.com/a/279362

Every line of code we write is a potential bug.

Haskell allows us to

  • write less code,
  • check our assumptions at compile time,
  • be precise about how we limit our power and
  • reason about how we can compose our code.

Why Not ?

Haskell is scary

Its only scary because its different

Haskell is different

The fact that its different makes it worthwile to learn

Haskell requires you to be a superhuman programmer

No it actually helps you to be a mediocre programmer. You need to keep less in your head and the compiler gives you training wheels.

All those operators make my eyes bleed

So normal language has punctuation for constructs that are very commonly used.

Haskell is the same, the operators you see are like punctation. They are also usually universally applicable, so instead of learning N API’s you learn a far lower set of operators.

We cannot cover everything

Haskell’s syntax is different

so lets start by going through its basics and then

work through a very typical piece of code,

the rest we will have todo another day.

Haskell Syntax Basics

Everything is either a declaration or an expression.

Declare function f taking two arguments returning their sum

f a b = a + b

Call f with 1 and 2

result_of_calling_f = f 1 2

Capitals are for type names and data conctructors

Specifying f’s type

f :: Int -> Int -> Int
f a b = a + b

Partially apply f to get g which adds 1

g :: Int -> Int
g = f 1
Variables can be used at the type level too giving you parametric polymorphism.

id works for all types
Only one way it can be implemented

id :: a -> a
id a = a

This is a compiler error
How do you add any 2 things

h :: a -> a -> a
h a b = a + b

Constrain h to types which are Num like
Num is a type class

h :: Num a => a -> a -> a
h a b = a + b

Type classes are not OOP, rather they identify a set of properties or attributes of a type.
Types are introduced by the data keyword

MyBool can be MyTrue or MyFalse
Type classes for free

data MyBool = MyTrue | MyFalse
  deriving (Show, Read, Eq, Ord, Enum, Bounded)

Types can be parameterized
constructors can take values

data AnIntOrSomething a =
  AnInt Int | OrSomething a

Constructors can use record syntax

data V2 a = V2 {x :: a, y :: a}
  deriving (Show, Read, Eq, Ord)

A V2 Int with x set to 1 and y set to 2

aV2Int :: V2 Int
aV2Int = V2 {x = 1, y = 2}

Record accessor and update
Copies input replacing x

incX :: Num a => V2 a -> V2 a
incX v2 = v2{x = x v2 + 1}
At the term level functions may have multiple declarations each either pattern matching and or applying guards

Function is True if the argument is either AnInt 5 or OrSomething v2 where x v2 == y v2
_ is the wild card pattern matching

is_it_5_or_a_V2_with_x_equal_to_y :: Eq a => AnIntOrSomething (V2 a) -> Bool
is_it_5_or_a_V2_with_x_equal_to_y (AnInt 5) = True
is_it_5_or_a_V2_with_x_equal_to_y (OrSomething (V2 {x=x, y=y})) | x == y = True
is_it_5_or_a_V2_with_x_equal_to_y _ = False

The case expression is an alternative
Result after -> instead of =
Same as function above

using_case ::
  Eq a => AnIntOrSomething (V2 a) -> Bool
using_case a =
  case a of
    AnInt 5 -> True
    OrSomething (V2 {x=x, y=y}) | x == y -> True
     _ -> False

At the non top level expressions can be bound to names with the let expression.

incY :: Num a => V2 a -> V2 a
incY v2 =
  let yOld = y v2
      one = 1
      yNew = one + yOld
  in v2{y=yNew}

When declaring functions a where block can be used instead. Syntatic sugar for a let expression.

incYWhere :: Num a => V2 a -> V2 a
incYWhere v2 = v2{y=yNew}
  where
    yOld = y v2
    one = 1
    yNew = one + yOld
Operators like + or || are not special but normal functions, only difference is they are infix by default.

Componentwise addition for V2 a constrained to Num

(^+^) :: Num a => V2 a -> V2 a -> V2 a
lhs ^+^ rhs = V2 { x = x lhs + x rhs
                 , y = y lhs + y rhs}

Operators have precedence 0 to 9
Function application is level 10

infixl 6 ^+^

Use operator ^+^ prefix

addV2Prefix :: Num a => V2 a -> V2 a -> V2 a
addV2Prefix lhs rhs = (^+^) lhs rhs

Use function addV2Prefix infix

addV2Infix :: Num a => V2 a -> V2 a -> V2 a
addV2Infix lhs rhs =  lhs `addV2Prefix` rhs
In order to run a program main has to be declared as type IO a
IO a is the type of things that can affect the outside world

The hello world program
putStrLn :: String -> IO ()

main = putStrLn "Hello world"

To chain IO a expressions use the bind operator >>=
(>>=) :: Monad m => m a -> (a -> m b) -> m b
Given a value m a and a function a -> m b remove the context m and feed to the function.

Echo line read from standard input
getLine :: IO String

main = getLine >>= putStrLn
To make working with >>= more convenient there are do blocks

Do blocks consist of several do statements
Do statements are expression of the type Monad m => m a
The results of the expressions can optionally be bound to names
Its only syntactic sugar desugaring to using >>=

main = do
  putStrLn ("Please enter your name")
  l <- getLine
  putStrLn ("Hello " ++ l)

Anonymous functions are introduced with \ ... ->

\a b -> a + b

The desugared version

main =
  putStrLn ("Please enter your name") >>=
    (\_ -> getLine >>= (\l -> putStrLn ("Hello " ++ l)))
Here are some more things that come up a lot

$ means eveluate whats on the right and give to the function on the left

-- So `f` is called with `a`, `b` and the
-- result of `c` called with `d`
f a b $ c d
($) :: (a -> b) -> a -> b

. means function composition, take the function on the right passing its output to the function on the left

(.) :: (b -> c) -> (a -> b) -> (a -> c)
-- psuedo code
f . c  === \x -> f (c x)

<$> is the infix version of fmap which is generalized map

-- psuedo code, for lists
f <$> c  === fmap f c === map f c

There is special syntax for tuples and lists

-- psuedo code
-- this is a list
[a,b,c] === a : b : c []
-- this is a tuple
(a,b,c)

A Monoid by any other name

What’s in a name? That which we call a rose, by any other name would smell as sweet.


Haskell does get a lot of negative press for the names it uses

If you are completely new to the software engineering world, would you intuitively know the meaning of the patterns visitor, strategy, command, model view controller and cake?

More importantly if you looked up their meanings would their definitions be precise and universal?

Haskell has this type class called Monoid, not knowing what it is you would look up its definition using hoogle and you would be informed that:

  • It is a type with an associative binary operation that has an identity,
  • the binary operator is called <> and
  • the identity is called mempty and
  • the following laws hold
    • x <> mempty = x right identity

    • mempty <> x = x left identity

    • x <> (y <> z) = (x <> y) <> z associativity

Ah this is just addition with + and 0, Addable is better name

But its also multiplication with * and 1, what to call it now ?

Ah its also string concatenation with ++ and ""
Concatenatable is a better name
If you squint addition or multiplication is like concatenating numbers

Then you realize a whole bunch of other things fit the rules, or you wouldn’t because the name was too specific

A Monoid is abstract and instead of inventing another too specific name Haskell used the one mathematicians use.

Monoids show up all over the place, even if they are called by different names, and especially if you parallelize any work flows.

Semigroup-ing and aggregating

  • A Semigroup is a Monoid without the identity element requirement.
  • Really useful if you have some columnar data where you want to declaratively group and aggregate
  • In this example we will take airplane crashes since 1908 from https://dev.socrata.com/foundry/opendata.socrata.com/q2te-8cvq and aggregate some statistics by different columns.

Here are links to everything needed to run the examples

First we define types for our columns so we cannot mix up our columns, note newtype is a real type, i.e. you can’t pass the wrapped thing in its place
-- Our date column wraps "Day" but parses as Y/M/D from the CSV
newtype Date = Date {getDay :: Day}
  deriving (Eq, Ord, Show, Read)

-- the date format definition used by the pretty printer and parser
mkDateFmt :: (TimeLocale -> String -> b) -> b
mkDateFmt f = f defaultTimeLocale "%m/%d/%Y"

-- pretty print the date in the same way that its read from the CSV
prettyDate :: Date -> String
prettyDate = mkDateFmt formatTime . getDay

-- customize the CSV parser for the date
instance FromField Date where
  parseField =
    --  types
    --   parseField :: FromField a => Field -> Parser a
    --   parseTimeM
    --    :: (Monad m, ParseTime t)
    --    => Bool -> TimeLocale -> String -> String -> m t
    --   >=> :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
    parseField >=>
      ( (Date <$>) .  mkDateFmt (parseTimeM True) )
Most of our columns are wrappers around simple types
-- the location column wraps "Text" and parses using its instance
newtype Location = Location {getLocation :: Text}
  deriving (FromField, ToField, Show, Read, Eq, Ord)

-- the operator column wraps "Text" and parses using its instance
newtype Operator = Operator {getOperator :: Text}
  deriving (FromField, ToField, Show, Read, Eq, Ord)

-- the flight number column wraps "Text" and parses using its instance
newtype FlightNumber = FlightNumber {getFlightNumber :: Text}
  deriving (FromField, ToField, Show, Read, Eq, Ord)

-- the A/C type column wraps "Text" and parses using its instance
newtype AcType = AcType {getAcType :: Text}
  deriving (FromField, ToField, Show, Read, Eq, Ord)

-- the fatalities column wraps "Int" and parses using its instance
newtype Fatalities = Fatalities {getFatalities :: Int}
  deriving (FromField, ToField, Show, Read, Eq, Ord, Num)
Next we define our row
-- the data type that represents a row in the CSV that we will parse
data CsvRow = CsvRow
  { date :: Date
  , location :: Location
  , operator :: Operator
  , flightNumber :: Maybe FlightNumber
  , acType :: AcType
  , fatalities :: Maybe Fatalities
  } deriving (Generic)

-- We define how to parse a CSV file making use of "genericParseNamedRecord"
-- to do this automatically for us because "CsvRow" is an instance of "Generic"
-- we only customized the definition of the labels
instance FromNamedRecord CsvRow where
  parseNamedRecord =
    -- types
    --   genericParseNamedRecord
    --    :: (Generic a, GFromNamedRecord (Rep a))
    --    => Options -> NamedRecord -> Parser a
    --   fieldLabelModifier :: String -> String
    genericParseNamedRecord
      defaultOptions
        { fieldLabelModifier =
            \case
              "flightNumber" -> "Flight #"
              "acType" -> "Type"
              h:t -> Char.toUpper h : t
              [] -> []
        }
Then we define a type for the statistics we wish to collect and a way to project the statistics from the row
-- a type to represent the number of crashes reported
newtype Crashes = Crashes {getCrashes :: Int}
  deriving (Num, Show, Read, Ord, Eq)

-- a data type for the statistic we want to record per row type
data Stats = Stats
  { statFirst :: Semigroup.Min Date          -- lower bound Date
  , statLast :: Semigroup.Max Date           -- upper bound Date
  , statFatalities :: Monoid.Sum Fatalities  -- sum of Fatalities
  , statCrashes :: Monoid.Sum Crashes        -- sum of Crashes
  } deriving (Generic, Show)

-- Generically derive a "Semigroup" instance for "Stats" using "Generic" and
-- the fact that each field has a "Semigroup" instance
instance Semigroup Stats where
  (<>)  = gsappenddefault


-- convert a CSV row into a statistic we can aggregate
rowToStats ::  CsvRow -> Stats
rowToStats CsvRow {  date , fatalities} =
   Stats
      { statFirst      = Semigroup.Min date
      , statLast       = Semigroup.Max date
      , statFatalities = Semigroup.Sum (fromMaybe 0 fatalities)
      , statCrashes    = Semigroup.Sum 1
      }
We are going to display our statistics in tabular form so we add a function that turns a Stats into a row of columns of strings and also a constant for the headers of our rows
-- display a "Stats" as a row of columns of "String"
displayStatsColumns :: Stats -> [String]
displayStatsColumns  =
  -- types:
  --   sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
  -- inferred concrete types:
  --   sequence :: [Stats -> String] -> Stats -> [String]
  sequence
    [ prettyDate . Semigroup.getMin . statFirst
    , prettyDate . Semigroup.getMax . statLast
    , show . getFatalities . Semigroup.getSum . statFatalities
    , show . getCrashes . Semigroup.getSum . statCrashes
    ]

-- the column headers associated with rows of columns of strings of "Stats"
statsHeaders :: [String]
statsHeaders = ["first", "last", "fatalities", "crashes"]
a -> b can be written (->) a b and there is a Monad instance for (->) a allowing us to use sequence
We define how we group statistics
-- group rows on some value aggregating statistics using some "Semigroup"
aggregateStatisticsBy
  :: (Ord groupBy, Semigroup statistic)
  => (row -> Maybe (groupBy, statistic))
  -> [row]
  -> [(groupBy, statistic)]
aggregateStatisticsBy grouper =
  -- types:
  --   toList :: Map k a -> [(k, a)]
  --   <> :: Semigroup a => a -> a -> a
  --   fromListWith :: Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
  --   mapMaybe :: (a -> Maybe b) -> [a] -> [b]
    -- :: Map a Stats -> [(a, Stats)]
    Map.toList .
    -- :: [(a, Stats)] -> Map a Stats
    Map.fromListWith (<>) .
    -- :: [CsvRow] -> [(a, Stats)]
    mapMaybe grouper

We group by inserting statistics into a Map and combining with the monoidal operator (<>) on a clash

We define a function that will do the grouping and displaying
-- group the CSV rows aggregating the statistics and displaying the "n" best ranked stats
groupAndDisplayStats
  :: (Ord o, Ord a)
  => (CsvRow -> Maybe (a, Stats)) -- grouping function
  -> String                       -- grouping column header
  -> (a -> String)                -- display grouping column
  -> (Stats -> o)                 -- ordering function
  -> Int                          -- number of rows to display
  -> [CsvRow]                     -- the CSV rows
  -> String
groupAndDisplayStats grouper groupName displayGroup ordering cnt rows =
  -- types:
  --   hable :: Config style -> [[String]] -> String
  --   take :: Int -> [a] -> [a]
  --   map :: (a -> b) -> [a] -> [b]
  --   snd :: (a, b) -> b
  --   sortOn :: Ord b => (a -> b) -> [a] -> [a]
    Hable.hable Hable.defaultConfig $
    (groupName : statsHeaders) :
    ( take cnt .
      --  :: [(a, Stats)] -> [[String]]
      map
        (\(g, stats) ->
          displayGroup g : displayStatsColumns stats
        ) .
      -- :: [(a, Stats)] -> [(a, Stats)]
      List.sortOn (ordering . snd) .
      -- :: [CsvRow] -> [(a, Stats)]
      aggregateStatisticsBy grouper $
      -- :: [CsvRow]
      rows
    )

We define grouping functions with each function being very clear on which column they group.

statsByOperator :: CsvRow -> Maybe (Operator, Stats)
statsByOperator row = Just ( operator row , rowToStats row)

statsByFlightNumber :: CsvRow -> Maybe (FlightNumber,  Stats)
statsByFlightNumber row = (,rowToStats row) <$> flightNumber row

statsByLocation :: CsvRow -> Maybe (Location, Stats)
statsByLocation row = Just ( location row , rowToStats row)

statsAcType :: CsvRow -> Maybe (AcType, Stats)
statsAcType row = Just ( acType row , rowToStats row)

We define ranking functions with each function being very clear which statistics are used for the ranking.

byMostFatalities :: Stats -> Down Fatalities
byMostFatalities = Down . Semigroup.getSum . statFatalities

byLeastFatalities :: Stats -> Fatalities
byLeastFatalities = Semigroup.getSum . statFatalities

bySafestToCrashWith :: Stats -> (Fatalities, Down Crashes)
bySafestToCrashWith Stats{statFatalities, statCrashes} =
  (Semigroup.getSum statFatalities, Down (Semigroup.getSum statCrashes))
We end off by wiring everything together with our main
main :: IO ()
main = do
  csvData <- BL.readFile "./Airplane_Crashes_and_Fatalities_Since_1908.csv"
  rows <-
    either fail (pure . Vector.toList . snd) $ decodeByName csvData

  putStrLn "5 deadliest operators"
  putStr $
    groupAndDisplayStats
      statsByOperator "operator" (Text.unpack . getOperator) byMostFatalities 5 rows

  putStrLn "5 safest operators"
  putStr $
    groupAndDisplayStats
      statsByOperator "operator" (Text.unpack . getOperator) byLeastFatalities 5 rows


  putStrLn "6 deadliest flight numbers"
  putStr $
    groupAndDisplayStats
      statsByFlightNumber "flight #" (Text.unpack . getFlightNumber) byMostFatalities 6 rows

  putStrLn "4 deadliest locations"
  putStr $
    groupAndDisplayStats
      statsByLocation "location" (Text.unpack . getLocation) byMostFatalities 4 rows

  putStrLn "5 deadliest A/C Types"
  putStr $
    groupAndDisplayStats
      statsAcType "A/C Type" (Text.unpack . getAcType) byMostFatalities 5 rows


  putStrLn "5 best A/C Types to crash with"
  putStr $
    groupAndDisplayStats
      statsAcType "A/C Type" (Text.unpack . getAcType) bySafestToCrashWith 5 rows

Giving us this output

5 deadliest operators
╔════════════════════════════╤════════════╤════════════╤════════════╤═════════╗
║ operator                   │ first      │ last       │ fatalities │ crashes ║
╟────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Aeroflot                   │ 12/04/1946 │ 09/14/2008 │ 7156       │ 179     ║
╟────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Military - U.S. Air Force  │ 08/07/1943 │ 03/31/2005 │ 3717       │ 176     ║
╟────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Air France                 │ 10/31/1933 │ 06/01/2009 │ 1734       │ 70      ║
╟────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ American Airlines          │ 12/22/1934 │ 11/12/2001 │ 1421       │ 36      ║
╟────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Pan American World Airways │ 01/11/1938 │ 12/21/1988 │ 1302       │ 41      ║
╚════════════════════════════╧════════════╧════════════╧════════════╧═════════╝
5 safest operators
╔════════════════════════════════╤════════════╤════════════╤════════════╤═════════╗
║ operator                       │ first      │ last       │ fatalities │ crashes ║
╟────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ American International Airways │ 08/18/1993 │ 08/18/1993 │ 0          │ 1       ║
╟────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Ararat Avia                    │ 10/21/1998 │ 10/21/1998 │ 0          │ 1       ║
╟────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Canadian Air Transat           │ 08/24/2001 │ 08/24/2001 │ 0          │ 1       ║
╟────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Centurian Air Cargo            │ 07/07/2008 │ 07/07/2008 │ 0          │ 1       ║
╟────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Hewa Bora Airways              │ 04/15/2008 │ 04/15/2008 │ 0          │ 1       ║
╚════════════════════════════════╧════════════╧════════════╧════════════╧═════════╝
6 deadliest flight numbers
╔═══════════╤════════════╤════════════╤════════════╤═════════╗
║ flight #  │ first      │ last       │ fatalities │ crashes ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ -         │ 08/06/1913 │ 02/10/2005 │ 628        │ 67      ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ 1736/4805 │ 03/27/1977 │ 03/27/1977 │ 583        │ 1       ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ 123       │ 08/12/1985 │ 08/12/1985 │ 520        │ 1       ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ 182       │ 09/25/1978 │ 06/23/1985 │ 466        │ 2       ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ 191       │ 06/24/1972 │ 08/02/1985 │ 410        │ 3       ║
╟───────────┼────────────┼────────────┼────────────┼─────────╢
║ 901       │ 03/19/1960 │ 08/09/1995 │ 409        │ 6       ║
╚═══════════╧════════════╧════════════╧════════════╧═════════╝
4 deadliest locations
╔═══════════════════════════════════════╤════════════╤════════════╤════════════╤═════════╗
║ location                              │ first      │ last       │ fatalities │ crashes ║
╟───────────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Tenerife, Canary Islands              │ 12/07/1965 │ 04/25/1980 │ 761        │ 3       ║
╟───────────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Mt. Osutaka, near Ueno Village, Japan │ 08/12/1985 │ 08/12/1985 │ 520        │ 1       ║
╟───────────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Moscow, Russia                        │ 03/26/1952 │ 07/29/2007 │ 432        │ 15      ║
╟───────────────────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Near Moscow, Russia                   │ 05/18/1935 │ 07/14/2001 │ 364        │ 9       ║
╚═══════════════════════════════════════╧════════════╧════════════╧════════════╧═════════╝
5 deadliest A/C Types
╔═══════════════════════════╤════════════╤════════════╤════════════╤═════════╗
║ A/C Type                  │ first      │ last       │ fatalities │ crashes ║
╟───────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Douglas DC-3              │ 10/06/1937 │ 12/15/1994 │ 4793       │ 334     ║
╟───────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Antonov AN-26             │ 07/14/1977 │ 10/04/2007 │ 1068       │ 36      ║
╟───────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Douglas DC-6B             │ 06/30/1951 │ 07/24/1985 │ 1055       │ 27      ║
╟───────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Douglas C-47              │ 10/01/1942 │ 09/02/2000 │ 1046       │ 62      ║
╟───────────────────────────┼────────────┼────────────┼────────────┼─────────╢
║ McDonnell Douglas DC-9-32 │ 03/16/1969 │ 02/02/1998 │ 951        │ 19      ║
╚═══════════════════════════╧════════════╧════════════╧════════════╧═════════╝
5 best A/C Types to crash with
╔══════════════════╤════════════╤════════════╤════════════╤═════════╗
║ A/C Type         │ first      │ last       │ fatalities │ crashes ║
╟──────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Lockheed L-1011  │ 05/05/1983 │ 07/30/1992 │ 0          │ 2       ║
╟──────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Sikorsky S-38B   │ 08/10/1934 │ 08/13/1935 │ 0          │ 2       ║
╟──────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Airbus A-330-243 │ 08/24/2001 │ 08/24/2001 │ 0          │ 1       ║
╟──────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Airbus A-340     │ 08/02/2005 │ 08/02/2005 │ 0          │ 1       ║
╟──────────────────┼────────────┼────────────┼────────────┼─────────╢
║ Airbus A.320-214 │ 03/22/1998 │ 03/22/1998 │ 0          │ 1       ║
╚══════════════════╧════════════╧════════════╧════════════╧═════════╝