Skip to content

Commit

Permalink
free-examples: Fix some -Wx-partial warnings
Browse files Browse the repository at this point in the history
These were uncovered by GHC 9.8, where -Wx-partial is included in -Wall.
  • Loading branch information
RyanGlScott committed Aug 1, 2023
1 parent d218063 commit 38f4f07
Show file tree
Hide file tree
Showing 2 changed files with 12 additions and 3 deletions.
8 changes: 7 additions & 1 deletion examples/Cabbage.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -83,8 +83,14 @@ When the starting side becomes empty, the farmer succeeds.
A straightforward implementation to solve the problem could use the
list monad, trying all possible solutions and

> getFirstSolution :: [Situation] -> Situation
> getFirstSolution ss =
> case ss of
> s:_ -> s
> [] -> error "No solutions"
>
> solution1 :: Situation
> solution1 = head $ solutions' initial
> solution1 = getFirstSolution $ solutions' initial
> where
> solutions' a = if success a
> then return a
Expand Down
7 changes: 5 additions & 2 deletions examples/NewtonCoiter.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -7,9 +7,11 @@ to find zeroes of a function is one such algorithm.
> {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, UndecidableInstances #-}
> module Main where

> import Control.Comonad.Trans.Coiter
> import Control.Comonad.Env
> import Control.Comonad.Trans.Coiter
> import Control.Comonad.Trans.Env (lowerEnvT)
> import Data.Foldable (toList, find)
> import Data.Functor.Identity (Identity(..))

> data Function = Function {
> -- Function to find zeroes of
Expand Down Expand Up @@ -75,7 +77,8 @@ future and check if the result improves at all.

> estimateOutlook :: Int -> Solution Result -> Outlook
> estimateOutlook sampleSize solution =
> let sample = map ferror $ take sampleSize $ tail $ toList solution in
> let sample = map ferror $ take sampleSize $ toList $ snd $ runIdentity $
> lowerEnvT $ runCoiterT solution in
> let result' = extract solution in
> Outlook { result = result',
> progress = ferror result' > minimum sample }
Expand Down

0 comments on commit 38f4f07

Please sign in to comment.