[Haskell-cafe] Why is it so different between 6.12.1 and 6.10.4_1 ?

zaxis z_axis at 163.com
Sat Mar 27 21:35:19 EDT 2010


Both 6.10 and 6.12 use same .ghci !
%cat ~/.ghci
:cd /media/G/www/qachina/db/doc/money
:l Money

%cat Money.hs|grep import
import System( getArgs )
import System.Random
import System.IO
import System.Time
import Text.Printf (printf)
import Text.Regex
import Data.List
import Data.Time.Calendar
import Data.Time.Calendar.WeekDate 
import Control.Monad

Sincerely!


Yusaku Hashimoto wrote:
> 
> Hmm, When a ghci was started, there should be the only loaded module
> (Prelude.) And in both 6.10 and 6.12, such instance is not defined or
> exported in its Prelude. So please try `ghci -ignore-dot-ghci`. It
> invokes ghci without reading ~/.ghci and ./.ghci.
> 
> And `((->) a)` is known as the Reader Monad, `a` can be regarded as
> the environment. My typical usage of that is like following:
> 
>     import Control.Monad
> 
>     data Vec = Vec { x :: Int, y :: Int }
>     absolute :: Vec -> Double
>     absolute = sqrt . fromIntegral . liftM2 (+) (square . x) (square . y)
>       where
>         square a = a * a
> 
> The definition of `absolute` above can be rewritten as
> 
>     absolute p = sqrt . fromIntegral $ square (x p) + square (y p)
>       where
>         square a = a * a
> 
> How `square . x` and `square . y` share the argument? Because `Monad
> ((->) a)` is defined as
> 
>     instance Monad ((->) a) where
>         return x = \a -> x
>         m >>= f = \a -> f (m a) a
> 
> Note `(>>=)` propagates `a` into both of its arguments. That's why the
> functions read same argument.
> 
> HTH
> -nwn
> 
> On Sat, Mar 27, 2010 at 3:31 PM, zaxis <z_axis at 163.com> wrote:
>>
>> I just start ghci from shell and do nothing else. In fact, i really donot
>> know `Monad ((->) a) ` . Would you mind expplain it ?
>>
>>
>> Yusaku Hashimoto wrote:
>>>
>>> Did you import the module includes the instance of Monad ((->) e)
>>> somewhere in your code loaded in ghci?
>>>
>>> I tried this on a fresh ghci 6.12, but I got "No instance" error.
>>>
>>> -nwn
>>>
>>> On Sat, Mar 27, 2010 at 9:20 AM, zaxis <z_axis at 163.com> wrote:
>>>>
>>>> In 6.12.1 under archlinux
>>>>>let f x y z = x + y + z
>>>>> :t f
>>>> f :: (Num a) => a -> a -> a -> a
>>>>
>>>>> :t (>>=) . f
>>>> (>>=) . f :: (Num a) => a -> ((a -> a) -> a -> b) -> a -> b
>>>>> ((>>=) . f) 1 (\f x -> f x) 2
>>>> 5
>>>>
>>>> In 6.10.4_1 under freebsd
>>>>> let f x y z = x + y + z
>>>> *Money> :t f
>>>> f :: (Num a) => a -> a -> a -> a
>>>>
>>>>> :t (>>=) . f
>>>> (>>=) . f  :: (Monad ((->) a), Num a) => a -> ((a -> a) -> a -> b) -> a
>>>> -> b
>>>>> ((>>=) . f) 1 (\f x -> f x) 2
>>>>
>>>> <interactive>:1:1:
>>>>    No instance for (Monad ((->) a))
>>>>      arising from a use of `>>=' at <interactive>:1:1-5
>>>>    Possible fix: add an instance declaration for (Monad ((->) a))
>>>>    In the first argument of `(.)', namely `(>>=)'
>>>>    In the expression: ((>>=) . f) 1 (\ f x -> f x) 2
>>>>    In the definition of `it': it = ((>>=) . f) 1 (\ f x -> f x) 2
>>>>
>>>> Sincerely!
>>>>
>>>>
>>>> -----
>>>> fac n = let {  f = foldr (*) 1 [1..n] } in f
>>>> --
>>>> View this message in context:
>>>> http://old.nabble.com/Why-is-it-so-different-between-6.12.1-and-6.10.4_1---tp28049329p28049329.html
>>>> Sent from the Haskell - Haskell-Cafe mailing list archive at
>>>> Nabble.com.
>>>>
>>>> _______________________________________________
>>>> Haskell-Cafe mailing list
>>>> Haskell-Cafe at haskell.org
>>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>>
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
>>>
>>
>>
>> -----
>> fac n = let {  f = foldr (*) 1 [1..n] } in f
>> --
>> View this message in context:
>> http://old.nabble.com/Why-is-it-so-different-between-6.12.1-and-6.10.4_1---tp28049329p28050535.html
>> Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
>>
>> _______________________________________________
>> Haskell-Cafe mailing list
>> Haskell-Cafe at haskell.org
>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 


-----
fac n = let {  f = foldr (*) 1 [1..n] } in f 
-- 
View this message in context: http://old.nabble.com/Why-is-it-so-different-between-6.12.1-and-6.10.4_1---tp28049329p28056706.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.



More information about the Haskell-Cafe mailing list