DoAndIfThenElse

Moritz Angermann moritz at lichtzwerge.de
Fri Feb 9 02:42:37 UTC 2018


Hi,

not sure if this helps.

testsuite/tests/parser/should_compile/DoAndIfThenElse.hs gives us
```
{-# LANGUAGE DoAndIfThenElse #-}

module DoAndIfThenElse where

foo :: IO ()
foo = do if True
         then return ()
         else return ()
```

and there is some other mention in 
libraries/bytestring/bench/wiki-haskell.html, which states:
```
<p>Haskell 2010 adds the <a href="/wiki/Foreign_function_interface" title="Foreign function interface">foreign function interface</a> (FFI) to Haskell, allowing for bindings to other programming languages, fixes some <a href="/wiki/Syntax_(programming_languages)" title="Syntax (programming languages)">syntax</a> issues (changes in the formal grammar) and bans so-called "n-plus-k-patterns", that is, definitions of the form <code>fact (n+1) = (n+1) * fact n</code> are no longer allowed. It introduces the Language-Pragma-Syntax-Extension which allows for designating a Haskell source as Haskell 2010 or requiring certain extensions to the Haskell language. The names of the extensions introduced in Haskell 2010 are DoAndIfThenElse, HierarchicalModules, EmptyDataDeclarations, FixityResolution, ForeignFunctionInterface, LineCommentSyntax, PatternGuards, RelaxedDependencyAnalysis, LanguagePragma and NoNPlusKPatterns.<sup id="cite_ref-2010ann_1-2" class="reference"><a href="#cite_note-2010ann-1"><span>[</span>1<span>]</span></a></sup></p>
```

in compiler/main/DynFlags.hs we find
```
languageExtensions (Just Haskell2010)
    = [LangExt.ImplicitPrelude,
       LangExt.MonomorphismRestriction,
       LangExt.DatatypeContexts,
       LangExt.TraditionalRecordSyntax,
       LangExt.EmptyDataDecls,
       LangExt.ForeignFunctionInterface,
       LangExt.PatternGuards,
       LangExt.DoAndIfThenElse,
       LangExt.RelaxedPolyRec]
```

So, in Haskell2010, it's always on, and allows to write the above code. When we set
NoDoAndIfThenElse, we get
```
    Unexpected semi-colons in conditional:
        if True; then return (); else return ()
    Perhaps you meant to use DoAndIfThenElse?
```

And then there's https://prime.haskell.org/wiki/DoAndIfThenElse.


Cheers,
 Moritz

> On Feb 9, 2018, at 10:24 AM, Harendra Kumar <harendra.kumar at gmail.com> wrote:
> 
> Hi,
> 
> I recently found a mention of DoAndIfThenElse extension somewhere. I looked inside the ghc user guide and could not find any such extension. Then I looked in the ghc man page, no mention. I googled and found a very sparse references to it here and there. Then I tried using the extension with ghc and ghc seems to accept it. What's the story behind this, why is it not documented but accepted?
> 
> thanks,
> harendra
> _______________________________________________
> ghc-devs mailing list
> ghc-devs at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs



More information about the ghc-devs mailing list