Giter Site home page Giter Site logo

protolude / protolude Goto Github PK

View Code? Open in Web Editor NEW
397.0 10.0 52.0 330 KB

A sensible starting Prelude template.

Home Page: http://www.stephendiehl.com/posts/protolude.html

License: MIT License

Haskell 90.96% Shell 8.88% Nix 0.16%
haskell prelude haskell-prelude alternative-prelude base safe partial-functions

protolude's Introduction

Protolude

Build Status Build Status Build Status Hackage

A sensible starting Prelude for building custom Preludes.

Design points:

  • Banishes String.
  • Banishes partial functions.
  • Compiler warning on bottoms.
  • Polymorphic string IO functions.
  • Polymorphic show.
  • Automatic string conversions.
  • Types for common data structures in scope.
  • Types for all common string types (Text/ByteString) in scope.
  • Banishes impure exception throwing outside of IO.
  • StateT/ReaderT/ExceptT transformers in scope by default.
  • Foldable / Traversable functions in scope by default.
  • Unsafe functions are prefixed with "unsafe" in separate module.
  • Compiler agnostic, GHC internal modules are abstracted out into Base.
  • sum and product are strict by default.
  • Includes Semiring for GHC >= 7.6.
  • Includes Bifunctor for GHC >= 7.6.
  • Includes Semigroup for GHC >= 7.6.

Supports:

  • GHC 7.6.3
  • GHC 7.8.4
  • GHC 7.10.3
  • GHC 8.0.2
  • GHC 8.2.2
  • GHC 8.4.1
  • GHC 8.4.4
  • GHC 8.6.1
  • GHC 8.6.4
  • GHC 8.6.5
  • GHC 8.8.1
  • GHC 8.10.1
  • GHC 9.0.1
  • GHC 9.2.1

Stack LTS:

  • lts-6.x
  • lts-7.x
  • lts-8.x
  • lts-9.x
  • lts-10.x
  • lts-11.x
  • lts-12.x
  • lts-13.x
  • lts-14.x
  • lts-15.x
  • lts-16.x
  • lts-17.x
  • lts-18.x
  • lts-19.14 and higher

Usage

To try out standalone prelude at the interactive shell, from the Protolude project directory run.

$ stack repl
> import Protolude

Swapping out the old Prelude

Disable the built-in prelude at the top of your file:

{-# LANGUAGE NoImplicitPrelude #-}

Or directly in your project cabal file:

default-extensions: NoImplicitPrelude

Then in your modules:

import Protolude

Dependencies

Protolude tries to be light on dependencies and only pulls in essential libraries that are universally common across most real-world projects. Lower and upper bounds are fully specified and compatible with both vanilla Cabal and tracks Stack LTS resolver.

Dependencies Lower (>=) Upper (<)
array 0.4 0.6
async 2.0 2.3
base 4.6 4.16
bytestring 0.10 0.11
containers 0.5 0.7
deepseq 1.3 1.5
ghc-prim 0.3 0.7
hashable 1.2 1.4
mtl 2.1 2.3
stm 2.4 2.6
text 1.2 1.3
transformers 0.4 0.6
fail 4.9 4.10

Structure

Protolude's main modules are the following:

FAQs

  • My putStrLn and putStr instances are no longer inferred in the presense of the -XOverloadedStrings extension?

Because the print functions are polymorphic the type of the print functions may require annotations if the type is not fully specified by inference. To force a specific type at the call site use either

putText :: MonadIO m => T.Text -> m ()
putLText :: MonadIO m => TL.Text -> m ()
  • How do I write manual Show instances if show isn't provided?

Generally speaking writing manual instances of Show is a Haskell antipattern because it produces law-violating instances of Show. You probably want to use a pretty printer library for custom printing.

If backwards compatibility is needed then the base library can be imported manually.

import GHC.Show (Show(..))

Automatic deriving of Show for your types is still supported since the class is in scope by default.

  • Partial functions like undefined raise compiler warnings on usage.

This is by design. For fatal uncatchable errors use the provided panic function if you intend the program to immediately abort.

panic "Thus I die. Thus, thus, thus. Now I am dead"

If inside of IO simply use throwIO for exception handling, or if in pure business logic use well-typed checked exceptions of the ExceptT variety.

  • Why is id not in scope?

It has been renamed to identity to reserve the id identifier for the more common use case of business logic.

  • But what if I want the partial functions?

You if you need partial functions for backwards compatibility you can use the Protolude.Partial module and mask the safe definitions as needed.

import Protolude hiding (head)
import Protolude.Partial (head)

Development Tools

GHC Magic

To build the exports management tool use:

$ cabal new-build exports --flag dev
$ cabal run exports

This tool uses GHC's internal compile symbol table to generate a list of exports and keep the export list of protolude stable across different versions of GHC and base.

Continious Integration

There is a massive test suite that tests all versions of GHC 7.6 - GHC HEAD alongside all Stack resolvers to ensure no regressions. Any pull requests or patch has to pass the 47 integrity checks before being considered. Any pull request must keep the export list consistent across GHC and Base version and not have any accidental symbol dropping or drift without updating the export golden tests.

License

Released under the MIT License. Copyright (c) 2016-2022, Stephen Diehl

protolude's People

Contributors

4e6 avatar adamwespiser avatar alexanderkjeldaas avatar andrevdm avatar asterite avatar blackgnezdo avatar cbaatz avatar ccntrq avatar cocreature avatar cs avatar dten avatar erikd avatar felixonmars avatar luc-tielen avatar martijnbastiaan avatar michaelburge avatar mimi1vx avatar mitchellwrosen avatar pierrer avatar profpatsch avatar sdiehl avatar snoyberg avatar timmot avatar tonyday567 avatar vendethiel avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

protolude's Issues

can you please add putTextLn?

Hello,

Can you please add a putTextLn?

The putStrLn is not that useful as it is ambiguous and needs a type signature. It would be nice to have putTextLn and not worry about ambiguity.

Thanks

maximum []

Caught this while my code (which relies on protoludes banishes partial functions) was in QA. I'm not sure if changing the type to match head behavior is desired, so it's up to you what to do. Wanted it known.

15:43:42 (19:43) [@bos-lp6rc:~/src/protolude] master* ± stack ghci
protolude-0.2: configure (lib)
Configuring protolude-0.2...
protolude-0.2: initial-build-steps (lib)
Configuring GHCi with the following packages: protolude
GHCi, version 8.0.1: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from /home/aflott/src/protolude/.ghci

<no location info>: error:
    Could not find module ‘Protolude’
    It is not a module in the current program, or in any known package.
Loaded GHCi configuration from /home/aflott/.ghci
[ 1 of 16] Compiling Bifunctor        ( /home/aflott/src/protolude/src/Bifunctor.hs, interpreted )
[ 2 of 16] Compiling Semiring         ( /home/aflott/src/protolude/src/Semiring.hs, interpreted )
[ 3 of 16] Compiling List             ( /home/aflott/src/protolude/src/List.hs, interpreted )
[ 4 of 16] Compiling Base             ( /home/aflott/src/protolude/src/Base.hs, interpreted )
[ 5 of 16] Compiling Conv             ( /home/aflott/src/protolude/src/Conv.hs, interpreted )
[ 6 of 16] Compiling Exceptions       ( /home/aflott/src/protolude/src/Exceptions.hs, interpreted )
[ 7 of 16] Compiling Unsafe           ( /home/aflott/src/protolude/src/Unsafe.hs, interpreted )
[ 8 of 16] Compiling Either           ( /home/aflott/src/protolude/src/Either.hs, interpreted )
[ 9 of 16] Compiling Applicative      ( /home/aflott/src/protolude/src/Applicative.hs, interpreted )
[10 of 16] Compiling Functor          ( /home/aflott/src/protolude/src/Functor.hs, interpreted )
[11 of 16] Compiling Monad            ( /home/aflott/src/protolude/src/Monad.hs, interpreted )
[12 of 16] Compiling Bool             ( /home/aflott/src/protolude/src/Bool.hs, interpreted )
[13 of 16] Compiling Show             ( /home/aflott/src/protolude/src/Show.hs, interpreted )
[14 of 16] Compiling Panic            ( /home/aflott/src/protolude/src/Panic.hs, interpreted )
[15 of 16] Compiling Debug            ( /home/aflott/src/protolude/src/Debug.hs, interpreted )
[16 of 16] Compiling Protolude        ( /home/aflott/src/protolude/src/Protolude.hs, interpreted )
Ok, modules loaded: Debug, Panic, Show, Bool, Monad, Functor, Applicative, Either, Protolude, Unsafe, Base, List, Semiring, Conv, Exceptions, Bifunctor.
Loaded GHCi configuration from /tmp/ghci29773/ghci-script
*Unsafe Prelude Applicative Base Bifunctor Bool Conv Debug Either Exceptions Functor List Monad Panic Protolude Semiring Show Unsafe>
*Unsafe Prelude Applicative Base Bifunctor Bool Conv Debug Either Exceptions Functor List Monad Panic Protolude Semiring Show Unsafe>
*Unsafe Prelude Applicative Base Bifunctor Bool Conv Debug Either Exceptions Functor List Monad Panic Protolude Semiring Show Unsafe> maximum []

<interactive>:3:1: warning: [-Wtype-defaults]
    • Defaulting the following constraints to type ‘()’
        (Ord a0) arising from a use of ‘it’ at <interactive>:3:1-10
        (Show a0)
          arising from a use of ‘Base.print’ at <interactive>:3:1-10
    • In the first argument of ‘Base.print’, namely ‘it’
      In a stmt of an interactive GHCi command: Base.print it
*** Exception: Prelude.maximum: empty list

I expected Nothing like head:

*Unsafe Prelude Applicative Base Bifunctor Bool Conv Debug Either Exceptions Functor List Monad Panic Protolude Semiring Show Unsafe> head []

<interactive>:4:1: warning: [-Wtype-defaults]
    • Defaulting the following constraint to type ‘()’
        Show a0 arising from a use of ‘Base.print’
    • In a stmt of an interactive GHCi command: Base.print it
Nothing

ByteString is not exported (‽)

When I look at the source code I see:

-- ByteString
import qualified Data.ByteString.Lazy
import qualified Data.ByteString as X (ByteString)

But ghci:

<interactive>:1:1: Not in scope: ‘ByteString’
*Import> import Protolude 
*Import Protolude> :i ByteString

<interactive>:1:1: Not in scope: ‘ByteString’
*Import Protolude> :i LByteString
type LByteString = Data.ByteString.Lazy.Internal.ByteString
    -- Defined in ‘Protolude’

huh?

While I agree that `head` is partial, overloading it has lead to surprising behavior

consider this test from a practical project:

    it "calculates complex case correctly" $ do
      let rows = length grid
          cols = length (head grid)
          grid :: [[Double]] =
                  [ [1.0,   2.0]
                  , [2.0,   3.0]
                  , [-2.0,  1.0]
                  , [0,     0  ]
                  ]
      (rows, cols) `shouldBe` (4, 2)

it fails with:

       expected: (4,2)
       but got: (4,1)

After scratching head for several minutes, that this is because the type signature has changed, but I say this is very surprising behavior that is undesirable.
I'm curious why head was reintroduced (and hasn't stayed being headMay) yet changed its signature for the safe one?

id trace functions

Can we have traceId and traceShowId as well? I find myself writing (\x -> traceShowId x x) lots of times.

The Print class often leads to ambiguous types in monad contexts

For example:

  scriptIO $ mapM_ (putStrLn :: String -> IO ()) <$> listDirectory outDir

without the type annotation this leads to the message

dohaskell.hs:32:14: error:
     Ambiguous type variable m0 arising from a use of mapM_
      prevents the constraint (Monad m0) from being solved.
      Relevant bindings include
        main :: IO (m0 ()) (bound at dohaskell.hs:20:1)
      Probable fix: use a type annotation to specify what m0 should be.
      These potential instances exist:
        instance Monad (Either e) -- Defined in ‘Data.Either’
        instance Monad Dual -- Defined in ‘Data.Monoid’
        instance Monad First -- Defined in ‘Data.Monoid’
        ...plus 12 others
        ...plus 7 instances involving out-of-scope types
        (use -fprint-potential-instances to see them all)
     In the first argument of (<$>), namely mapM_ putStrLn
      In the second argument of ($), namely
        mapM_ putStrLn <$> listDirectory outDir
      In a stmt of a 'do' block:
        scriptIO $ mapM_ putStrLn <$> listDirectory outDir

dohaskell.hs:32:20: error:
     Ambiguous type variable m0 arising from a use of putStrLn
      prevents the constraint (MonadIO m0) from being solved.
      Relevant bindings include
        main :: IO (m0 ()) (bound at dohaskell.hs:20:1)
      Probable fix: use a type annotation to specify what m0 should be.
      These potential instances exist:
        instance [safe] MonadIO IO -- Defined in ‘Control.Monad.IO.Class’
        instance [safe] MonadIO m => MonadIO (ExceptT e m)
          -- Defined in ‘transformers-0.5.2.0:Control.Monad.Trans.Except’
        ...plus one instance involving out-of-scope types
        (use -fprint-potential-instances to see them all)
     In the first argument of mapM_, namely putStrLn
      In the first argument of (<$>), namely mapM_ putStrLn
      In the second argument of ($), namely
        mapM_ putStrLn <$> listDirectory outDir

inside an ExceptT String IO block (from https://hackage.haskell.org/package/errors-2.1.2/docs/Control-Error-Script.html).

Errors like these happen regularly with the Print class.

Protolude re-exports Type with GHC 8.2 but not with GHC 8.0

I have a library that uses Protolude and defines its own type called Type. I'd like it to compile with GHC 8.0 and 8.2 using protolude >= 0.2.1.

If I import Protolude as

import Protolude hiding (Type)

I get the following warning when using GHC 8.0 (actually stackage 9.21):

    [ 6 of 19] Compiling GraphQL.Internal.Syntax.AST ( src/GraphQL/Internal/Syntax/AST.hs, .stack-work/dist/x86_64-osx/Cabal-1.24.2.0/build/GraphQL/Internal/Syntax/AST.o )

    /Users/jml/src/graphql-api/src/GraphQL/Internal/Syntax/AST.hs:49:1: warning: [-Wdodgy-imports]
        Module ‘Protolude’ does not export ‘Type’

If I import Protolude without hiding anything, I get the following error when using GHC 8.2 (actually stackage 10.4):

    [ 6 of 19] Compiling GraphQL.Internal.Syntax.AST ( src/GraphQL/Internal/Syntax/AST.hs, .stack-work/dist/x86_64-osx/Cabal-2.0.1.0/build/GraphQL/Internal/Syntax/AST.o )

    /Users/jml/src/graphql-api/src/GraphQL/Internal/Syntax/AST.hs:81:55: error:
        Ambiguous occurrence ‘Type’
        It could refer to either ‘Protolude.Type’,
                                 imported from ‘Protolude’ at src/GraphQL/Internal/Syntax/AST.hs:49:1-16
                                 (and originally defined in ‘GHC.Types’)
                              or ‘GraphQL.Internal.Syntax.AST.Type’,
                                 defined at src/GraphQL/Internal/Syntax/AST.hs:172:1
       |
    81 | data VariableDefinition = VariableDefinition Variable Type (Maybe DefaultValue)
       |                                                       ^^^^

In both cases, protolude is constrained to >= 0.2.1.

I looked at the Protolude source to find where the re-export was coming from, but couldn't do so in the time allotted. In the meantime, I'll rename the type to work around this.

Is this actually a bug in Protolude?

StringConv doesn't do UTF-8 encoding for String→ByteString

For conversion between Text and ByteString, StringConv does UTF-8 encoding/decoding. For String and ByteString, it doesn't. Is there any good reason for this? The current behavior seems inconsistent to me (not to mention that someone might get bitten by lossy ASCII encoding).

idea: liftIO1, liftIO2, liftIO3

Lift an IO operation with n arguments into another monad.
At least 1 and 2 are helpful I think.

liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d

Impl from ghc, module MonadUtils:

-- | Lift an 'IO' operation with 1 argument into another monad
liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b
liftIO1 = (.) liftIO

-- | Lift an 'IO' operation with 2 arguments into another monad
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c
liftIO2 = ((.).(.)) liftIO

-- | Lift an 'IO' operation with 3 arguments into another monad
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d
liftIO3 = ((.).((.).(.))) liftIO

ExceptT constructor

Any reason why the ExceptT constructor is not exported? As far as I can see, it’s the only way to conveniently go from Either to ExceptT.

Import fromString along with IsString

Currently we import it as import Data.String as X (IsString)

Instance declarations of IsString gives a cryptic error that the class is present but the function fromString is not a visible function of the type.

traceShow has different type

Debug.Trace.traceShow already exists with a different signature.

The Protolude one should probably use the same type if it exposes the same function name.

0.1.11?

I think it would make sense to release 0.1.11 (yes, I want to have liftIO1 :P).

toS from Text to ByteString adds ""

Hello,

Thanks for sharing Protolude.

Using toS to convert from Text to ByteString outputs this: ""sample text here""

whereas, using Data.String.Conversions.cs outputs this: "sample text here"

Is it a better idea to just export Data.String.Conversions instead instead of exporting toS?

Thanks

Some useful functions

While recognizing that deciding what to include and exclude is a difficult balancing act, I was wondering if there was a specific reason that forM/mapM are not included here? (Also, apologies if this is the wrong place to bring this up, I'm still trying to figure out github's interface)

Proposal: Add safe-exceptions package to Protolude dependencies

Hi Stephen,

First of all, I would like to thank you for building this library, I started to heavily use it since your comments and blogpost around why you implemented it (totally agree). I've stopped using the default prelude in all my personal projects and it has made a huge improvement in the way I do Haskell these days.

I've found another library around execeptions that brings me a similar experience to Protolude, the library is called safe-exceptions, it's announcement blogpost goes through good explanations around why I would like to use in a "production" setting rather than relying on the default APIs.

Would you be open to include this as the Protolude default for exceptions API? If not, would you like to expand on your rationale? I'm very interested in hearing your thoughts on the matter.

Thanks for your time.

Haddock in hackage and stackage

This is a minor issue but since protolude-0.2 haddock looks a bit off both on hackage and stackage

Only the Protolude and Unsafe modules have generated haddocks.

Generic `note` and `hush`?

Our prelude has these two things:

-- | Generic version of 'hush' from Control.Errors
hush :: Alternative m => Either e a -> m a
hush (Left _)  = empty
hush (Right x) = pure x

-- | Generic version of 'note' from Control.Errors
note :: (MonadError e m) => e -> Maybe a -> m a
note err = maybe (throwError err) pure

They are inspired by functions of the same name in the errors package, except more generic so I don't have to remember which spelling I want when.

I guess the former could be:

hush = either (const empty) pure

What do you think?

Exporting `yield` conflicts with pipes

I use yield with pipes more commonly than I use the concurrency primitive. This means I hide yield from Protolude more often than I use it.

I can see how this is a matter of taste though.

[Question] fail method not exposed ?

What's the idiomatic way to handle call to the fail method from the Monad interface ?

It is not exposed by protolude and it is not quite clear to me if it is always a good idea to replace the call with panic (particularly in parser logic).

Thanks for your help.

Exception handling functions

What are your thoughts on adding async-exception handling functions to Protolude, such as

  • Control.Exception from base
  • Control.Monad.Catch from exceptions
  • Control.Monad.Trans.Control monad-control

(Of these, exceptions is the nicest, IMO)

Why were the internal modules hidden?

Prior to version 0.2 I was able to make my own adapted version of protolude by just copying Protolude.hs and make some changes to it. This adapted protolude still depended on the protolude package to get access to the other modules. That's no longer possible since the internal modules are not exported.

In fact, I was under the impression that this way of customizing Protolude.hs was the intended use of the package, since it's said to be a "Prelude template".

Any chance the modules could be exported again?

Expose `flip fmap` as `for`?

I've seen some people discuss this on Twitter and it seems like an OK idea to me:

Expose flip fmap as for, s.t. for :: Functor f => f a -> (a -> b) -> f b, and expose what's currently called for as forA.

What do you think?

No StringConv instance for Text ghcjs-base-0.2.0.0:Data.JSString.Internal.Type.JSString

There isn't full coverage for the GHCJS base library:

    No instance for (StringConv
                       Text ghcjs-base-0.2.0.0:Data.JSString.Internal.Type.JSString)
      arising from a use of ‘toS’
    In the first argument of ‘CallbackPropertyWithSingleArgument’, namely
      ‘(toS ev)’
    In the expression: CallbackPropertyWithSingleArgument (toS ev)
    In the expression:
      CallbackPropertyWithSingleArgument (toS ev) $ \ _ -> f```

Using printf rather than formatting

Hey, I'm mostly curious if there's a specific reason you've included printf instead of formatting. The main benefit I can see with formatting are that formats are composable. (Putting this publicly as an issue rather than in a private email for the benefit of future readers!)

One drawback of printf is that it only returns Strings, which are banned. Similar thing goes for choosing to keep in readMaybe and friends without converting to Text.

Releasing 0.2.2

Do you know when 0.2.2 is going to land on hackage ?
Just asking because it prevents our (ghc-8.4.1) travis-test to succeed.

Cheers,

with no `Show` instance define ability, how does one use `HUnit` ?

Hi

HUnit relies heavily on custom types under test having Show instances.
https://hackage.haskell.org/package/tasty-hunit-0.9.2/docs/src/Test-Tasty-HUnit-Orig.html#%40%3D%3F

It is of course would be great to use another printing instance like Pretty to output things in Tasty/HUnit but it does not look to be possible currently

The next best thing is perhaps to define Show instances in terms of Pretty locally in tests (to not taint the rest of the library with Show) but then there is the orphaned instances problem

What is the currently suggested way of solving this problem?

Thanks

Exporting `Handler` conflicts with servant handlers

Servant exports a Handler type for web endpoints. Protolude re-exports the Handler for exceptions. I rarely use the latter but frequently use the former. I'd personally prefer it if Protolude didn't export Handler.

re-use (&) from Data.Function if base >= 8.0

The re-definition of (&) would force users of libraries that naturally re-export it from Data.Function (if base >= 4.8.0.0 ) to hide it from Protolude.

This is a bit annoying; while working with protolude together with turtle for instance the list of hiding items is getting long enough ;-)

Thanks for the wonderful prelude.

Concern about partial functions in Conv

While StringConv makes perfect sense in some instances (such as StringConv String Text), conversions from bytes to strings is an operation that can fail. However StringConv doesn't produce a result that includes failures.

Because of this instances likeStringConv ByteString Text can either throw runtime errors or produce incorrect data, depending on whether toS or toSL is used.

Have you considered restricting StringConv to only conversions that can be made without errors?

(<&>) = flip (<$>)

We already have

(&) = flip ($)

so I think <&> would be a nice logical completion. Especially for use cases like

somefunctor <&> function >>= \case
  pattern-match

Of course there’s foreach, but the naming is kind of questionable, especially combined with for from Traversable. For example, I have a piece of code where the levels are becoming confusing:

metas <- for (foreach postDirs (FP.</> postFileName)) postToPostMeta
metas <- for (postDirs <&> (FP.</> postFileName)) postToPostMeta

looks nicer to me. Not much, but at least a bit. Hm, maybe I should just go with

metas <- for (postDirs `foreach` (FP.</> postFileName)) postToPostMeta

Another valid stance would be to not have <&> or even & because it’s just confusing code flow even more.

Make Semigroup superclass of Monoid.

AFAIK the only reason it's not is because of potential code breakage, but that is not a concern for this library.

It would be nice to use the <> operator on monoids again.

Neither undefined or error raise compiler warnings on usage

From README.md:

Partial functions like undefined and error raise compiler warnings on usage.

This is by design. For fatal uncatchable errors use the provided panic function if you intend the program to immediately abort.

Has this intentionally been removed or should warning pragmas be attached to these functions?

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.